From gitlab at gitlab.haskell.org Sun Nov 1 00:14:33 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 20:14:33 -0400 Subject: [Git][ghc/ghc][wip/T17609] 1021 commits: Fix unboxed-sums GC ptr-slot rubbish value (#17791) Message-ID: <5f9dfde9d13e4_7853fb6603f4f201766f1@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: 951c1fb0 by Sylvain Henry at 2020-05-09T21:46:38-04:00 Fix unboxed-sums GC ptr-slot rubbish value (#17791) This patch allows boot libraries to use unboxed sums without implicitly depending on `base` package because of `absentSumFieldError`. See updated Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make - - - - - b352d63c by Ben Gamari at 2020-05-09T21:47:14-04:00 rts: Make non-existent linker search path merely a warning As noted in #18105, previously this resulted in a rather intrusive error message. This is in contrast to the general expectation that search paths are merely places to look, not places that must exist. Fixes #18105. - - - - - cf4f1e2f by Ben Gamari at 2020-05-13T02:02:33-04:00 rts/CNF: Fix fixup comparison function Previously we would implicitly convert the difference between two words to an int, resulting in an integer overflow on 64-bit machines. Fixes #16992 - - - - - a03da9bf by Ömer Sinan Ağacan at 2020-05-13T02:03:16-04:00 Pack some of IdInfo fields into a bit field This reduces residency of compiler quite a bit on some programs. Example stats when building T10370: Before: 2,871,242,832 bytes allocated in the heap 4,693,328,008 bytes copied during GC 33,941,448 bytes maximum residency (276 sample(s)) 375,976 bytes maximum slop 83 MiB total memory in use (0 MB lost due to fragmentation) After: 2,858,897,344 bytes allocated in the heap 4,629,255,440 bytes copied during GC 32,616,624 bytes maximum residency (278 sample(s)) 314,400 bytes maximum slop 80 MiB total memory in use (0 MB lost due to fragmentation) So -3.9% residency, -1.3% bytes copied and -0.4% allocations. Fixes #17497 Metric Decrease: T9233 T9675 - - - - - 670c3e5c by Ben Gamari at 2020-05-13T02:03:54-04:00 get-win32-tarballs: Fix base URL Revert a change previously made for testing purposes. - - - - - 8ad8dc41 by Ben Gamari at 2020-05-13T02:03:54-04:00 get-win32-tarballs: Improve diagnostics output - - - - - 8c0740b7 by Simon Jakobi at 2020-05-13T02:04:33-04:00 docs: Add examples for Data.Semigroup.Arg{Min,Max} Context: #17153 - - - - - cb22348f by Ben Gamari at 2020-05-13T02:05:11-04:00 Add few cleanups of the CAF logic Give the NameSet of non-CAFfy names a proper newtype to distinguish it from all of the other NameSets floating about. - - - - - 90e38b81 by Emeka Nkurumeh at 2020-05-13T02:05:51-04:00 fix printf warning when using with ghc with clang on mingw - - - - - 86d8ac22 by Sebastian Graf at 2020-05-13T02:06:29-04:00 CprAnal: Don't attach CPR sigs to expandable bindings (#18154) Instead, look through expandable unfoldings in `cprTransform`. See the new Note [CPR for expandable unfoldings]: ``` Long static data structures (whether top-level or not) like xs = x1 : xs1 xs1 = x2 : xs2 xs2 = x3 : xs3 should not get CPR signatures, because they * Never get WW'd, so their CPR signature should be irrelevant after analysis (in fact the signature might even be harmful for that reason) * Would need to be inlined/expanded to see their constructed product * Recording CPR on them blows up interface file sizes and is redundant with their unfolding. In case of Nested CPR, this blow-up can be quadratic! But we can't just stop giving DataCon application bindings the CPR property, for example fac 0 = 1 fac n = n * fac (n-1) fac certainly has the CPR property and should be WW'd! But FloatOut will transform the first clause to lvl = 1 fac 0 = lvl If lvl doesn't have the CPR property, fac won't either. But lvl doesn't have a CPR signature to extrapolate into a CPR transformer ('cprTransform'). So instead we keep on cprAnal'ing through *expandable* unfoldings for these arity 0 bindings via 'cprExpandUnfolding_maybe'. In practice, GHC generates a lot of (nested) TyCon and KindRep bindings, one for each data declaration. It's wasteful to attach CPR signatures to each of them (and intractable in case of Nested CPR). ``` Fixes #18154. - - - - - e34bf656 by Ben Gamari at 2020-05-13T02:07:08-04:00 users-guide: Add discussion of shared object naming Fixes #18074. - - - - - 5d0f2445 by Ben Gamari at 2020-05-13T02:07:47-04:00 testsuite: Print sign of performance changes Executes the minor formatting change in the tabulated performance changes suggested in #18135. - - - - - 9e4b981f by Ben Gamari at 2020-05-13T02:08:24-04:00 testsuite: Add testcase for #18129 - - - - - 266310c3 by Ivan-Yudin at 2020-05-13T02:09:03-04:00 doc: Reformulate the opening paragraph of Ch. 4 in User's guide Removes mentioning of Hugs (it is not helpful for new users anymore). Changes the wording for the rest of the paragraph. Fixes #18132. - - - - - 55e35c0b by Baldur Blöndal at 2020-05-13T20:02:48-04:00 Predicate, Equivalence derive via `.. -> a -> All' - - - - - d7e0b57f by Alp Mestanogullari at 2020-05-13T20:03:30-04:00 hadrian: add a --freeze2 option to freeze stage 1 and 2 - - - - - d880d6b2 by Artem Pelenitsyn at 2020-05-13T20:04:11-04:00 Don't reload environment files on every setSessionDynFlags Makes `interpretPackageEnv` (which loads envirinment files) a part of `parseDynamicFlags` (parsing command-line arguments, which is typically done once) instead of `setSessionDynFlags` (which is typically called several times). Making several (transitive) calls to `interpretPackageEnv`, as before, caused #18125 #16318, which should be fixed now. - - - - - 102cfd67 by Ryan Scott at 2020-05-13T20:04:46-04:00 Factor out HsPatSigType for pat sigs/RULE term sigs (#16762) This implements chunks (2) and (3) of https://gitlab.haskell.org/ghc/ghc/issues/16762#note_270170. Namely, it introduces a dedicated `HsPatSigType` AST type, which represents the types that can appear in pattern signatures and term-level `RULE` binders. Previously, these were represented with `LHsSigWcType`. Although `LHsSigWcType` is isomorphic to `HsPatSigType`, the intended semantics of the two types are slightly different, as evidenced by the fact that they have different code paths in the renamer and typechecker. See also the new `Note [Pattern signature binders and scoping]` in `GHC.Hs.Types`. - - - - - b17574f7 by Hécate at 2020-05-13T20:05:28-04:00 fix(documentation): Fix the RST links to GHC.Prim - - - - - df021fb1 by Baldur Blöndal at 2020-05-13T20:06:06-04:00 Document (->) using inferred quantification for its runtime representations. Fixes #18142. - - - - - 1a93ea57 by Takenobu Tani at 2020-05-13T20:06:54-04:00 Tweak man page for ghc command This commit updates the ghc command's man page as followings: * Enable `man_show_urls` to show URL addresses in the `DESCRIPTION` section of ghc.rst, because sphinx currently removes hyperlinks for man pages. * Add a `SEE ALSO` section to point to the GHC homepage - - - - - a951e1ba by Takenobu Tani at 2020-05-13T20:07:37-04:00 GHCi: Add link to the user's guide in help message This commit adds a link to the user's guide in ghci's `:help` message. Newcomers could easily reach to details of ghci. - - - - - 404581ea by Jeff Happily at 2020-05-13T20:08:15-04:00 Handle single unused import - - - - - 1c999e5d by Ben Gamari at 2020-05-13T20:09:07-04:00 Ensure that printMinimalImports closes handle Fixes #18166. - - - - - c9f5a8f4 by Ben Gamari at 2020-05-13T20:09:51-04:00 hadrian: Tell testsuite driver about LLVM availability This reflects the logic present in the Make build system into Hadrian. Fixes #18167. - - - - - c05c0659 by Simon Jakobi at 2020-05-14T03:31:21-04:00 Improve some folds over Uniq[D]FM * Replace some non-deterministic lazy folds with strict folds. * Replace some O(n log n) folds in deterministic order with O(n) non-deterministic folds. * Replace some folds with set-operations on the underlying IntMaps. This reduces max residency when compiling `nofib/spectral/simple/Main.hs` with -O0 by about 1%. Maximum residency when compiling Cabal also seems reduced on the order of 3-9%. - - - - - 477f13bb by Simon Jakobi at 2020-05-14T03:31:58-04:00 Use Data.IntMap.disjoint Data.IntMap gained a dedicated `disjoint` function in containers-0.6.2.1. This patch applies this function where appropriate in hopes of modest compiler performance improvements. Closes #16806. - - - - - e9c0110c by Ben Gamari at 2020-05-14T12:25:53-04:00 IdInfo: Add reference to bitfield-packing ticket - - - - - 9bd20e83 by Sebastian Graf at 2020-05-15T10:42:09-04:00 DmdAnal: Improve handling of precise exceptions This patch does two things: Fix possible unsoundness in what was called the "IO hack" and implement part 2.1 of the "fixing precise exceptions" plan in https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions, which, in combination with !2956, supersedes !3014 and !2525. **IO hack** The "IO hack" (which is a fallback to preserve precise exceptions semantics and thus soundness, rather than some smart thing that increases precision) is called `exprMayThrowPreciseException` now. I came up with two testcases exemplifying possible unsoundness (if twisted enough) in the old approach: - `T13380d`: Demonstrating unsoundness of the "IO hack" when resorting to manual state token threading and direct use of primops. More details below. - `T13380e`: Demonstrating unsoundness of the "IO hack" when we have Nested CPR. Not currently relevant, as we don't have Nested CPR yet. - `T13380f`: Demonstrating unsoundness of the "IO hack" for safe FFI calls. Basically, the IO hack assumed that precise exceptions can only be thrown from a case scrutinee of type `(# State# RealWorld, _ #)`. I couldn't come up with a program using the `IO` abstraction that violates this assumption. But it's easy to do so via manual state token threading and direct use of primops, see `T13380d`. Also similar code might be generated by Nested CPR in the (hopefully not too) distant future, see `T13380e`. Hence, we now have a more careful test in `forcesRealWorld` that passes `T13380{d,e}` (and will hopefully be robust to Nested CPR). **Precise exceptions** In #13380 and #17676 we saw that we didn't preserve precise exception semantics in demand analysis. We fixed that with minimal changes in !2956, but that was terribly unprincipled. That unprincipledness resulted in a loss of precision, which is tracked by these new test cases: - `T13380b`: Regression in dead code elimination, because !2956 was too syntactic about `raiseIO#` - `T13380c`: No need to apply the "IO hack" when the IO action may not throw a precise exception (and the existing IO hack doesn't detect that) Fixing both issues in !3014 turned out to be too complicated and had the potential to regress in the future. Hence we decided to only fix `T13380b` and augment the `Divergence` lattice with a new middle-layer element, `ExnOrDiv`, which means either `Diverges` (, throws an imprecise exception) or throws a *precise* exception. See the wiki page on Step 2.1 for more implementational details: https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions#dead-code-elimination-for-raiseio-with-isdeadenddiv-introducing-exnordiv-step-21 - - - - - 568d7279 by Ben Gamari at 2020-05-15T10:42:46-04:00 GHC.Cmm.Opt: Handle MO_XX_Conv This MachOp was introduced by 2c959a1894311e59cd2fd469c1967491c1e488f3 but a wildcard match in cmmMachOpFoldM hid the fact that it wasn't handled. Ideally we would eliminate the match but this appears to be a larger task. Fixes #18141. - - - - - 5bcf8606 by Ryan Scott at 2020-05-17T08:46:38-04:00 Remove duplicate Note [When to print foralls] in GHC.Core.TyCo.Ppr There are two different Notes named `[When to print foralls]`. The most up-to-date one is in `GHC.Iface.Type`, but there is a second one in `GHC.Core.TyCo.Ppr`. The latter is less up-to-date, as it was written before GHC switched over to using ifaces to pretty-print types. I decided to just remove the latter and replace it with a reference to the former. [ci skip] - - - - - 55f0e783 by Fumiaki Kinoshita at 2020-05-21T12:10:44-04:00 base: Add Generic instances to various datatypes under GHC.* * GHC.Fingerprint.Types: Fingerprint * GHC.RTS.Flags: GiveGCStats, GCFlags, ConcFlags, DebugFlags, CCFlags, DoHeapProfile, ProfFlags, DoTrace, TraceFlags, TickyFlags, ParFlags and RTSFlags * GHC.Stats: RTSStats and GCStats * GHC.ByteOrder: ByteOrder * GHC.Unicode: GeneralCategory * GHC.Stack.Types: SrcLoc Metric Increase: haddock.base - - - - - a9311cd5 by Gert-Jan Bottu at 2020-05-21T12:11:31-04:00 Explicit Specificity Implementation for Ticket #16393. Explicit specificity allows users to manually create inferred type variables, by marking them with braces. This way, the user determines which variables can be instantiated through visible type application. The additional syntax is included in the parser, allowing users to write braces in type variable binders (type signatures, data constructors etc). This information is passed along through the renamer and verified in the type checker. The AST for type variable binders, data constructors, pattern synonyms, partial signatures and Template Haskell has been updated to include the specificity of type variables. Minor notes: - Bumps haddock submodule - Disables pattern match checking in GHC.Iface.Type with GHC 8.8 - - - - - 24e61aad by Ben Price at 2020-05-21T12:12:17-04:00 Lint should say when it is checking a rule It is rather confusing that when lint finds an error in a rule attached to a binder, it reports the error as in the RHS, not the rule: ... In the RHS of foo We add a clarifying line: ... In the RHS of foo In a rule attached to foo The implication that the rule lives inside the RHS is a bit odd, but this niggle is already present for unfoldings, whose pattern we are following. - - - - - 78c6523c by Ben Gamari at 2020-05-21T12:13:01-04:00 nonmoving: Optimise the write barrier - - - - - 13f6c9d0 by Andreas Klebinger at 2020-05-21T12:13:45-04:00 Refactor linear reg alloc to remember past assignments. When assigning registers we now first try registers we assigned to in the past, instead of picking the "first" one. This is in extremely helpful when dealing with loops for which variables are dead for part of the loop. This is important for patterns like this: foo = arg1 loop: use(foo) ... foo = getVal() goto loop; There we: * assign foo to the register of arg1. * use foo, it's dead after this use as it's overwritten after. * do other things. * look for a register to put foo in. If we pick an arbitrary one it might differ from the register the start of the loop expect's foo to be in. To fix this we simply look for past register assignments for the given variable. If we find one and the register is free we use that register. This reduces the need for fixup blocks which match the register assignment between blocks. In the example above between the end and the head of the loop. This patch also moves branch weight estimation ahead of register allocation and adds a flag to control it (cmm-static-pred). * It means the linear allocator is more likely to assign the hotter code paths first. * If it assign these first we are: + Less likely to spill on the hot path. + Less likely to introduce fixup blocks on the hot path. These two measure combined are surprisingly effective. Based on nofib we get in the mean: * -0.9% instructions executed * -0.1% reads/writes * -0.2% code size. * -0.1% compiler allocations. * -0.9% compile time. * -0.8% runtime. Most of the benefits are simply a result of removing redundant moves and spills. Reduced compiler allocations likely are the result of less code being generated. (The added lookup is mostly non-allocating). - - - - - edc2cc58 by Andreas Klebinger at 2020-05-21T12:14:25-04:00 NCG: Codelayout: Distinguish conditional and other branches. In #18053 we ended up with a suboptimal code layout because the code layout algorithm didn't distinguish between conditional and unconditional control flow. We can completely eliminate unconditional control flow instructions by placing blocks next to each other, not so much for conditionals. In terms of implementation we simply give conditional branches less weight before computing the layout. Fixes #18053 - - - - - b7a6b2f4 by Gleb Popov at 2020-05-21T12:15:26-04:00 gitlab-ci: Set locale to C.UTF-8. - - - - - a8c27cf6 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Allow spaces in GHCi :script file names This patch updates the user interface of GHCi so that file names passed to the ':script' command may contain spaces escaped with a backslash. For example: :script foo\ bar.script The implementation uses a modified version of 'words' that does not break on escaped spaces. Fixes #18027. - - - - - 82663959 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Add extra tests for GHCi :script syntax checks The syntax for GHCi's ":script" command allows for only a single file name to be passed as an argument. This patch adds a test for the cases in which a file name is missing or multiple file names are passed. Related to #T18027. - - - - - a0b79e1b by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Allow GHCi :script file names in double quotes This patch updates the user interface of GHCi so that file names passed to the ':script' command can be wrapped in double quotes. For example: :script "foo bar.script" The implementation uses a modified version of 'words' that treats character sequences enclosed in double quotes as single words. Fixes #18027. - - - - - cf566330 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Update documentation for GHCi :script This patch adds the fixes that allow for file names containing spaces to be passed to GHCi's ':script' command to the release notes for 8.12 and expands the user-guide documentation for ':script' by mentioning how such file names can be passed. Related to #18027. - - - - - 0004ccb8 by Tuan Le at 2020-05-21T12:16:46-04:00 llvmGen: Consider Relocatable read-only data as not constantReferences: #18137 - - - - - 964d3ea2 by John Ericson at 2020-05-21T12:17:30-04:00 Use `Checker` for `tc_pat` - - - - - b797aa42 by John Ericson at 2020-05-21T12:17:30-04:00 Use `Checker` for `tc_lpat` and `tc_lpats` - - - - - 5108e84a by John Ericson at 2020-05-21T12:17:30-04:00 More judiciously panic in `ts_pat` - - - - - 510e0451 by John Ericson at 2020-05-21T12:17:30-04:00 Put `PatEnv` first in `GHC.Tc.Gen.Pat.Checker` - - - - - cb4231db by John Ericson at 2020-05-21T12:17:30-04:00 Tiny cleaup eta-reduce away a function argument In GHC, not in the code being compiled! - - - - - 6890c38d by John Ericson at 2020-05-21T12:17:30-04:00 Use braces with do in `SplicePat` case for consistency - - - - - 3451584f by buggymcbugfix at 2020-05-21T12:18:06-04:00 Fix spelling mistakes and typos - - - - - b552e531 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Add INLINABLE pragmas to Enum list producers The INLINABLE pragmas ensure that we export stable (unoptimised) unfoldings in the interface file so we can do list fusion at usage sites. Related tickets: #15185, #8763, #18178. - - - - - e7480063 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Piggyback on Enum Word methods for Word64 If we are on a 64 bit platform, we can use the efficient Enum Word methods for the Enum Word64 instance. - - - - - 892b0c41 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Document INLINE(ABLE) pragmas that enable fusion - - - - - 2b363ebb by Richard Eisenberg at 2020-05-21T12:18:45-04:00 MR template should ask for key part - - - - - a95bbd0b by Sebastian Graf at 2020-05-21T12:19:37-04:00 Make `Int`'s `mod` and `rem` strict in their first arguments They used to be strict until 4d2ac2d (9 years ago). It's obviously better to be strict for performance reasons. It also blocks #18067. NoFib results: ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- integer -1.1% +0.4% wheel-sieve2 +21.2% +20.7% -------------------------------------------------------------------------------- Min -1.1% -0.0% Max +21.2% +20.7% Geometric Mean +0.2% +0.2% ``` The regression in `wheel-sieve2` is due to reboxing that likely will go away with the resolution of #18067. See !3282 for details. Fixes #18187. - - - - - d3d055b8 by Galen Huntington at 2020-05-21T12:20:18-04:00 Clarify pitfalls of NegativeLiterals; see #18022. - - - - - 1b508a9e by Alexey Kuleshevich at 2020-05-21T12:21:02-04:00 Fix wording in primops documentation to reflect the correct reasoning: * Besides resizing functions, shrinking ones also mutate the size of a mutable array and because of those two `sizeofMutabeByteArray` and `sizeofSmallMutableArray` are now deprecated * Change reference in documentation to the newer functions `getSizeof*` instead of `sizeof*` for shrinking functions * Fix incorrect mention of "byte" instead of "small" - - - - - 4ca0c8a1 by Andreas Klebinger at 2020-05-21T12:21:53-04:00 Don't variable-length encode magic iface constant. We changed to use variable length encodings for many types by default, including Word32. This makes sense for numbers but not when Word32 is meant to represent four bytes. I added a FixedLengthEncoding newtype to Binary who's instances interpret their argument as a collection of bytes instead of a number. We then use this when writing/reading magic numbers to the iface file. I also took the libery to remove the dummy iface field. This fixes #18180. - - - - - a1275081 by Krzysztof Gogolewski at 2020-05-21T12:22:35-04:00 Add a regression test for #11506 The testcase works now. See explanation in https://gitlab.haskell.org/ghc/ghc/issues/11506#note_273202 - - - - - 8a816e5f by Krzysztof Gogolewski at 2020-05-21T12:23:55-04:00 Sort deterministically metric output Previously, we sorted according to the test name and way, but the metrics (max_bytes_used/peak_megabytes_allocated etc.) were appearing in nondeterministic order. - - - - - 566cc73f by Sylvain Henry at 2020-05-21T12:24:45-04:00 Move isDynLinkName into GHC.Types.Name It doesn't belong into GHC.Unit.State - - - - - d830bbc9 by Adam Sandberg Ericsson at 2020-05-23T13:36:20-04:00 docs: fix formatting and add some links [skip ci] - - - - - 49301ad6 by Andrew Martin at 2020-05-23T13:37:01-04:00 Implement cstringLength# and FinalPtr This function and its accompanying rule resolve issue #5218. A future PR to the bytestring library will make the internal Data.ByteString.Internal.unsafePackAddress compute string length with cstringLength#. This will improve the status quo because it is eligible for constant folding. Additionally, introduce a new data constructor to ForeignPtrContents named FinalPtr. This additional data constructor, when used in the IsString instance for ByteString, leads to more Core-to-Core optimization opportunities, fewer runtime allocations, and smaller binaries. Also, this commit re-exports all the functions from GHC.CString (including cstringLength#) in GHC.Exts. It also adds a new test driver. This test driver is used to perform substring matches on Core that is dumped after all the simplifier passes. In this commit, it is used to check that constant folding of cstringLength# works. - - - - - dcd6bdcc by Ben Gamari at 2020-05-23T13:37:48-04:00 simplCore: Ignore ticks in rule templates This fixes #17619, where a tick snuck in to the template of a rule, resulting in a panic during rule matching. The tick in question was introduced via post-inlining, as discussed in `Note [Simplifying rules]`. The solution we decided upon was to simply ignore ticks in the rule template, as discussed in `Note [Tick annotations in RULE matching]`. Fixes #18162. Fixes #17619. - - - - - 82cb8913 by John Ericson at 2020-05-23T13:38:32-04:00 Fix #18145 and also avoid needless work with implicit vars - `forAllOrNothing` now is monadic, so we can trace whether we bind an explicit `forall` or not. - #18145 arose because the free vars calculation was needlessly complex. It is now greatly simplified. - Replaced some other implicit var code with `filterFreeVarsToBind`. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - a60dc835 by Ben Gamari at 2020-05-23T13:39:12-04:00 Bump process submodule Fixes #17926. - - - - - 856adf54 by Ben Gamari at 2020-05-23T13:40:21-04:00 users-guide: Clarify meaning of -haddock flag Fixes #18206. - - - - - 7ae57afd by Ben Gamari at 2020-05-23T13:41:03-04:00 git: Add ignored commits file This can be used to tell git to ignore bulk renaming commits like the recently-finished module hierarchy refactoring. Configured with, git config blame.ignoreRevsFile .git-ignore-revs - - - - - 63d30e60 by jneira at 2020-05-24T01:54:42-04:00 Add hie-bios script for windows systems It is a direct translation of the sh script - - - - - 59182b88 by jneira at 2020-05-24T01:54:42-04:00 Honour previous values for CABAL and CABFLAGS The immediate goal is let the hie-bios.bat script set CABFLAGS with `-v0` and remove all cabal output except the compiler arguments - - - - - 932dc54e by jneira at 2020-05-24T01:54:42-04:00 Add specific configuration for windows in hie.yaml - - - - - e0eda070 by jneira at 2020-05-24T01:54:42-04:00 Remove not needed hie-bios output - - - - - a0ea59d6 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Move Config module into GHC.Settings - - - - - 37430251 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Rename GHC.Core.Arity into GHC.Core.Opt.Arity - - - - - a426abb9 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Rename GHC.Hs.Types into GHC.Hs.Type See discussion in https://gitlab.haskell.org/ghc/ghc/issues/13009#note_268610 - - - - - 1c91a7a0 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Bump haddock submodule - - - - - 66bd24d1 by Ryan Scott at 2020-05-24T01:56:03-04:00 Add orderingTyCon to wiredInTyCons (#18185) `Ordering` needs to be wired in for use in the built-in `CmpNat` and `CmpSymbol` type families, but somehow it was never added to the list of `wiredInTyCons`, leading to the various oddities observed in #18185. Easily fixed by moving `orderingTyCon` from `basicKnownKeyNames` to `wiredInTyCons`. Fixes #18185. - - - - - 01c43634 by Matthew Pickering at 2020-05-24T01:56:42-04:00 Remove unused hs-boot file - - - - - 7a07aa71 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix cross-compiler build (#16051) - - - - - 15ccca16 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix distDir per stage - - - - - b420fb24 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix hp2ps error during cross-compilation Fixed by @alp (see https://gitlab.haskell.org/ghc/ghc/issues/16051#note_274265) - - - - - cd339ef0 by Joshua Price at 2020-05-24T15:22:56-04:00 Make Unicode brackets opening/closing tokens (#18225) The tokens `[|`, `|]`, `(|`, and `|)` are opening/closing tokens as described in GHC Proposal #229. This commit makes the unicode variants (`⟦`, `⟧`, `⦇`, and `⦈`) act the same as their ASCII counterparts. - - - - - 013d7120 by Ben Gamari at 2020-05-25T09:48:17-04:00 Revert "Specify kind variables for inferred kinds in base." As noted in !3132, this has rather severe knock-on consequences in user-code. We'll need to revisit this before merging something along these lines. This reverts commit 9749fe1223d182b1f8e7e4f7378df661c509f396. - - - - - 4c4312ed by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Drop redundant ad-hoc boot module check To determine whether the module is a boot module Coverage.addTicksToBinds was checking for a `boot` suffix in the module source filename. This is quite ad-hoc and shouldn't be necessary; the callsite in `deSugar` already checks that the module isn't a boot module. - - - - - 1abf3c84 by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Make tickBoxCount strict This could otherwise easily cause a leak of (+) thunks. - - - - - b2813750 by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Make ccIndices strict This just seems like a good idea. - - - - - 02e278eb by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Don't produce ModBreaks if not HscInterpreted emptyModBreaks contains a bottom and consequently it's important that we don't use it unless necessary. - - - - - b8c014ce by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Factor out addMixEntry - - - - - 53814a64 by Zubin Duggal at 2020-05-26T03:03:24-04:00 Add info about typeclass evidence to .hie files See `testsuite/tests/hiefile/should_run/HieQueries.hs` and `testsuite/tests/hiefile/should_run/HieQueries.stdout` for an example of this We add two new fields, `EvidenceVarBind` and `EvidenceVarUse` to the `ContextInfo` associated with an Identifier. These are associated with the appropriate identifiers for the evidence variables collected when we come across `HsWrappers`, `TcEvBinds` and `IPBinds` while traversing the AST. Instance dictionary and superclass selector dictionaries from `tcg_insts` and classes defined in `tcg_tcs` are also recorded in the AST as originating from their definition span This allows us to save a complete picture of the evidence constructed by the constraint solver, and will let us report this to the user, enabling features like going to the instance definition from the invocation of a class method(or any other method taking a constraint) and finding all usages of a particular instance. Additionally, - Mark NodeInfo with an origin so we can differentiate between bindings origininating in the source vs those in ghc - Along with typeclass evidence info, also include information on Implicit Parameters - Add a few utility functions to HieUtils in order to query the new info Updates haddock submodule - - - - - 6604906c by Sebastian Graf at 2020-05-26T03:04:04-04:00 Make WorkWrap.Lib.isWorkerSmallEnough aware of the old arity We should allow a wrapper with up to 82 parameters when the original function had 82 parameters to begin with. I verified that this made no difference on NoFib, but then again it doesn't use huge records... Fixes #18122. - - - - - cf772f19 by Sylvain Henry at 2020-05-26T03:04:45-04:00 Enhance Note [About units] for Backpack - - - - - ede24126 by Takenobu Tani at 2020-05-27T00:13:55-04:00 core-spec: Modify file paths according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * GHC/Core.hs <= coreSyn/CoreSyn.hs * GHC/Core/Coercion.hs <= types/Coercion.hs * GHC/Core/Coercion/Axiom.hs <= types/CoAxiom.hs * GHC/Core/Coercion/Opt.hs <= types/OptCoercion.hs * GHC/Core/DataCon.hs <= basicTypes/DataCon.hs * GHC/Core/FamInstEnv.hs <= types/FamInstEnv.hs * GHC/Core/Lint.hs <= coreSyn/CoreLint.hs * GHC/Core/Subst.hs <= coreSyn/CoreSubst.hs * GHC/Core/TyCo/Rep.hs <= types/TyCoRep.hs * GHC/Core/TyCon.hs <= types/TyCon.hs * GHC/Core/Type.hs <= types/Type.hs * GHC/Core/Unify.hs <= types/Unify.hs * GHC/Types/Literal.hs <= basicTypes/Literal.hs * GHC/Types/Var.hs <= basicTypes/Var.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [skip ci] - - - - - 04750304 by Ben Gamari at 2020-05-27T00:14:33-04:00 eventlog: Fix racy flushing Previously no attempt was made to avoid multiple threads writing their capability-local eventlog buffers to the eventlog writer simultaneously. This could result in multiple eventlog streams being interleaved. Fix this by documenting that the EventLogWriter's write() and flush() functions may be called reentrantly and fix the default writer to protect its FILE* by a mutex. Fixes #18210. - - - - - d6203f24 by Joshua Price at 2020-05-27T00:15:17-04:00 Make `identifier` parse unparenthesized `->` (#18060) - - - - - 28deee28 by Ben Gamari at 2020-05-28T16:23:21-04:00 GHC.Core.Unfold: Refactor traceInline This reduces duplication as well as fixes a bug wherein -dinlining-check would override -ddump-inlinings. Moreover, the new variant - - - - - 1f393e1e by Ben Gamari at 2020-05-28T16:23:21-04:00 Avoid unnecessary allocations due to tracing utilities While ticky-profiling the typechecker I noticed that hundreds of millions of SDocs are being allocated just in case -ddump-*-trace is enabled. This is awful. We avoid this by ensuring that the dump flag check is inlined into the call site, ensuring that the tracing document needn't be allocated unless it's actually needed. See Note [INLINE conditional tracing utilities] for details. Fixes #18168. Metric Decrease: T9961 haddock.Cabal haddock.base haddock.compiler - - - - - 5f621a78 by Vladislav Zavialov at 2020-05-28T16:23:58-04:00 Add Semigroup/Monoid for Q (#18123) - - - - - dc5f004c by Xavier Denis at 2020-05-28T16:24:37-04:00 Fix #18071 Run the core linter on candidate instances to ensure they are well-kinded. Better handle quantified constraints by using a CtWanted to avoid having unsolved constraints thrown away at the end by the solver. - - - - - 10e6982c by Sebastian Graf at 2020-05-28T16:25:14-04:00 FloatOut: Only eta-expand dead-end RHS if arity will increase (#18231) Otherwise we risk turning trivial RHS into non-trivial RHS, introducing unnecessary bindings in the next Simplifier run, resulting in more churn. Fixes #18231. - - - - - 08dab5f7 by Sebastian Graf at 2020-05-28T16:25:14-04:00 DmdAnal: Recognise precise exceptions from case alternatives (#18086) Consider ```hs m :: IO () m = do putStrLn "foo" error "bar" ``` `m` (from #18086) always throws a (precise or imprecise) exception or diverges. Yet demand analysis infers `<L,A>` as demand signature instead of `<L,A>x` for it. That's because the demand analyser sees `putStrLn` occuring in a case scrutinee and decides that it has to `deferAfterPreciseException`, because `putStrLn` throws a precise exception on some control flow paths. This will mask the `botDiv` `Divergence`of the single case alt containing `error` to `topDiv`. Since `putStrLn` has `topDiv` itself, the final `Divergence` is `topDiv`. This is easily fixed: `deferAfterPreciseException` works by `lub`ing with the demand type of a virtual case branch denoting the precise exceptional control flow. We used `nopDmdType` before, but we can be more precise and use `exnDmdType`, which is `nopDmdType` with `exnDiv`. Now the `Divergence` from the case alt will degrade `botDiv` to `exnDiv` instead of `topDiv`, which combines with the result from the scrutinee to `exnDiv`, and all is well. Fixes #18086. - - - - - aef95f11 by Ben Gamari at 2020-05-28T16:25:53-04:00 Ticky-ticky: Record DataCon name in ticker name This makes it significantly easier to spot the nature of allocations regressions and comes at a reasonably low cost. - - - - - 8f021b8c by Ben Gamari at 2020-05-28T16:26:34-04:00 hadrian: Don't track GHC's verbosity argument Teach hadrian to ignore GHC's -v argument in its recompilation check, thus fixing #18131. - - - - - 13d9380b by Ben Gamari at 2020-05-28T16:27:20-04:00 Rip out CmmStackInfo(updfr_space) As noted in #18232, this field is currently completely unused and moreover doesn't have a clear meaning. - - - - - f10d11fa by Andreas Klebinger at 2020-05-29T01:38:42-04:00 Fix "build/elem" RULE. An redundant constraint prevented the rule from matching. Fixing this allows a call to elem on a known list to be translated into a series of equality checks, and eventually a simple case expression. Surprisingly this seems to regress elem for strings. To avoid this we now also allow foldrCString to inline and add an UTF8 variant. This results in elem being compiled to a tight non-allocating loop over the primitive string literal which performs a linear search. In the process this commit adds UTF8 variants for some of the functions in GHC.CString. This is required to make this work for both ASCII and UTF8 strings. There are also small tweaks to the CString related rules. We now allow ourselfes the luxury to compare the folding function via eqExpr, which helps to ensure the rule fires before we inline foldrCString*. Together with a few changes to allow matching on both the UTF8 and ASCII variants of the CString functions. - - - - - bbeb2389 by Ben Gamari at 2020-05-29T01:39:19-04:00 CoreToStg: Add Outputable ArgInfo instance - - - - - 0e3361ca by Simon Peyton Jones at 2020-05-29T01:39:19-04:00 Make Lint check return type of a join point Consider join x = rhs in body It's important that the type of 'rhs' is the same as the type of 'body', but Lint wasn't checking that invariant. Now it does! This was exposed by investigation into !3113. - - - - - c49f7df0 by Simon Peyton Jones at 2020-05-29T01:39:19-04:00 Do not float join points in exprIsConApp_maybe We hvae been making exprIsConApp_maybe cleverer in recent times: commit b78cc64e923716ac0512c299f42d4d0012306c05 Date: Thu Nov 15 17:14:31 2018 +0100 Make constructor wrappers inline only during the final phase commit 7833cf407d1f608bebb1d38bb99d3035d8d735e6 Date: Thu Jan 24 17:58:50 2019 +0100 Look through newtype wrappers (Trac #16254) commit c25b135ff5b9c69a90df0ccf51b04952c2dc6ee1 Date: Thu Feb 21 12:03:22 2019 +0000 Fix exprIsConApp_maybe But alas there was still a bug, now immortalised in Note [Don't float join points] in SimpleOpt. It's quite hard to trigger because it requires a dead join point, but it came up when compiling Cabal Cabal.Distribution.Fields.Lexer.hs, when working on !3113. Happily, the fix is extremly easy. Finding the bug was not so easy. - - - - - 46720997 by Ben Gamari at 2020-05-29T01:39:19-04:00 Allow simplification through runRW# Because runRW# inlines so late, we were previously able to do very little simplification across it. For instance, given even a simple program like case runRW# (\s -> let n = I# 42# in n) of I# n# -> f n# we previously had no way to avoid the allocation of the I#. This patch allows the simplifier to push strict contexts into the continuation of a runRW# application, as explained in in Note [Simplification of runRW#] in GHC.CoreToStg.Prep. Fixes #15127. Metric Increase: T9961 Metric Decrease: ManyConstructors Co-Authored-By: Simon Peyton-Jone <simonpj at microsoft.com> - - - - - 277c2f26 by Ben Gamari at 2020-05-29T01:39:55-04:00 Eta expand un-saturated primops Now since we no longer try to predict CAFfyness we have no need for the solution to #16846. Eta expanding unsaturated primop applications is conceptually simpler, especially in the presence of levity polymorphism. This essentially reverts cac8dc9f51e31e4c0a6cd9bc302f7e1bc7c03beb, as suggested in #18079. Closes #18079. - - - - - f44d7ae0 by Simon Jakobi at 2020-05-29T01:40:34-04:00 base: Scrap deprecation plan for Data.Monoid.{First,Last} See the discussion on the libraries mailing list for context: https://mail.haskell.org/pipermail/libraries/2020-April/030357.html - - - - - 8b494895 by Jeremy Schlatter at 2020-05-29T01:41:12-04:00 Fix typo in documentation - - - - - 998450f4 by Gleb Popov at 2020-05-29T01:41:53-04:00 Always define USE_PTHREAD_FOR_ITIMER for FreeBSD. - - - - - f9a513e0 by Alp Mestanogullari at 2020-05-29T01:42:36-04:00 hadrian: introduce 'install' target Its logic is very simple. It `need`s the `binary-dist-dir` target and runs suitable `configure` and `make install` commands for the user. A new `--prefix` command line argument is introduced to specify where GHC should be installed. - - - - - 67738db1 by Travis Whitaker at 2020-05-29T13:34:48-04:00 Build a threaded stage 1 if the bootstrapping GHC supports it. - - - - - aac19e6c by Peter Trommler at 2020-05-29T13:35:24-04:00 PPC NCG: No per-symbol .section ".toc" directives All position independent symbols are collected during code generation and emitted in one go. Prepending each symbol with a .section ".toc" directive is redundant. This patch drops the per-symbol directives leading to smaller assembler files. Fixes #18250 - - - - - 4413828b by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Teach getNumProcessors to return available processors Previously we would report the number of physical processors, which can be quite wrong in a containerized setting. Now we rather return how many processors are in our affinity mask when possible. I also refactored the code to prefer platform-specific since this will report logical CPUs instead of physical (using `machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD). Fixes #14781. - - - - - 1449435c by Ben Gamari at 2020-05-30T06:07:31-04:00 users-guide: Note change in getNumProcessors in users guide - - - - - 3d960169 by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Drop compatibility shims for Windows Vista We can now assume that the thread and processor group interfaces are available. - - - - - 7f8f948c by Peter Trommler at 2020-05-30T06:08:07-04:00 PPC NCG: Fix .size directive on powerpc64 ELF v1 Thanks to Sergei Trofimovich for pointing out the issue. Fixes #18237 - - - - - 7c555b05 by Andreas Klebinger at 2020-05-30T06:08:43-04:00 Optimize GHC.Utils.Monad. Many functions in this module are recursive and as such are marked loop breakers. Which means they are unlikely to get an unfolding. This is *bad*. We always want to specialize them to specific Monads. Which requires a visible unfolding at the use site. I rewrote the recursive ones from: foo f x = ... foo x' ... to foo f x = go x where go x = ... As well as giving some pragmas to make all of them available for specialization. The end result is a reduction of allocations of about -1.4% for nofib/spectral/simple/Main.hs when compiled with `-O`. ------------------------- Metric Decrease: T12425 T14683 T5631 T9233 T9675 T9961 WWRec ------------------------- - - - - - 8b1cb5df by Ben Gamari at 2020-05-30T06:09:20-04:00 Windows: Bump Windows toolchain to 0.2 - - - - - 6947231a by Zubin Duggal at 2020-05-30T06:10:02-04:00 Simplify contexts in GHC.Iface.Ext.Ast - - - - - 2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00 Cleanup OVERWRITING_CLOSURE logic The code is just more confusing than it needs to be. We don't need to mix the threaded check with the ldv profiling check since ldv's init already checks for this. Hence they can be two separate checks. Taking the sanity checking into account is also cleaner via DebugFlags.sanity. No need for checking the DEBUG define. The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the old code had also make things a lot more opaque IMO so I removed those. - - - - - 6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00 Fix OVERWRITING_CLOSURE assuming closures are not inherently used The new ASSERT in LDV_recordDead() was being tripped up by MVars when removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via OVERWRITE_INFO(). - - - - - 38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00 Always zero shrunk mutable array slop when profiling When shrinking arrays in the profiling way we currently don't always zero the leftover slop. This means we can't traverse such closures in the heap profiler. The old Note [zeroing slop] and #8402 have some rationale for why this is so but I belive the reasoning doesn't apply to mutable closures. There users already have to ensure multiple threads don't step on each other's toes so zeroing should be safe. - - - - - b0c1f2a6 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for #18151 - - - - - 9a99a178 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for desugaring of PostfixOperators - - - - - 2b89ca5b by Ben Gamari at 2020-06-01T06:33:37-04:00 HsToCore: Eta expand left sections Strangely, the comment next to this code already alluded to the fact that even simply eta-expanding will sacrifice laziness. It's quite unclear how we regressed so far. See #18151. - - - - - d412d7a3 by Kirill Elagin at 2020-06-01T06:34:21-04:00 Winferred-safe-imports: Do not exit with error Currently, when -Winferred-safe-imports is enabled, even when it is not turned into an error, the compiler will still exit with exit code 1 if this warning was emitted. Make sure it is really treated as a warning. - - - - - f945eea5 by Ben Gamari at 2020-06-01T06:34:58-04:00 nonmoving: Optimise log2_ceil - - - - - aab606e4 by Bodigrim at 2020-06-01T06:35:36-04:00 Clarify description of fromListN - - - - - 7e5220e2 by Bodigrim at 2020-06-01T06:35:36-04:00 Apply suggestion to libraries/base/GHC/Exts.hs - - - - - f3fb1ce9 by fendor at 2020-06-01T06:36:18-04:00 Add `isInScope` check to `lintCoercion` Mirrors the behaviour of `lintType`. - - - - - 5ac4d946 by fendor at 2020-06-01T06:36:18-04:00 Lint rhs of IfaceRule - - - - - 1cef6126 by Jeremy Schlatter at 2020-06-01T06:37:00-04:00 Fix wording in documentation The duplicate "orphan instance" phrase here doesn't make sense, and was probably an accident. - - - - - 5aaf08f2 by Takenobu Tani at 2020-06-01T06:37:43-04:00 configure: Modify aclocal.m4 according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * Rename: * compiler/GHC/Parser.hs <= compiler/parser/Parser.hs * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs * Add: * compiler/GHC/Cmm/Lexer.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular - - - - - 15857ad8 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Don't fail if we can't unlink __symlink_test Afterall, it's possible we were unable to create it due to lack of symlink permission. - - - - - 4a7229ef by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Refactor ghostscript detection Tamar reported that he saw crashes due to unhandled exceptions. - - - - - 2ab37eaf by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/perf_notes: Fix ill-typed assignments - - - - - e45d5b66 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/testutil: Fix bytes/str mismatch - - - - - 7002d0cb by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Work around spurious mypy failure - - - - - 11390e3a by Takenobu Tani at 2020-06-01T06:39:05-04:00 Clean up file paths for new module hierarchy This updates comments only. This patch replaces file references according to new module hierarchy. See also: * https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular * https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 8f2e5732 by Takenobu Tani at 2020-06-01T06:39:05-04:00 Modify file paths to module paths for new module hierarchy This updates comments only. This patch replaces module references according to new module hierarchy [1][2]. For files under the `compiler/` directory, I replace them as module paths instead of file paths. For instance, `GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3]. For current and future haddock's markup, this patch encloses the module name with "" [4]. [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 [3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613 [4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules - - - - - 68b71c4a by Tom Ellis at 2020-06-01T06:39:55-04:00 Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo - - - - - 95da76c2 by Sylvain Henry at 2020-06-01T06:40:41-04:00 Hadrian: fix binary-dist target for cross-compilation - - - - - 730fcd54 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for the @-operator Since GHC diverges from the Haskell Report by allowing the user to define (@) as an infix operator, we better give a good error message when the user does so unintentionally. In general, this is rather hard to do, as some failures will be discovered only in the renamer or the type checker: x :: (Integer, Integer) x @ (a, b) = (1, 2) This patch does *not* address this general case. However, it gives much better error messages when the binding is not syntactically valid: pairs xs @ (_:xs') = zip xs xs' Before this patch, the error message was rather puzzling: <interactive>:1:1: error: Parse error in pattern: pairs After this patch, the error message includes a hint: <interactive>:1:1: error: Parse error in pattern: pairs In a function binding for the ‘@’ operator. Perhaps you meant an as-pattern, which must not be surrounded by whitespace - - - - - 0fde5377 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TypeApplications With this patch, we always parse f @t as a type application, thereby producing better error messages. This steals two syntactic forms: * Prefix form of the @-operator in expressions. Since the @-operator is a divergence from the Haskell Report anyway, this is not a major loss. * Prefix form of @-patterns. Since we are stealing loose infix form anyway, might as well sacrifice the prefix form for the sake of much better error messages. - - - - - c68e7e1e by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TemplateHaskellQuotes While [e| |], [t| |], [d| |], and so on, steal syntax from list comprehensions, [| |] and [|| ||] do not steal any syntax. Thus we can improve error messages by always accepting them in the lexer. Turns out the renamer already performs necessary validation. - - - - - 120aedbd by Ben Gamari at 2020-06-01T16:07:02-04:00 gitlab-ci: Disable use of ld.lld on ARMv7 It turns out that lld non-deterministically fails on ARMv7. I suspect this may be due to the a kernel regression as this only started happening when we upgraded to 5.4. Nevertheless, easily avoided by simply sticking with gold. Works around #18280. - - - - - d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00 gitlab-ci: Ensure that workaround for #18280 applies to bindisttest We need to ensure that the `configure` flags working around #18280 are propagated to the bindisttest `configure` as well. - - - - - cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00 gitlab-ci: Allow ARMv7 job to fail Due to #18298. - - - - - 32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00 Clean up boot vs non-boot disambiguating types We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule. - - - - - c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00 docs: Add more details on InterruptibleFFI. Details from https://gitlab.haskell.org/ghc/ghc/issues/8684 and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430 - - - - - 1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00 Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr. MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd. This regression did not make it into a release of GHC. Here, the original behavior is restored, and FinalPtr is given the same treatment as PlainPtr. - - - - - 2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00 Fix documentation on type families not being extracted It looks like the location of the Names used for CoAxioms on type families are now located at their type constructors. Previously, Docs.hs thought the Names were located in the RHS, so the RealSrcSpan in the instanceMap and getInstLoc didn't match up. Fixes #18241 - - - - - 6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00 GHC.Hs.Instances: Compile with -O0 This module contains exclusively Data instances, which are going to be slow no matter what we do. Furthermore, they are incredibly slow to compile with optimisation (see #9557). Consequently we compile this with -O0. See #18254. - - - - - c330331a by nineonine at 2020-06-04T04:37:59-04:00 Add test for #17669 - - - - - cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00 rts: Add Windows-specific implementation of rtsSleep Previously we would use the POSIX path, which uses `nanosleep`. However, it turns out that `nanosleep` is provided by `libpthread` on Windows. In general we don't want to incur such a dependency. Avoid this by simply using `Sleep` on Windows. Fixes #18272. - - - - - ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00 compiler: Disable use of process jobs with process < 1.6.9 Due to #17926. - - - - - 6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00 [linker] Adds void printLoadedObjects(void); This allows us to dump in-memory object code locations for debugging. Fixup printLoadedObjects prototype - - - - - af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00 base: fix sign confusion in log1mexp implementation (fix #17125) author: claude (https://gitlab.haskell.org/trac-claude) The correct threshold for log1mexp is -(log 2) with the current specification of log1mexp. This change improves accuracy for large negative inputs. To avoid code duplication, a small helper function is added; it isn't the default implementation in Floating because it needs Ord. This patch does nothing to address that the Haskell specification is different from that in common use in other languages. - - - - - 2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00 Simple subsumption This patch simplifies GHC to use simple subsumption. Ticket #17775 Implements GHC proposal #287 https://github.com/ghc-proposals/ghc-proposals/blob/master/ proposals/0287-simplify-subsumption.rst All the motivation is described there; I will not repeat it here. The implementation payload: * tcSubType and friends become noticably simpler, because it no longer uses eta-expansion when checking subsumption. * No deeplyInstantiate or deeplySkolemise That in turn means that some tests fail, by design; they can all be fixed by eta expansion. There is a list of such changes below. Implementing the patch led me into a variety of sticky corners, so the patch includes several othe changes, some quite significant: * I made String wired-in, so that "foo" :: String rather than "foo" :: [Char] This improves error messages, and fixes #15679 * The pattern match checker relies on knowing about in-scope equality constraints, andd adds them to the desugarer's environment using addTyCsDs. But the co_fn in a FunBind was missed, and for some reason simple-subsumption ends up with dictionaries there. So I added a call to addTyCsDs. This is really part of #18049. * I moved the ic_telescope field out of Implication and into ForAllSkol instead. This is a nice win; just expresses the code much better. * There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader. We called checkDataKindSig inside tc_kind_sig, /before/ solveEqualities and zonking. Obviously wrong, easily fixed. * solveLocalEqualitiesX: there was a whole mess in here, around failing fast enough. I discovered a bad latent bug where we could successfully kind-check a type signature, and use it, but have unsolved constraints that could fill in coercion holes in that signature -- aargh. It's all explained in Note [Failure in local type signatures] in GHC.Tc.Solver. Much better now. * I fixed a serious bug in anonymous type holes. IN f :: Int -> (forall a. a -> _) -> Int that "_" should be a unification variable at the /outer/ level; it cannot be instantiated to 'a'. This was plain wrong. New fields mode_lvl and mode_holes in TcTyMode, and auxiliary data type GHC.Tc.Gen.HsType.HoleMode. This fixes #16292, but makes no progress towards the more ambitious #16082 * I got sucked into an enormous refactoring of the reporting of equality errors in GHC.Tc.Errors, especially in mkEqErr1 mkTyVarEqErr misMatchMsg misMatchMsgOrCND In particular, the very tricky mkExpectedActualMsg function is gone. It took me a full day. But the result is far easier to understand. (Still not easy!) This led to various minor improvements in error output, and an enormous number of test-case error wibbles. One particular point: for occurs-check errors I now just say Can't match 'a' against '[a]' rather than using the intimidating language of "occurs check". * Pretty-printing AbsBinds Tests review * Eta expansions T11305: one eta expansion T12082: one eta expansion (undefined) T13585a: one eta expansion T3102: one eta expansion T3692: two eta expansions (tricky) T2239: two eta expansions T16473: one eta determ004: two eta expansions (undefined) annfail06: two eta (undefined) T17923: four eta expansions (a strange program indeed!) tcrun035: one eta expansion * Ambiguity check at higher rank. Now that we have simple subsumption, a type like f :: (forall a. Eq a => Int) -> Int is no longer ambiguous, because we could write g :: (forall a. Eq a => Int) -> Int g = f and it'd typecheck just fine. But f's type is a bit suspicious, and we might want to consider making the ambiguity check do a check on each sub-term. Meanwhile, these tests are accepted, whereas they were previously rejected as ambiguous: T7220a T15438 T10503 T9222 * Some more interesting error message wibbles T13381: Fine: one error (Int ~ Exp Int) rather than two (Int ~ Exp Int, Exp Int ~ Int) T9834: Small change in error (improvement) T10619: Improved T2414: Small change, due to order of unification, fine T2534: A very simple case in which a change of unification order means we get tow unsolved constraints instead of one tc211: bizarre impredicative tests; just accept this for now Updates Cabal and haddock submodules. Metric Increase: T12150 T12234 T5837 haddock.base Metric Decrease: haddock.compiler haddock.Cabal haddock.base Merge note: This appears to break the `UnliftedNewtypesDifficultUnification` test. It has been marked as broken in the interest of merging. (cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5) - - - - - 2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00 Simplify bindLHsTyVarBndrs and bindHsQTyVars Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate `Maybe` arguments, which I find terribly confusing. Thankfully, it's possible to remove one `Maybe` argument from each of these functions, which this patch accomplishes: * `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if GHC should warn about any of the quantified type variables going unused. However, every call site uses `Nothing` in practice. This makes sense, since it doesn't really make sense to warn about unused type variables bound by an `LHsQTyVars`. For instance, you wouldn't warn about the `a` in `data Proxy a = Proxy` going unused. As a result, I simply remove this `Maybe SDoc` argument altogether. * `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same reasons that `bindHsQTyVars` took one. To make things more confusing, however, `bindLHsTyVarBndrs` also takes a separate `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in warnings and error messages. In practice, the `Maybe SDoc` and the `HsDocContext` often contain the same text. See the call sites for `bindLHsTyVarBndrs` in `rnFamInstEqn` and `rnConDecl`, for instance. There are only a handful of call sites where the text differs between the `Maybe SDoc` and `HsDocContext` arguments: * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`" and the `HsDocContext` says "`In the transformation rule`". * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says "`In the type`" but the `HsDocContext` is inhereted from the surrounding context (e.g., if `rnHsTyKi` were called on a top-level type signature, the `HsDocContext` would be "`In the type signature`" instead) In both cases, warnings/error messages arguably _improve_ by unifying making the `Maybe SDoc`'s text match that of the `HsDocContext`. As a result, I decided to remove the `Maybe SDoc` argument to `bindLHsTyVarBndrs` entirely and simply reuse the text from the `HsDocContext`. (I decided to change the phrase "transformation rule" to "rewrite rule" while I was in the area.) The `Maybe SDoc` argument has one other purpose: signaling when to emit "`Unused quantified type variable`" warnings. To recover this functionality, I replaced the `Maybe SDoc` argument with a boolean-like `WarnUnusedForalls` argument. The only `bindLHsTyVarBndrs` call site that chooses _not_ to emit these warnings in `bindHsQTyVars`. - - - - - e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00 hadrian: Add missing deriveConstants dependency on ghcplatform.h deriveConstants wants to compile C sources which #include PosixSource.h, which itself #includes ghcplatform.h. Make sure that Hadrian knows about this dependency. Fixes #18290. - - - - - b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00 ghc-prim needs to depend on libc and libm libm is just an empty shell on musl, and all the math functions are contained in libc. - - - - - 6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00 Disable DLL loading if without system linker Some platforms (musl, aarch64) do not have a working dynamic linker implemented in the libc, even though we might see dlopen. It will ultimately just return that this is not supported. Hence we'll add a flag to the compiler to flat our disable loading dlls. This is needed as we will otherwise try to load the shared library even if this will subsequently fail. At that point we have given up looking for static options though. - - - - - 4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00 Range is actually +/-2^32, not +/-2^31 See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf - - - - - f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00 OccurAnal: Avoid exponential behavior due to where clauses Previously the `Var` case of `occAnalApp` could in some cases (namely in the case of `runRW#` applications) call `occAnalRhs` two. In the case of nested `runRW#`s this results in exponential complexity. In some cases the compilation time that resulted would be very long indeed (see #18296). Fixes #18296. Metric Decrease: T9961 T12150 T12234 - - - - - 9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00 Add link to GHC's wiki in the GHC API header This adds a URL to point to GHC's wiki in the GHC API header. Newcomers could easily find more information from the GHC API's web like [1]. [1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html [skip ci] - - - - - 72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00 Make GADT constructors adhere to the forall-or-nothing rule properly Issue #18191 revealed that the types of GADT constructors don't quite adhere to the `forall`-or-nothing rule. This patch serves to clean up this sad state of affairs somewhat. The main change is not in the code itself, but in the documentation, as this patch introduces two sections to the GHC User's Guide: * A "Formal syntax for GADTs" section that presents a BNF-style grammar for what is and isn't allowed in GADT constructor types. This mostly exists to codify GHC's existing behavior, but it also imposes a new restriction that addresses #18191: the outermost `forall` and/or context in a GADT constructor is not allowed to be surrounded by parentheses. Doing so would make these `forall`s/contexts nested, and GADTs do not support nested `forall`s/contexts at present. * A "`forall`-or-nothing rule" section that describes exactly what the `forall`-or-nothing rule is all about. Surprisingly, there was no mention of this anywhere in the User's Guide up until now! To adhere the new specification in the "Formal syntax for GADTs" section of the User's Guide, the following code changes were made: * A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced. This is very much like `splitLHsSigmaTy`, except that it avoids splitting apart any parentheses, which can be syntactically significant for GADT types. See `Note [No nested foralls or contexts in GADT constructors]` in `GHC.Hs.Type`. * `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return it when given a prefix GADT constructor. Unlike `ConDeclGADT`, `ConDeclGADTPrefixPs` does not split the GADT type into its argument and result types, as this cannot be done until after the type is renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why this is the case). * `GHC.Renamer.Module.rnConDecl` now has an additional case for `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into its `forall`s, context, argument types, and result type, and (2) checks for nested `forall`s/contexts. Step (2) used to be performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather than the renamer, but now the relevant code from the typechecker can simply be deleted. One nice side effect of this change is that we are able to give a more accurate error message for GADT constructors that use visible dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`), which improves the stderr in the `T16326_Fail6` test case. Fixes #18191. Bumps the Haddock submodule. - - - - - a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00 Always use rnImplicitBndrs to bring implicit tyvars into scope This implements a first step towards #16762 by changing the renamer to always use `rnImplicitBndrs` to bring implicitly bound type variables into scope. The main change is in `rnFamInstEqn` and `bindHsQTyVars`, which previously used _ad hoc_ methods of binding their implicit tyvars. There are a number of knock-on consequences: * One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding mechanism was to give more precise source locations in `-Wunused-type-patterns` warnings. (See https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an example of this.) However, these warnings are actually a little _too_ precise, since implicitly bound type variables don't have exact binding sites like explicitly bound type variables do. A similar problem existed for "`Different names for the same type variable`" errors involving implicit tyvars bound by `bindHsQTyVars`. Therefore, we simply accept the less precise (but more accurate) source locations from `rnImplicitBndrs` in `rnFamInstEqn` and `bindHsQTyVars`. See `Note [Source locations for implicitly bound type variables]` in `GHC.Rename.HsType` for the full story. * In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs to be able to look up names from the parent class (in the event that we are renaming an associated type family instance). As a result, `rnImplicitBndrs` now takes an argument of type `Maybe assoc`, which is `Just` in the event that a type family instance is associated with a class. * Previously, GHC kept track of three type synonyms for free type variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups` (which are allowed to contain duplicates), and `FreeKiTyVarsNoDups` (which contain no duplicates). However, making is a distinction between `-Dups` and `-NoDups` is now pointless, as all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually end up being passed to `rnImplicitBndrs`, which removes duplicates. As a result, I decided to just get rid of `FreeKiTyVarsDups` and `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`. * The `bindLRdrNames` and `deleteBys` functions are now dead code, so I took the liberty of removing them. - - - - - 24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00 Clarify leaf module names for new module hierarchy This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00 rts: Remove unused GET_ENTRY closure macro This macro is not used and got broken in the meantime, as ENTRY_CODE was deleted. - - - - - 87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00 Fix -fkeep-cafs flag name in users guide - - - - - ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00 Expose impliedGFlags, impledOffGFlags, impliedXFlags - - - - - 7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00 Cross-module LambdaFormInfo passing - Store LambdaFormInfos of exported Ids in interface files - Use them in importing modules This is for optimization purposes: if we know LambdaFormInfo of imported Ids we can generate more efficient calling code, see `getCallMethod`. Exporting (putting them in interface files or in ModDetails) and importing (reading them from interface files) are both optional. We don't assume known LambdaFormInfos anywhere and do not change how we call Ids with unknown LambdaFormInfos. Runtime, allocation, and residency numbers when building Cabal-the-library (commit 0d4ee7ba3): (Log and .hp files are in the MR: !2842) | | GHC HEAD | This patch | Diff | |-----|----------|------------|----------------| | -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% | | -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% | | -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% | | | GHC HEAD | This patch | Diff | |-----|-----------------|-----------------|----------------------------| | -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% | | -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% | | -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% | NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively turn all GCs into major GCs, and do GC more often. | | GHC HEAD | This patch | Diff | |-----|----------------------------|------------------------------|----------------------------| | -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% | | -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% | | -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% | NoFib results: -------------------------------------------------------------------------------- Program Size Allocs Instrs Reads Writes -------------------------------------------------------------------------------- CS 0.0% 0.0% +0.0% +0.0% +0.0% CSD 0.0% 0.0% 0.0% +0.0% +0.0% FS 0.0% 0.0% +0.0% +0.0% +0.0% S 0.0% 0.0% +0.0% +0.0% +0.0% VS 0.0% 0.0% +0.0% +0.0% +0.0% VSD 0.0% 0.0% +0.0% +0.0% +0.1% VSM 0.0% 0.0% +0.0% +0.0% +0.0% anna 0.0% 0.0% -0.3% -0.8% -0.0% ansi 0.0% 0.0% -0.0% -0.0% 0.0% atom 0.0% 0.0% -0.0% -0.0% 0.0% awards 0.0% 0.0% -0.1% -0.3% 0.0% banner 0.0% 0.0% -0.0% -0.0% -0.0% bernouilli 0.0% 0.0% -0.0% -0.0% -0.0% binary-trees 0.0% 0.0% -0.0% -0.0% +0.0% boyer 0.0% 0.0% -0.0% -0.0% 0.0% boyer2 0.0% 0.0% -0.0% -0.0% 0.0% bspt 0.0% 0.0% -0.0% -0.2% 0.0% cacheprof 0.0% 0.0% -0.1% -0.4% +0.0% calendar 0.0% 0.0% -0.0% -0.0% 0.0% cichelli 0.0% 0.0% -0.9% -2.4% 0.0% circsim 0.0% 0.0% -0.0% -0.0% 0.0% clausify 0.0% 0.0% -0.1% -0.3% 0.0% comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0% compress 0.0% 0.0% -0.0% -0.0% -0.0% compress2 0.0% 0.0% -0.0% -0.0% 0.0% constraints 0.0% 0.0% -0.1% -0.2% -0.0% cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0% cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0% cse 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0% dom-lt 0.0% 0.0% -0.1% -0.2% 0.0% eliza 0.0% 0.0% -0.5% -1.5% 0.0% event 0.0% 0.0% -0.0% -0.0% -0.0% exact-reals 0.0% 0.0% -0.1% -0.3% +0.0% exp3_8 0.0% 0.0% -0.0% -0.0% -0.0% expert 0.0% 0.0% -0.3% -1.0% -0.0% fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0% fasta 0.0% 0.0% -0.0% -0.0% +0.0% fem 0.0% 0.0% -0.0% -0.0% 0.0% fft 0.0% 0.0% -0.0% -0.0% 0.0% fft2 0.0% 0.0% -0.0% -0.0% 0.0% fibheaps 0.0% 0.0% -0.0% -0.0% +0.0% fish 0.0% 0.0% 0.0% -0.0% +0.0% fluid 0.0% 0.0% -0.4% -1.2% +0.0% fulsom 0.0% 0.0% -0.0% -0.0% 0.0% gamteb 0.0% 0.0% -0.1% -0.3% 0.0% gcd 0.0% 0.0% -0.0% -0.0% 0.0% gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0% genfft 0.0% 0.0% -0.0% -0.0% 0.0% gg 0.0% 0.0% -0.0% -0.0% +0.0% grep 0.0% 0.0% -0.0% -0.0% -0.0% hidden 0.0% 0.0% -0.1% -0.4% -0.0% hpg 0.0% 0.0% -0.2% -0.5% +0.0% ida 0.0% 0.0% -0.0% -0.0% +0.0% infer 0.0% 0.0% -0.3% -0.8% -0.0% integer 0.0% 0.0% -0.0% -0.0% +0.0% integrate 0.0% 0.0% -0.0% -0.0% 0.0% k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0% kahan 0.0% 0.0% -0.0% -0.0% +0.0% knights 0.0% 0.0% -2.2% -5.4% 0.0% lambda 0.0% 0.0% -0.6% -1.8% 0.0% last-piece 0.0% 0.0% -0.0% -0.0% 0.0% lcss 0.0% 0.0% -0.0% -0.1% 0.0% life 0.0% 0.0% -0.0% -0.1% 0.0% lift 0.0% 0.0% -0.2% -0.6% +0.0% linear 0.0% 0.0% -0.0% -0.0% -0.0% listcompr 0.0% 0.0% -0.0% -0.0% 0.0% listcopy 0.0% 0.0% -0.0% -0.0% 0.0% maillist 0.0% 0.0% -0.1% -0.3% +0.0% mandel 0.0% 0.0% -0.0% -0.0% 0.0% mandel2 0.0% 0.0% -0.0% -0.0% -0.0% mate +0.0% 0.0% -0.0% -0.0% -0.0% minimax 0.0% 0.0% -0.2% -1.0% 0.0% mkhprog 0.0% 0.0% -0.1% -0.2% -0.0% multiplier 0.0% 0.0% -0.0% -0.0% -0.0% n-body 0.0% 0.0% -0.0% -0.0% +0.0% nucleic2 0.0% 0.0% -0.1% -0.2% 0.0% para 0.0% 0.0% -0.0% -0.0% -0.0% paraffins 0.0% 0.0% -0.0% -0.0% 0.0% parser 0.0% 0.0% -0.2% -0.7% 0.0% parstof 0.0% 0.0% -0.0% -0.0% +0.0% pic 0.0% 0.0% -0.0% -0.0% 0.0% pidigits 0.0% 0.0% +0.0% +0.0% +0.0% power 0.0% 0.0% -0.2% -0.6% +0.0% pretty 0.0% 0.0% -0.0% -0.0% -0.0% primes 0.0% 0.0% -0.0% -0.0% 0.0% primetest 0.0% 0.0% -0.0% -0.0% -0.0% prolog 0.0% 0.0% -0.3% -1.1% 0.0% puzzle 0.0% 0.0% -0.0% -0.0% 0.0% queens 0.0% 0.0% -0.0% -0.0% +0.0% reptile 0.0% 0.0% -0.0% -0.0% 0.0% reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0% rewrite 0.0% 0.0% -0.7% -2.5% -0.0% rfib 0.0% 0.0% -0.0% -0.0% 0.0% rsa 0.0% 0.0% -0.0% -0.0% 0.0% scc 0.0% 0.0% -0.1% -0.2% -0.0% sched 0.0% 0.0% -0.0% -0.0% -0.0% scs 0.0% 0.0% -1.0% -2.6% +0.0% simple 0.0% 0.0% +0.0% -0.0% +0.0% solid 0.0% 0.0% -0.0% -0.0% 0.0% sorting 0.0% 0.0% -0.6% -1.6% 0.0% spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0% sphere 0.0% 0.0% -0.0% -0.0% -0.0% symalg 0.0% 0.0% -0.0% -0.0% +0.0% tak 0.0% 0.0% -0.0% -0.0% 0.0% transform 0.0% 0.0% -0.0% -0.0% 0.0% treejoin 0.0% 0.0% -0.0% -0.0% 0.0% typecheck 0.0% 0.0% -0.0% -0.0% +0.0% veritas +0.0% 0.0% -0.2% -0.4% +0.0% wang 0.0% 0.0% -0.0% -0.0% 0.0% wave4main 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0% x2n1 0.0% 0.0% -0.0% -0.0% -0.0% -------------------------------------------------------------------------------- Min 0.0% 0.0% -2.2% -5.4% -0.0% Max +0.0% 0.0% +0.0% +0.0% +0.1% Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0% Metric increases micro benchmarks tracked in #17686: Metric Increase: T12150 T12234 T12425 T13035 T5837 T6048 T9233 Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00 Give Language a Bounded instance - - - - - 9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Optimisation in Unique.Supply This patch switches on -fno-state-hack in GHC.Types.Unique.Supply. It turned out that my fixes for #18078 (coercion floating) changed the optimisation pathway for mkSplitUniqSupply in such a way that we had an extra allocation inside the inner loop. Adding -fno-state-hack fixed that -- and indeed the loop in mkSplitUniqSupply is a classic example of the way in which -fno-state-hack can be bad; see #18238. Moreover, the new code is better than the old. They allocate the same, but the old code ends up with a partial application. The net effect is that the test perf/should_run/UniqLoop runs 20% faster! From 2.5s down to 2.0s. The allocation numbers are the same -- but elapsed time falls. Good! The bad thing about this is that it's terribly delicate. But at least it's a good example of such delicacy in action. There is a long Note [Optimising the unique supply] which now explains all this. - - - - - 6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Implement cast worker/wrapper properly The cast worker/wrapper transformation transforms x = e |> co into y = e x = y |> co This is done by the simplifier, but we were being careless about transferring IdInfo from x to y, and about what to do if x is a NOINLNE function. This resulted in a series of bugs: #17673, #18093, #18078. This patch fixes all that: * Main change is in GHC.Core.Opt.Simplify, and the new prepareBinding function, which does this cast worker/wrapper transform. See Note [Cast worker/wrappers]. * There is quite a bit of refactoring around prepareRhs, makeTrivial etc. It's nicer now. * Some wrappers from strictness and cast w/w, notably those for a function with a NOINLINE, should inline very late. There wasn't really a mechanism for that, which was an existing bug really; so I invented a new finalPhase = Phase (-1). It's used for all simplifier runs after the user-visible phase 2,1,0 have run. (No new runs of the simplifier are introduced thereby.) See new Note [Compiler phases] in GHC.Types.Basic; the main changes are in GHC.Core.Opt.Driver * Doing this made me trip over two places where the AnonArgFlag on a FunTy was being lost so we could end up with (Num a -> ty) rather than (Num a => ty) - In coercionLKind/coercionRKind - In contHoleType in the Simplifier I fixed the former by defining mkFunctionType and using it in coercionLKind/RKind. I could have done the same for the latter, but the information is almost to hand. So I fixed the latter by - adding sc_hole_ty to ApplyToVal (like ApplyToTy), - adding as_hole_ty to ValArg (like TyArg) - adding sc_fun_ty to StrictArg Turned out I could then remove ai_type from ArgInfo. This is just moving the deck chairs around, but it worked out nicely. See the new Note [AnonArgFlag] in GHC.Types.Var * When looking at the 'arity decrease' thing (#18093) I discovered that stable unfoldings had a much lower arity than the actual optimised function. That's what led to the arity-decrease message. Simple solution: eta-expand. It's described in Note [Eta-expand stable unfoldings] in GHC.Core.Opt.Simplify * I also discovered that unsafeCoerce wasn't being inlined if the context was boring. So (\x. f (unsafeCoerce x)) would create a thunk -- yikes! I fixed that by making inlineBoringOK a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold. I also found that unsafeCoerceName was unused, so I removed it. I made a test case for #18078, and a very similar one for #17673. The net effect of all this on nofib is very modest, but positive: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.4% -0.1% -3.1% -3.1% 0.0% fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0% maillist -0.4% -0.1% -7.8% -1.0% -14.3% primetest -0.4% -15.6% -7.1% -6.6% 0.0% -------------------------------------------------------------------------------- Min -0.9% -15.6% -13.3% -14.2% -14.3% Max -0.3% 0.0% +12.1% +12.4% 0.0% Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1% All following metric decreases are compile-time allocation decreases between -1% and -3%: Metric Decrease: T5631 T13701 T14697 T15164 - - - - - 32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00 Fix lookupGlobalOccRn_maybe sometimes reporting an error In some cases it was possible for lookupGlobalOccRn_maybe to return an error, when it should be returning a Nothing. If it called lookupExactOcc_either when there were no matching GlobalRdrElts in the otherwise case, it would return an error message. This could be caused when lookupThName_maybe in Template Haskell was looking in different namespaces (thRdrNameGuesses), guessing different namespaces that the name wasn't guaranteed to be found in. However, by addressing this some more accurate errors were being lost in the conversion to Maybes. So some of the lookup* functions have been shuffled about so that errors should always be ignored in lookup*_maybes, and propagated otherwise. This fixes #18263 - - - - - 9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00 Initialize the allocation counter in GHCi to 0 (Fixes #16012) According to the documentation for the function `getAllocationCounter` in [System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html) initialize the allocationCounter also in GHCi to 0. - - - - - 8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00 test: fix conc038 We had spurious failures of conc038 test on CI with stdout: ``` newThread started -mainThread -Haskell: 2 newThread back again +mainThread 1 sec later shutting down +Haskell: 2 ``` - - - - - 4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00 Release Notes: Add news from the pattern-match checker [skip ci] - - - - - 3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00 Only test T16190 with the NCG T16190 is meant to test a NCG feature. It has already caused spurious failures in other MRs (e.g. !2165) when LLVM is used. - - - - - 2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00 DynFlags refactoring VIII (#17957) * Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.* * Add LlvmOpts datatype to store Llvm backend options * Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and Llvm.MetaExpr) which require LlvmOpts. * Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`) - - - - - 7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove unused code - - - - - 72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor homeUnit * rename thisPackage into homeUnit * document and refactor several Backpack things - - - - - 8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Rename unsafeGetUnitInfo into unsafeLookupUnit - - - - - f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Add allowVirtualUnits field in PackageState Instead of always querying DynFlags to know whether we are allowed to use virtual units (i.e. instantiated on-the-fly, cf Note [About units] in GHC.Unit), we store it once for all in `PackageState.allowVirtualUnits`. This avoids using DynFlags too much (cf #17957) and is preliminary work for #14335. - - - - - e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Enhance UnitId use * use UnitId instead of String to identify wired-in units * use UnitId instead of Unit in the backend (Unit are only use by Backpack to produce type-checked interfaces, not real code) * rename lookup functions for consistency * documentation - - - - - 9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove LinkerUnitId type alias - - - - - d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor WiredMap * Remove WiredInUnitId and WiredUnitId type aliases - - - - - 3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document and refactor `mkUnit` and `mkUnitInfoMap` - - - - - d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove PreloadUnitId type alias - - - - - f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename listUnitInfoMap into listUnitInfo There is no Map involved - - - - - ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc. - - - - - 202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Make ClosureUnitInfoMap uses UnitInfoMap - - - - - 55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove ClosureUnitInfoMap - - - - - 653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit (2) * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc. - - - - - ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move dump_mod_map into initUnits - - - - - 598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move wiring of homeUnitInstantiations outside of mkUnitState - - - - - 437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00 Avoid timing module map dump in initUnits - - - - - 9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove preload parameter of mkUnitState * Remove preload parameter (unused) * Don't explicitly return preloaded units: redundant because already returned as "preloadUnits" field of UnitState - - - - - 266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: refactor unwireUnit - - - - - 9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document getPreloadUnitsAnd - - - - - bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: remove useless add_package parameter - - - - - 36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: make listVisibleModuleNames take a UnitState - - - - - 5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document add_package - - - - - 4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document closeUnitDeps - - - - - 42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: findWiredInUnits - - - - - a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: reportCycles, reportUnusable - - - - - 8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: merge_databases - - - - - fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: add UnitConfig datatype Avoid directly querying flags from DynFlags to build the UnitState. Instead go via UnitConfig so that we could reuse this to make another UnitState for plugins. - - - - - 4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move distrustAll into mkUnitState - - - - - 28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Create helper upd_wired_in_home_instantiations - - - - - ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Put database cache in UnitConfig - - - - - bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00 Don't return preload units when we set DyNFlags Preload units can be retrieved in UnitState when needed (i.e. in GHCi) - - - - - 1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 NCGConfig: remove useless ncgUnitId field - - - - - c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Doc: fix some comments - - - - - 456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Bump haddock submodule and allow metric decrease Metric Decrease: T12150 T12234 T5837 Metric Increase: T16190 - - - - - 42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00 Trim the demand for recursive product types Ticket #18304 showed that we need to be very careful when exploring the demand (esp usage demand) on recursive product types. This patch solves the problem by trimming the demand on such types -- in effect, a form of "widening". See the Note [Trimming a demand to a type] in DmdAnal, which explains how I did this by piggy-backing on an existing mechansim for trimming demands becuase of GADTs. The significant payload of this patch is very small indeed: * Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to avoid looking through recursive types. But on the way * I found that ae_rec_tc was entirely inoperative and did nothing. So I removed it altogether from DmdAnal. * I moved some code around in DmdAnal and Demand. (There are no actual changes in dmdFix.) * I changed the API of DmsAnal.dmdAnalRhsLetDown to return a StrictSig rather than a decorated Id * I removed the dead function peelTsFuns from Demand Performance effects: Nofib: 0.0% changes. Not surprising, because they don't use recursive products Perf tests T12227: 1% increase in compiler allocation, becuase $cto gets w/w'd. It did not w/w before because it takes a deeply nested argument, so the worker gets too many args, so we abandon w/w altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough) With this patch we trim the demands. That is not strictly necessary (since these Generic type constructors are like tuples -- they can't cause a loop) but the net result is that we now w/w $cto which is fine. UniqLoop: 16% decrease in /runtime/ allocation. The UniqSupply is a recursive product, so currently we abandon all strictness on 'churn'. With this patch 'churn' gets useful strictness, and we w/w it. Hooray Metric Decrease: UniqLoop Metric Increase: T12227 - - - - - 87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00 Add introductory prose for Data.Traversable - - - - - 9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00 Fix #12073: Add MonadFix Q instance - - - - - 220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00 testsuite: Increase size of T12150 As noted in #18319, this test was previously very fragile. Increase its size to make it more likely that its fails with its newly-increased acceptance threshold. Metric Increase: T12150 - - - - - 8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00 gitlab-ci: Always push perf notes Previously we ci.sh would run with `set -e` implying that we wouldn't push perf notes if the testsuite were to fail, even if it *only* failed due to perf notes. This rendered the whole performance testing story quite fragile as a single regressing commit would cause every successive commit to fail since a new baseline would not be uploaded. Fix this by ensuring that we always push performance notes. - - - - - 7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00 gitlab-ci: Eliminate redundant push of CI metrics - - - - - a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00 Use HsForAllTelescope to avoid inferred, visible foralls Currently, `HsForAllTy` permits the combination of `ForallVis` and `Inferred`, but you can't actually typecheck code that uses it (e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a new `HsForAllTelescope` data type that makes a type-level distinction between visible and invisible `forall`s such that visible `forall`s do not track `Specificity`. That part of the patch is actually quite small; the rest is simply changing consumers of `HsType` to accommodate this new type. Fixes #18235. Bumps the `haddock` submodule. - - - - - c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00 winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges. The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00 codeGen: Don't discard live case binders in unsafeEqualityProof logic Previously CoreToStg would unconditionally discard cases of the form: case unsafeEqualityProof of wild { _ -> rhs } and rather replace the whole thing with `rhs`. However, in some cases (see #18227) the case binder is still live, resulting in unbound occurrences in `rhs`. Fix this by only discarding the case if the case binder is dead. Fixes #18227. - - - - - e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00 testsuite: Add tests for #18227 T18227A is the original issue which gave rise to the ticket and depends upon bytestring. T18227B is a minimized reproducer. - - - - - 8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Fix rts include and library paths Fixes two bugs: * (?) and (<>) associated in a surprising way * We neglected to include libdw paths in the rts configure flags - - - - - bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Drop redundant GHC arguments Cabal should already be passing this arguments to GHC. - - - - - 01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00 FFI: Fix pass small ints in foreign call wrappers The Haskell calling convention requires integer parameters smaller than wordsize to be promoted to wordsize (where the upper bits are don't care). To access such small integer parameter read a word from the parameter array and then cast that word to the small integer target type. Fixes #15933 - - - - - 502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00 Fix "ndecreasingIndentation" in manual (#18116) - - - - - 9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00 Use foldl' in unionManyUniqDSets - - - - - 761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00 Load .lo as well. Some archives contain so called linker objects, with the affectionate .lo suffic. For example the musl libc.a will come in that form. We still want to load those objects, hence we should not discard them and look for .lo as well. Ultimately we might want to fix this proerly by looking at the file magic. - - - - - cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00 User's Guide: KnownNat evidence is Natural This bit of documentation got outdated after commit 1fcede43d2b30f33b7505e25eb6b1f321be0407f - - - - - d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00 Fix typos and formatting in user guide - - - - - 56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00 Resolve TODO - - - - - 3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00 Rename TcHoleErrors to GHC.Tc.Errors.Hole - - - - - d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00 hadrian: Build with threaded runtime if available See #16873. - - - - - 0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00 T16190: only measure bytes_allocated Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics fluctuate by 13%. - - - - - 4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00 docs: fix formatting in users guide - - - - - eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00 Move CLabel assertions into smart constructors (#17957) It avoids using DynFlags in the Outputable instance of Clabel to check assertions at pretty-printing time. - - - - - 7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00 base: Bump to 4.15.0.0 - - - - - 20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00 configure: Use grep -q instead of --quiet The latter is apparently not supported by busybox. - - - - - 40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00 Linear types (#15981) This is the first step towards implementation of the linear types proposal (https://github.com/ghc-proposals/ghc-proposals/pull/111). It features * A language extension -XLinearTypes * Syntax for linear functions in the surface language * Linearity checking in Core Lint, enabled with -dlinear-core-lint * Core-to-core passes are mostly compatible with linearity * Fields in a data type can be linear or unrestricted; linear fields have multiplicity-polymorphic constructors. If -XLinearTypes is disabled, the GADT syntax defaults to linear fields The following items are not yet supported: * a # m -> b syntax (only prefix FUN is supported for now) * Full multiplicity inference (multiplicities are really only checked) * Decent linearity error messages * Linear let, where, and case expressions in the surface language (each of these currently introduce the unrestricted variant) * Multiplicity-parametric fields * Syntax for annotating lambda-bound or let-bound with a multiplicity * Syntax for non-linear/multiple-field-multiplicity records * Linear projections for records with a single linear field * Linear pattern synonyms * Multiplicity coercions (test LinearPolyType) A high-level description can be found at https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation Following the link above you will find a description of the changes made to Core. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Matthew Pickering * Arnaud Spiwack With contributions from: * Mark Barbone * Alexander Vershilov Updates haddock submodule. - - - - - 6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00 Various performance improvements This implements several general performance improvements to GHC, to offset the effect of the linear types change. General optimisations: - Add a `coreFullView` function which iterates `coreView` on the head. This avoids making function recursive solely because the iterate `coreView` themselves. As a consequence, this functions can be inlined, and trigger case-of-known constructor (_e.g._ `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`, `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`, `tyConAppTyCon_maybe`). The common pattern about all these functions is that they are almost always used as views, and immediately consumed by a case expression. This commit also mark them asx `INLINE`. - In `subst_ty` add a special case for nullary `TyConApp`, which avoid allocations altogether. - Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This required quite a bit of module shuffling. case. `myTyConApp` enforces crucial sharing, which was lost during substitution. See also !2952 . - Make `subst_ty` stricter. - In `eqType` (specifically, in `nonDetCmpType`), add a special case, tested first, for the very common case of nullary `TyConApp`. `nonDetCmpType` has been made `INLINE` otherwise it is actually a regression. This is similar to the optimisations in !2952. Linear-type specific optimisations: - Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in the definition of the pattern synonyms `One` and `Many`. - Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`: `Multiplicity` now import `Type` normally, rather than from the `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the `One` and `Many` pattern synonyms. - Make `updateIdTypeAndMult` strict in its type and multiplicity - The `scaleIdBy` gets a specialised definition rather than being an alias to `scaleVarBy` - `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type, Type)` instead of `Type -> Maybe (Scaled Type, Type)` - Remove the `MultMul` pattern synonym in favour of a view `isMultMul` because pattern synonyms appear not to inline well. - in `eqType`, in a `FunTy`, compare multiplicities last: they are almost always both `Many`, so it helps failing faster. - Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the instances of `TyConApp ManyDataConTy []` are physically the same. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Arnaud Spiwack Metric Decrease: haddock.base T12227 T12545 T12990 T1969 T3064 T5030 T9872b Metric Increase: haddock.base haddock.Cabal haddock.compiler T12150 T12234 T12425 T12707 T13035 T13056 T15164 T16190 T18304 T1969 T3064 T3294 T5631 T5642 T5837 T6048 T9020 T9233 T9675 T9872a T9961 WWRec - - - - - 57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Remove integer-simple integer-simple uses lists of words (`[Word]`) to represent big numbers instead of ByteArray#: * it is less efficient than the newer ghc-bignum native backend * it isn't compatible with the big number representation that is now shared by all the ghc-bignum backends (based on the one that was used only in integer-gmp before). As a consequence, we simply drop integer-simple - - - - - 9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00 ghc-bignum library ghc-bignum is a newer package that aims to replace the legacy integer-simple and integer-gmp packages. * it supports several backends. In particular GMP is still supported and most of the code from integer-gmp has been merged in the "gmp" backend. * the pure Haskell "native" backend is new and is much faster than the previous pure Haskell implementation provided by integer-simple * new backends are easier to write because they only have to provide a few well defined functions. All the other code is common to all backends. In particular they all share the efficient small/big number distinction previously used only in integer-gmp. * backends can all be tested against the "native" backend with a simple Cabal flag. Backends are only allowed to differ in performance, their results should be the same. * Add `integer-gmp` compat package: provide some pattern synonyms and function aliases for those in `ghc-bignum`. It is intended to avoid breaking packages that depend on `integer-gmp` internals. Update submodules: text, bytestring Metric Decrease: Conversions ManyAlternatives ManyConstructors Naperian T10359 T10547 T10678 T12150 T12227 T12234 T12425 T13035 T13719 T14936 T1969 T4801 T4830 T5237 T5549 T5837 T8766 T9020 parsing001 space_leak_001 T16190 haddock.base On ARM and i386, T17499 regresses (+6% > 5%). On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%). Metric Increase: T17499 T13701 - - - - - 96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update compiler Thanks to ghc-bignum, the compiler can be simplified: * Types and constructors of Integer and Natural can be wired-in. It means that we don't have to query them from interfaces. It also means that numeric literals don't have to carry their type with them. * The same code is used whatever ghc-bignum backend is enabled. In particular, conversion of bignum literals into final Core expressions is now much more straightforward. Bignum closure inspection too. * GHC itself doesn't depend on any integer-* package anymore * The `integerLibrary` setting is gone. - - - - - 0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `base` package * GHC.Natural isn't implemented in `base` anymore. It is provided by ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural primitives in `base` without fearing issues with built-in rewrite rules (cf #15286) * `base` doesn't conditionally depend on an integer-* package anymore, it depends on ghc-bignum * Some duplicated code in integer-* can now be factored in GHC.Float * ghc-bignum tries to use a uniform naming convention so most of the other changes are renaming - - - - - aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `make` based build system * replace integer-* package selection with ghc-bignum backend selection - - - - - f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update testsuite * support detection of slow ghc-bignum backend (to replace the detection of integer-simple use). There are still some test cases that the native backend doesn't handle efficiently enough. * remove tests for GMP only functions that have been removed from ghc-bignum * fix test results showing dependent packages (e.g. integer-gmp) or showing suggested instances * fix test using Integer/Natural API or showing internal names - - - - - dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update Hadrian * support ghc-bignum backend selection in flavours and command-line * support ghc-bignum "--check" flag (compare results of selected backend against results of the native one) in flavours and command-line (e.g. pass --bignum=check-gmp" to check the "gmp" backend) * remove the hack to workaround #15286 * build GMP only when the gmp backend is used * remove hacks to workaround `text` package flags about integer-*. We fix `text` to use ghc-bignum unconditionally in another patch - - - - - fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Bump bytestring and text submodules - - - - - 1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00 docs: mention -hiedir in docs for -outputdir [skip ci] - - - - - 729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00 Hadrian: fix build on Mac OS Catalina (#17798) - - - - - 95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00 Relax allocation threshold for T12150. This test performs little work, so the most minor allocation changes often cause the test to fail. Increasing the threshold to 2% should help with this. - - - - - 8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00 hadrian: Bump pinned cabal.project to an existent index-state - - - - - 08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00 Fix uninitialized field read in Linker.c Valgrind report of the bug when running the test `linker_unload`: ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522) ==29666== by 0x36C0600: loadArchive (LoadArchive.c:626) ==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload) ==29666== ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507) ==29666== by 0x369CA8D: loadObj_ (Linker.c:1536) ==29666== by 0x369CB17: loadObj (Linker.c:1557) ==29666== by 0x3866BC: main (linker_unload.c:33) The problem is `mkOc` allocates a new `ObjectCode` and calls `setOcInitialStatus` without initializing the `status` field. `setOcInitialStatus` reads the field as first thing: static void setOcInitialStatus(ObjectCode* oc) { if (oc->status == OBJECT_DONT_RESOLVE) return; if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; } } `setOcInitialStatus` is unsed in two places for two different purposes: in `mkOc` where we don't have the `status` field initialized yet (`mkOc` is supposed to initialize it), and `loadOc` where we do have `status` field initialized and we want to update it. Instead of splitting the function into two functions which are both called just once I inline the functions in the use sites and remove it. Fixes #18342 - - - - - da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00 fix windows bootstrap due to linker changes - - - - - 2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00 DynFlags: store default depth in SDocContext (#17957) It avoids having to use DynFlags to reach for pprUserLength. - - - - - d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00 Move tablesNextToCode field into Platform tablesNextToCode is a platform setting and doesn't belong into DynFlags (#17957). Doing this is also a prerequisite to fix #14335 where we deal with two platforms (target and host) that may have different platform settings. - - - - - 809caedf by John Ericson at 2020-06-23T22:47:37-04:00 Switch from HscSource to IsBootInterface for module lookup in GhcMake We look up modules by their name, and not their contents. There is no way to separately reference a signature vs regular module; you get what you get. Only boot files can be referenced indepenently with `import {-# SOURCE #-}`. - - - - - 7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Cmm: introduce SAVE_REGS/RESTORE_REGS We don't want to save both Fn and Dn register sets on x86-64 as they are aliased to the same arch register (XMMn). Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]` which makes a set of Cmm registers alive so that they cover all arch registers used to pass parameter, we could have Fn, Dn and XMMn alive at the same time. It made the LLVM code generator choke (see #17920). Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of registers. - - - - - 2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00 CmmToC: don't add extern decl to parsed Cmm data Previously, if a .cmm file *not in the RTS* contained something like: ```cmm section "rodata" { msg : bits8[] "Test\n"; } ``` It would get compiled by CmmToC into: ```c ERW_(msg); const char msg[] = "Test\012"; ``` and fail with: ``` /tmp/ghc32129_0/ghc_4.hc:5:12: error: error: conflicting types for \u2018msg\u2019 const char msg[] = "Test\012"; ^~~ In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error: /tmp/ghc32129_0/ghc_4.hc:4:6: error: note: previous declaration of \u2018msg\u2019 was here ERW_(msg); ^ /builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error: note: in definition of macro \u2018ERW_\u2019 #define ERW_(X) extern StgWordArray (X) ^ ``` See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes Now we don't generate these extern declarations (ERW_, etc.) for top-level data. It shouldn't change anything for the RTS (the only place we use .cmm files) as it is already special cased in `GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit extern declarations when needed. Note that it allows `cgrun069` test to pass with CmmToC (cf #15467). - - - - - 5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00 LLVM: refactor and comment register padding code (#17920) - - - - - cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Add tests for #17920 Metric Decrease: T12150 T12234 - - - - - a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00 Fix issue #18262 by zonking constraints after solving Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results. - - - - - 181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00 Fix a buglet in Simplify.simplCast This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal - - - - - 625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00 Two small tweaks to Coercion.simplifyArgsWorker These tweaks affect the inner loop of simplifyArgsWorker, which in turn is called from the flattener in Flatten.hs. This is a key perf bottleneck to T9872{a,b,c,d}. These two small changes have a modest but useful benefit. No change in functionality whatsoever. Relates to #18354 - - - - - b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00 Don't use timesInt2# with GHC < 8.11 (fix #18358) - - - - - 7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00 Fix invalid printf format - - - - - a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00 Add missing entry to freeNamesItem (#18369) - - - - - 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - efa9c6f2 by Ben Gamari at 2020-10-31T20:14:23-04:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - 18 changed files: - + .git-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/merge_request_templates/merge-request.md - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - − compiler/GHC/Builtin/Names.hs-boot - compiler/GHC/Builtin/Names/TH.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92c7a720b306a40cb238c2eef7e1e4a74e82ffaa...efa9c6f2846dddf2ac85d49ff54fb5d9f6aa53a8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92c7a720b306a40cb238c2eef7e1e4a74e82ffaa...efa9c6f2846dddf2ac85d49ff54fb5d9f6aa53a8 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 Sun Nov 1 00:47:59 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 20:47:59 -0400 Subject: [Git][ghc/ghc][wip/fix-testsuite-gs] 746 commits: Enable large address space optimization on windows. Message-ID: <5f9e05bf4830f_7853fb642ce0e2c1804da@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/fix-testsuite-gs at Glasgow Haskell Compiler / GHC Commits: 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - cdaf427c by GHC GitLab CI at 2020-10-31T20:47:56-04:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 23 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/test-metrics.sh - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Builtin/RebindableNames.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Uniques.hs-boot - compiler/GHC/Builtin/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c16f1afe5f4d1cfc91e299328b5b9c31a2ea20fe...cdaf427c21fdd0f0ea1088baaecbae28c4e67695 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c16f1afe5f4d1cfc91e299328b5b9c31a2ea20fe...cdaf427c21fdd0f0ea1088baaecbae28c4e67695 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 Sun Nov 1 00:57:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 20:57:44 -0400 Subject: [Git][ghc/ghc][wip/T18043] 746 commits: Enable large address space optimization on windows. Message-ID: <5f9e0808f3849_7853fb6425946dc1810b4@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18043 at Glasgow Haskell Compiler / GHC Commits: 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - 0759fec7 by Ben Gamari at 2020-10-31T20:57:35-04:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 23 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/test-metrics.sh - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Builtin/RebindableNames.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Uniques.hs-boot - compiler/GHC/Builtin/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5883fd4105547f738fa6db2f595d1d798b7e72e7...0759fec79169d14f3266b460d62c2e1080646b4c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5883fd4105547f738fa6db2f595d1d798b7e72e7...0759fec79169d14f3266b460d62c2e1080646b4c 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 Sun Nov 1 01:13:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 21:13:26 -0400 Subject: [Git][ghc/ghc][wip/T18234] 872 commits: gitlab-ci: Allow ARMv7 job to fail Message-ID: <5f9e0bb67b514_7858a295ec1820d9@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00 gitlab-ci: Allow ARMv7 job to fail Due to #18298. - - - - - 32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00 Clean up boot vs non-boot disambiguating types We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule. - - - - - c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00 docs: Add more details on InterruptibleFFI. Details from https://gitlab.haskell.org/ghc/ghc/issues/8684 and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430 - - - - - 1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00 Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr. MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd. This regression did not make it into a release of GHC. Here, the original behavior is restored, and FinalPtr is given the same treatment as PlainPtr. - - - - - 2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00 Fix documentation on type families not being extracted It looks like the location of the Names used for CoAxioms on type families are now located at their type constructors. Previously, Docs.hs thought the Names were located in the RHS, so the RealSrcSpan in the instanceMap and getInstLoc didn't match up. Fixes #18241 - - - - - 6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00 GHC.Hs.Instances: Compile with -O0 This module contains exclusively Data instances, which are going to be slow no matter what we do. Furthermore, they are incredibly slow to compile with optimisation (see #9557). Consequently we compile this with -O0. See #18254. - - - - - c330331a by nineonine at 2020-06-04T04:37:59-04:00 Add test for #17669 - - - - - cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00 rts: Add Windows-specific implementation of rtsSleep Previously we would use the POSIX path, which uses `nanosleep`. However, it turns out that `nanosleep` is provided by `libpthread` on Windows. In general we don't want to incur such a dependency. Avoid this by simply using `Sleep` on Windows. Fixes #18272. - - - - - ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00 compiler: Disable use of process jobs with process < 1.6.9 Due to #17926. - - - - - 6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00 [linker] Adds void printLoadedObjects(void); This allows us to dump in-memory object code locations for debugging. Fixup printLoadedObjects prototype - - - - - af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00 base: fix sign confusion in log1mexp implementation (fix #17125) author: claude (https://gitlab.haskell.org/trac-claude) The correct threshold for log1mexp is -(log 2) with the current specification of log1mexp. This change improves accuracy for large negative inputs. To avoid code duplication, a small helper function is added; it isn't the default implementation in Floating because it needs Ord. This patch does nothing to address that the Haskell specification is different from that in common use in other languages. - - - - - 2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00 Simple subsumption This patch simplifies GHC to use simple subsumption. Ticket #17775 Implements GHC proposal #287 https://github.com/ghc-proposals/ghc-proposals/blob/master/ proposals/0287-simplify-subsumption.rst All the motivation is described there; I will not repeat it here. The implementation payload: * tcSubType and friends become noticably simpler, because it no longer uses eta-expansion when checking subsumption. * No deeplyInstantiate or deeplySkolemise That in turn means that some tests fail, by design; they can all be fixed by eta expansion. There is a list of such changes below. Implementing the patch led me into a variety of sticky corners, so the patch includes several othe changes, some quite significant: * I made String wired-in, so that "foo" :: String rather than "foo" :: [Char] This improves error messages, and fixes #15679 * The pattern match checker relies on knowing about in-scope equality constraints, andd adds them to the desugarer's environment using addTyCsDs. But the co_fn in a FunBind was missed, and for some reason simple-subsumption ends up with dictionaries there. So I added a call to addTyCsDs. This is really part of #18049. * I moved the ic_telescope field out of Implication and into ForAllSkol instead. This is a nice win; just expresses the code much better. * There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader. We called checkDataKindSig inside tc_kind_sig, /before/ solveEqualities and zonking. Obviously wrong, easily fixed. * solveLocalEqualitiesX: there was a whole mess in here, around failing fast enough. I discovered a bad latent bug where we could successfully kind-check a type signature, and use it, but have unsolved constraints that could fill in coercion holes in that signature -- aargh. It's all explained in Note [Failure in local type signatures] in GHC.Tc.Solver. Much better now. * I fixed a serious bug in anonymous type holes. IN f :: Int -> (forall a. a -> _) -> Int that "_" should be a unification variable at the /outer/ level; it cannot be instantiated to 'a'. This was plain wrong. New fields mode_lvl and mode_holes in TcTyMode, and auxiliary data type GHC.Tc.Gen.HsType.HoleMode. This fixes #16292, but makes no progress towards the more ambitious #16082 * I got sucked into an enormous refactoring of the reporting of equality errors in GHC.Tc.Errors, especially in mkEqErr1 mkTyVarEqErr misMatchMsg misMatchMsgOrCND In particular, the very tricky mkExpectedActualMsg function is gone. It took me a full day. But the result is far easier to understand. (Still not easy!) This led to various minor improvements in error output, and an enormous number of test-case error wibbles. One particular point: for occurs-check errors I now just say Can't match 'a' against '[a]' rather than using the intimidating language of "occurs check". * Pretty-printing AbsBinds Tests review * Eta expansions T11305: one eta expansion T12082: one eta expansion (undefined) T13585a: one eta expansion T3102: one eta expansion T3692: two eta expansions (tricky) T2239: two eta expansions T16473: one eta determ004: two eta expansions (undefined) annfail06: two eta (undefined) T17923: four eta expansions (a strange program indeed!) tcrun035: one eta expansion * Ambiguity check at higher rank. Now that we have simple subsumption, a type like f :: (forall a. Eq a => Int) -> Int is no longer ambiguous, because we could write g :: (forall a. Eq a => Int) -> Int g = f and it'd typecheck just fine. But f's type is a bit suspicious, and we might want to consider making the ambiguity check do a check on each sub-term. Meanwhile, these tests are accepted, whereas they were previously rejected as ambiguous: T7220a T15438 T10503 T9222 * Some more interesting error message wibbles T13381: Fine: one error (Int ~ Exp Int) rather than two (Int ~ Exp Int, Exp Int ~ Int) T9834: Small change in error (improvement) T10619: Improved T2414: Small change, due to order of unification, fine T2534: A very simple case in which a change of unification order means we get tow unsolved constraints instead of one tc211: bizarre impredicative tests; just accept this for now Updates Cabal and haddock submodules. Metric Increase: T12150 T12234 T5837 haddock.base Metric Decrease: haddock.compiler haddock.Cabal haddock.base Merge note: This appears to break the `UnliftedNewtypesDifficultUnification` test. It has been marked as broken in the interest of merging. (cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5) - - - - - 2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00 Simplify bindLHsTyVarBndrs and bindHsQTyVars Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate `Maybe` arguments, which I find terribly confusing. Thankfully, it's possible to remove one `Maybe` argument from each of these functions, which this patch accomplishes: * `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if GHC should warn about any of the quantified type variables going unused. However, every call site uses `Nothing` in practice. This makes sense, since it doesn't really make sense to warn about unused type variables bound by an `LHsQTyVars`. For instance, you wouldn't warn about the `a` in `data Proxy a = Proxy` going unused. As a result, I simply remove this `Maybe SDoc` argument altogether. * `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same reasons that `bindHsQTyVars` took one. To make things more confusing, however, `bindLHsTyVarBndrs` also takes a separate `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in warnings and error messages. In practice, the `Maybe SDoc` and the `HsDocContext` often contain the same text. See the call sites for `bindLHsTyVarBndrs` in `rnFamInstEqn` and `rnConDecl`, for instance. There are only a handful of call sites where the text differs between the `Maybe SDoc` and `HsDocContext` arguments: * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`" and the `HsDocContext` says "`In the transformation rule`". * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says "`In the type`" but the `HsDocContext` is inhereted from the surrounding context (e.g., if `rnHsTyKi` were called on a top-level type signature, the `HsDocContext` would be "`In the type signature`" instead) In both cases, warnings/error messages arguably _improve_ by unifying making the `Maybe SDoc`'s text match that of the `HsDocContext`. As a result, I decided to remove the `Maybe SDoc` argument to `bindLHsTyVarBndrs` entirely and simply reuse the text from the `HsDocContext`. (I decided to change the phrase "transformation rule" to "rewrite rule" while I was in the area.) The `Maybe SDoc` argument has one other purpose: signaling when to emit "`Unused quantified type variable`" warnings. To recover this functionality, I replaced the `Maybe SDoc` argument with a boolean-like `WarnUnusedForalls` argument. The only `bindLHsTyVarBndrs` call site that chooses _not_ to emit these warnings in `bindHsQTyVars`. - - - - - e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00 hadrian: Add missing deriveConstants dependency on ghcplatform.h deriveConstants wants to compile C sources which #include PosixSource.h, which itself #includes ghcplatform.h. Make sure that Hadrian knows about this dependency. Fixes #18290. - - - - - b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00 ghc-prim needs to depend on libc and libm libm is just an empty shell on musl, and all the math functions are contained in libc. - - - - - 6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00 Disable DLL loading if without system linker Some platforms (musl, aarch64) do not have a working dynamic linker implemented in the libc, even though we might see dlopen. It will ultimately just return that this is not supported. Hence we'll add a flag to the compiler to flat our disable loading dlls. This is needed as we will otherwise try to load the shared library even if this will subsequently fail. At that point we have given up looking for static options though. - - - - - 4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00 Range is actually +/-2^32, not +/-2^31 See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf - - - - - f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00 OccurAnal: Avoid exponential behavior due to where clauses Previously the `Var` case of `occAnalApp` could in some cases (namely in the case of `runRW#` applications) call `occAnalRhs` two. In the case of nested `runRW#`s this results in exponential complexity. In some cases the compilation time that resulted would be very long indeed (see #18296). Fixes #18296. Metric Decrease: T9961 T12150 T12234 - - - - - 9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00 Add link to GHC's wiki in the GHC API header This adds a URL to point to GHC's wiki in the GHC API header. Newcomers could easily find more information from the GHC API's web like [1]. [1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html [skip ci] - - - - - 72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00 Make GADT constructors adhere to the forall-or-nothing rule properly Issue #18191 revealed that the types of GADT constructors don't quite adhere to the `forall`-or-nothing rule. This patch serves to clean up this sad state of affairs somewhat. The main change is not in the code itself, but in the documentation, as this patch introduces two sections to the GHC User's Guide: * A "Formal syntax for GADTs" section that presents a BNF-style grammar for what is and isn't allowed in GADT constructor types. This mostly exists to codify GHC's existing behavior, but it also imposes a new restriction that addresses #18191: the outermost `forall` and/or context in a GADT constructor is not allowed to be surrounded by parentheses. Doing so would make these `forall`s/contexts nested, and GADTs do not support nested `forall`s/contexts at present. * A "`forall`-or-nothing rule" section that describes exactly what the `forall`-or-nothing rule is all about. Surprisingly, there was no mention of this anywhere in the User's Guide up until now! To adhere the new specification in the "Formal syntax for GADTs" section of the User's Guide, the following code changes were made: * A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced. This is very much like `splitLHsSigmaTy`, except that it avoids splitting apart any parentheses, which can be syntactically significant for GADT types. See `Note [No nested foralls or contexts in GADT constructors]` in `GHC.Hs.Type`. * `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return it when given a prefix GADT constructor. Unlike `ConDeclGADT`, `ConDeclGADTPrefixPs` does not split the GADT type into its argument and result types, as this cannot be done until after the type is renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why this is the case). * `GHC.Renamer.Module.rnConDecl` now has an additional case for `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into its `forall`s, context, argument types, and result type, and (2) checks for nested `forall`s/contexts. Step (2) used to be performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather than the renamer, but now the relevant code from the typechecker can simply be deleted. One nice side effect of this change is that we are able to give a more accurate error message for GADT constructors that use visible dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`), which improves the stderr in the `T16326_Fail6` test case. Fixes #18191. Bumps the Haddock submodule. - - - - - a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00 Always use rnImplicitBndrs to bring implicit tyvars into scope This implements a first step towards #16762 by changing the renamer to always use `rnImplicitBndrs` to bring implicitly bound type variables into scope. The main change is in `rnFamInstEqn` and `bindHsQTyVars`, which previously used _ad hoc_ methods of binding their implicit tyvars. There are a number of knock-on consequences: * One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding mechanism was to give more precise source locations in `-Wunused-type-patterns` warnings. (See https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an example of this.) However, these warnings are actually a little _too_ precise, since implicitly bound type variables don't have exact binding sites like explicitly bound type variables do. A similar problem existed for "`Different names for the same type variable`" errors involving implicit tyvars bound by `bindHsQTyVars`. Therefore, we simply accept the less precise (but more accurate) source locations from `rnImplicitBndrs` in `rnFamInstEqn` and `bindHsQTyVars`. See `Note [Source locations for implicitly bound type variables]` in `GHC.Rename.HsType` for the full story. * In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs to be able to look up names from the parent class (in the event that we are renaming an associated type family instance). As a result, `rnImplicitBndrs` now takes an argument of type `Maybe assoc`, which is `Just` in the event that a type family instance is associated with a class. * Previously, GHC kept track of three type synonyms for free type variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups` (which are allowed to contain duplicates), and `FreeKiTyVarsNoDups` (which contain no duplicates). However, making is a distinction between `-Dups` and `-NoDups` is now pointless, as all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually end up being passed to `rnImplicitBndrs`, which removes duplicates. As a result, I decided to just get rid of `FreeKiTyVarsDups` and `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`. * The `bindLRdrNames` and `deleteBys` functions are now dead code, so I took the liberty of removing them. - - - - - 24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00 Clarify leaf module names for new module hierarchy This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00 rts: Remove unused GET_ENTRY closure macro This macro is not used and got broken in the meantime, as ENTRY_CODE was deleted. - - - - - 87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00 Fix -fkeep-cafs flag name in users guide - - - - - ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00 Expose impliedGFlags, impledOffGFlags, impliedXFlags - - - - - 7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00 Cross-module LambdaFormInfo passing - Store LambdaFormInfos of exported Ids in interface files - Use them in importing modules This is for optimization purposes: if we know LambdaFormInfo of imported Ids we can generate more efficient calling code, see `getCallMethod`. Exporting (putting them in interface files or in ModDetails) and importing (reading them from interface files) are both optional. We don't assume known LambdaFormInfos anywhere and do not change how we call Ids with unknown LambdaFormInfos. Runtime, allocation, and residency numbers when building Cabal-the-library (commit 0d4ee7ba3): (Log and .hp files are in the MR: !2842) | | GHC HEAD | This patch | Diff | |-----|----------|------------|----------------| | -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% | | -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% | | -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% | | | GHC HEAD | This patch | Diff | |-----|-----------------|-----------------|----------------------------| | -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% | | -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% | | -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% | NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively turn all GCs into major GCs, and do GC more often. | | GHC HEAD | This patch | Diff | |-----|----------------------------|------------------------------|----------------------------| | -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% | | -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% | | -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% | NoFib results: -------------------------------------------------------------------------------- Program Size Allocs Instrs Reads Writes -------------------------------------------------------------------------------- CS 0.0% 0.0% +0.0% +0.0% +0.0% CSD 0.0% 0.0% 0.0% +0.0% +0.0% FS 0.0% 0.0% +0.0% +0.0% +0.0% S 0.0% 0.0% +0.0% +0.0% +0.0% VS 0.0% 0.0% +0.0% +0.0% +0.0% VSD 0.0% 0.0% +0.0% +0.0% +0.1% VSM 0.0% 0.0% +0.0% +0.0% +0.0% anna 0.0% 0.0% -0.3% -0.8% -0.0% ansi 0.0% 0.0% -0.0% -0.0% 0.0% atom 0.0% 0.0% -0.0% -0.0% 0.0% awards 0.0% 0.0% -0.1% -0.3% 0.0% banner 0.0% 0.0% -0.0% -0.0% -0.0% bernouilli 0.0% 0.0% -0.0% -0.0% -0.0% binary-trees 0.0% 0.0% -0.0% -0.0% +0.0% boyer 0.0% 0.0% -0.0% -0.0% 0.0% boyer2 0.0% 0.0% -0.0% -0.0% 0.0% bspt 0.0% 0.0% -0.0% -0.2% 0.0% cacheprof 0.0% 0.0% -0.1% -0.4% +0.0% calendar 0.0% 0.0% -0.0% -0.0% 0.0% cichelli 0.0% 0.0% -0.9% -2.4% 0.0% circsim 0.0% 0.0% -0.0% -0.0% 0.0% clausify 0.0% 0.0% -0.1% -0.3% 0.0% comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0% compress 0.0% 0.0% -0.0% -0.0% -0.0% compress2 0.0% 0.0% -0.0% -0.0% 0.0% constraints 0.0% 0.0% -0.1% -0.2% -0.0% cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0% cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0% cse 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0% dom-lt 0.0% 0.0% -0.1% -0.2% 0.0% eliza 0.0% 0.0% -0.5% -1.5% 0.0% event 0.0% 0.0% -0.0% -0.0% -0.0% exact-reals 0.0% 0.0% -0.1% -0.3% +0.0% exp3_8 0.0% 0.0% -0.0% -0.0% -0.0% expert 0.0% 0.0% -0.3% -1.0% -0.0% fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0% fasta 0.0% 0.0% -0.0% -0.0% +0.0% fem 0.0% 0.0% -0.0% -0.0% 0.0% fft 0.0% 0.0% -0.0% -0.0% 0.0% fft2 0.0% 0.0% -0.0% -0.0% 0.0% fibheaps 0.0% 0.0% -0.0% -0.0% +0.0% fish 0.0% 0.0% 0.0% -0.0% +0.0% fluid 0.0% 0.0% -0.4% -1.2% +0.0% fulsom 0.0% 0.0% -0.0% -0.0% 0.0% gamteb 0.0% 0.0% -0.1% -0.3% 0.0% gcd 0.0% 0.0% -0.0% -0.0% 0.0% gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0% genfft 0.0% 0.0% -0.0% -0.0% 0.0% gg 0.0% 0.0% -0.0% -0.0% +0.0% grep 0.0% 0.0% -0.0% -0.0% -0.0% hidden 0.0% 0.0% -0.1% -0.4% -0.0% hpg 0.0% 0.0% -0.2% -0.5% +0.0% ida 0.0% 0.0% -0.0% -0.0% +0.0% infer 0.0% 0.0% -0.3% -0.8% -0.0% integer 0.0% 0.0% -0.0% -0.0% +0.0% integrate 0.0% 0.0% -0.0% -0.0% 0.0% k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0% kahan 0.0% 0.0% -0.0% -0.0% +0.0% knights 0.0% 0.0% -2.2% -5.4% 0.0% lambda 0.0% 0.0% -0.6% -1.8% 0.0% last-piece 0.0% 0.0% -0.0% -0.0% 0.0% lcss 0.0% 0.0% -0.0% -0.1% 0.0% life 0.0% 0.0% -0.0% -0.1% 0.0% lift 0.0% 0.0% -0.2% -0.6% +0.0% linear 0.0% 0.0% -0.0% -0.0% -0.0% listcompr 0.0% 0.0% -0.0% -0.0% 0.0% listcopy 0.0% 0.0% -0.0% -0.0% 0.0% maillist 0.0% 0.0% -0.1% -0.3% +0.0% mandel 0.0% 0.0% -0.0% -0.0% 0.0% mandel2 0.0% 0.0% -0.0% -0.0% -0.0% mate +0.0% 0.0% -0.0% -0.0% -0.0% minimax 0.0% 0.0% -0.2% -1.0% 0.0% mkhprog 0.0% 0.0% -0.1% -0.2% -0.0% multiplier 0.0% 0.0% -0.0% -0.0% -0.0% n-body 0.0% 0.0% -0.0% -0.0% +0.0% nucleic2 0.0% 0.0% -0.1% -0.2% 0.0% para 0.0% 0.0% -0.0% -0.0% -0.0% paraffins 0.0% 0.0% -0.0% -0.0% 0.0% parser 0.0% 0.0% -0.2% -0.7% 0.0% parstof 0.0% 0.0% -0.0% -0.0% +0.0% pic 0.0% 0.0% -0.0% -0.0% 0.0% pidigits 0.0% 0.0% +0.0% +0.0% +0.0% power 0.0% 0.0% -0.2% -0.6% +0.0% pretty 0.0% 0.0% -0.0% -0.0% -0.0% primes 0.0% 0.0% -0.0% -0.0% 0.0% primetest 0.0% 0.0% -0.0% -0.0% -0.0% prolog 0.0% 0.0% -0.3% -1.1% 0.0% puzzle 0.0% 0.0% -0.0% -0.0% 0.0% queens 0.0% 0.0% -0.0% -0.0% +0.0% reptile 0.0% 0.0% -0.0% -0.0% 0.0% reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0% rewrite 0.0% 0.0% -0.7% -2.5% -0.0% rfib 0.0% 0.0% -0.0% -0.0% 0.0% rsa 0.0% 0.0% -0.0% -0.0% 0.0% scc 0.0% 0.0% -0.1% -0.2% -0.0% sched 0.0% 0.0% -0.0% -0.0% -0.0% scs 0.0% 0.0% -1.0% -2.6% +0.0% simple 0.0% 0.0% +0.0% -0.0% +0.0% solid 0.0% 0.0% -0.0% -0.0% 0.0% sorting 0.0% 0.0% -0.6% -1.6% 0.0% spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0% sphere 0.0% 0.0% -0.0% -0.0% -0.0% symalg 0.0% 0.0% -0.0% -0.0% +0.0% tak 0.0% 0.0% -0.0% -0.0% 0.0% transform 0.0% 0.0% -0.0% -0.0% 0.0% treejoin 0.0% 0.0% -0.0% -0.0% 0.0% typecheck 0.0% 0.0% -0.0% -0.0% +0.0% veritas +0.0% 0.0% -0.2% -0.4% +0.0% wang 0.0% 0.0% -0.0% -0.0% 0.0% wave4main 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0% x2n1 0.0% 0.0% -0.0% -0.0% -0.0% -------------------------------------------------------------------------------- Min 0.0% 0.0% -2.2% -5.4% -0.0% Max +0.0% 0.0% +0.0% +0.0% +0.1% Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0% Metric increases micro benchmarks tracked in #17686: Metric Increase: T12150 T12234 T12425 T13035 T5837 T6048 T9233 Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00 Give Language a Bounded instance - - - - - 9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Optimisation in Unique.Supply This patch switches on -fno-state-hack in GHC.Types.Unique.Supply. It turned out that my fixes for #18078 (coercion floating) changed the optimisation pathway for mkSplitUniqSupply in such a way that we had an extra allocation inside the inner loop. Adding -fno-state-hack fixed that -- and indeed the loop in mkSplitUniqSupply is a classic example of the way in which -fno-state-hack can be bad; see #18238. Moreover, the new code is better than the old. They allocate the same, but the old code ends up with a partial application. The net effect is that the test perf/should_run/UniqLoop runs 20% faster! From 2.5s down to 2.0s. The allocation numbers are the same -- but elapsed time falls. Good! The bad thing about this is that it's terribly delicate. But at least it's a good example of such delicacy in action. There is a long Note [Optimising the unique supply] which now explains all this. - - - - - 6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Implement cast worker/wrapper properly The cast worker/wrapper transformation transforms x = e |> co into y = e x = y |> co This is done by the simplifier, but we were being careless about transferring IdInfo from x to y, and about what to do if x is a NOINLNE function. This resulted in a series of bugs: #17673, #18093, #18078. This patch fixes all that: * Main change is in GHC.Core.Opt.Simplify, and the new prepareBinding function, which does this cast worker/wrapper transform. See Note [Cast worker/wrappers]. * There is quite a bit of refactoring around prepareRhs, makeTrivial etc. It's nicer now. * Some wrappers from strictness and cast w/w, notably those for a function with a NOINLINE, should inline very late. There wasn't really a mechanism for that, which was an existing bug really; so I invented a new finalPhase = Phase (-1). It's used for all simplifier runs after the user-visible phase 2,1,0 have run. (No new runs of the simplifier are introduced thereby.) See new Note [Compiler phases] in GHC.Types.Basic; the main changes are in GHC.Core.Opt.Driver * Doing this made me trip over two places where the AnonArgFlag on a FunTy was being lost so we could end up with (Num a -> ty) rather than (Num a => ty) - In coercionLKind/coercionRKind - In contHoleType in the Simplifier I fixed the former by defining mkFunctionType and using it in coercionLKind/RKind. I could have done the same for the latter, but the information is almost to hand. So I fixed the latter by - adding sc_hole_ty to ApplyToVal (like ApplyToTy), - adding as_hole_ty to ValArg (like TyArg) - adding sc_fun_ty to StrictArg Turned out I could then remove ai_type from ArgInfo. This is just moving the deck chairs around, but it worked out nicely. See the new Note [AnonArgFlag] in GHC.Types.Var * When looking at the 'arity decrease' thing (#18093) I discovered that stable unfoldings had a much lower arity than the actual optimised function. That's what led to the arity-decrease message. Simple solution: eta-expand. It's described in Note [Eta-expand stable unfoldings] in GHC.Core.Opt.Simplify * I also discovered that unsafeCoerce wasn't being inlined if the context was boring. So (\x. f (unsafeCoerce x)) would create a thunk -- yikes! I fixed that by making inlineBoringOK a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold. I also found that unsafeCoerceName was unused, so I removed it. I made a test case for #18078, and a very similar one for #17673. The net effect of all this on nofib is very modest, but positive: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.4% -0.1% -3.1% -3.1% 0.0% fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0% maillist -0.4% -0.1% -7.8% -1.0% -14.3% primetest -0.4% -15.6% -7.1% -6.6% 0.0% -------------------------------------------------------------------------------- Min -0.9% -15.6% -13.3% -14.2% -14.3% Max -0.3% 0.0% +12.1% +12.4% 0.0% Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1% All following metric decreases are compile-time allocation decreases between -1% and -3%: Metric Decrease: T5631 T13701 T14697 T15164 - - - - - 32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00 Fix lookupGlobalOccRn_maybe sometimes reporting an error In some cases it was possible for lookupGlobalOccRn_maybe to return an error, when it should be returning a Nothing. If it called lookupExactOcc_either when there were no matching GlobalRdrElts in the otherwise case, it would return an error message. This could be caused when lookupThName_maybe in Template Haskell was looking in different namespaces (thRdrNameGuesses), guessing different namespaces that the name wasn't guaranteed to be found in. However, by addressing this some more accurate errors were being lost in the conversion to Maybes. So some of the lookup* functions have been shuffled about so that errors should always be ignored in lookup*_maybes, and propagated otherwise. This fixes #18263 - - - - - 9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00 Initialize the allocation counter in GHCi to 0 (Fixes #16012) According to the documentation for the function `getAllocationCounter` in [System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html) initialize the allocationCounter also in GHCi to 0. - - - - - 8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00 test: fix conc038 We had spurious failures of conc038 test on CI with stdout: ``` newThread started -mainThread -Haskell: 2 newThread back again +mainThread 1 sec later shutting down +Haskell: 2 ``` - - - - - 4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00 Release Notes: Add news from the pattern-match checker [skip ci] - - - - - 3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00 Only test T16190 with the NCG T16190 is meant to test a NCG feature. It has already caused spurious failures in other MRs (e.g. !2165) when LLVM is used. - - - - - 2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00 DynFlags refactoring VIII (#17957) * Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.* * Add LlvmOpts datatype to store Llvm backend options * Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and Llvm.MetaExpr) which require LlvmOpts. * Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`) - - - - - 7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove unused code - - - - - 72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor homeUnit * rename thisPackage into homeUnit * document and refactor several Backpack things - - - - - 8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Rename unsafeGetUnitInfo into unsafeLookupUnit - - - - - f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Add allowVirtualUnits field in PackageState Instead of always querying DynFlags to know whether we are allowed to use virtual units (i.e. instantiated on-the-fly, cf Note [About units] in GHC.Unit), we store it once for all in `PackageState.allowVirtualUnits`. This avoids using DynFlags too much (cf #17957) and is preliminary work for #14335. - - - - - e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Enhance UnitId use * use UnitId instead of String to identify wired-in units * use UnitId instead of Unit in the backend (Unit are only use by Backpack to produce type-checked interfaces, not real code) * rename lookup functions for consistency * documentation - - - - - 9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove LinkerUnitId type alias - - - - - d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor WiredMap * Remove WiredInUnitId and WiredUnitId type aliases - - - - - 3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document and refactor `mkUnit` and `mkUnitInfoMap` - - - - - d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove PreloadUnitId type alias - - - - - f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename listUnitInfoMap into listUnitInfo There is no Map involved - - - - - ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc. - - - - - 202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Make ClosureUnitInfoMap uses UnitInfoMap - - - - - 55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove ClosureUnitInfoMap - - - - - 653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit (2) * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc. - - - - - ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move dump_mod_map into initUnits - - - - - 598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move wiring of homeUnitInstantiations outside of mkUnitState - - - - - 437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00 Avoid timing module map dump in initUnits - - - - - 9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove preload parameter of mkUnitState * Remove preload parameter (unused) * Don't explicitly return preloaded units: redundant because already returned as "preloadUnits" field of UnitState - - - - - 266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: refactor unwireUnit - - - - - 9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document getPreloadUnitsAnd - - - - - bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: remove useless add_package parameter - - - - - 36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: make listVisibleModuleNames take a UnitState - - - - - 5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document add_package - - - - - 4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document closeUnitDeps - - - - - 42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: findWiredInUnits - - - - - a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: reportCycles, reportUnusable - - - - - 8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: merge_databases - - - - - fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: add UnitConfig datatype Avoid directly querying flags from DynFlags to build the UnitState. Instead go via UnitConfig so that we could reuse this to make another UnitState for plugins. - - - - - 4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move distrustAll into mkUnitState - - - - - 28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Create helper upd_wired_in_home_instantiations - - - - - ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Put database cache in UnitConfig - - - - - bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00 Don't return preload units when we set DyNFlags Preload units can be retrieved in UnitState when needed (i.e. in GHCi) - - - - - 1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 NCGConfig: remove useless ncgUnitId field - - - - - c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Doc: fix some comments - - - - - 456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Bump haddock submodule and allow metric decrease Metric Decrease: T12150 T12234 T5837 Metric Increase: T16190 - - - - - 42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00 Trim the demand for recursive product types Ticket #18304 showed that we need to be very careful when exploring the demand (esp usage demand) on recursive product types. This patch solves the problem by trimming the demand on such types -- in effect, a form of "widening". See the Note [Trimming a demand to a type] in DmdAnal, which explains how I did this by piggy-backing on an existing mechansim for trimming demands becuase of GADTs. The significant payload of this patch is very small indeed: * Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to avoid looking through recursive types. But on the way * I found that ae_rec_tc was entirely inoperative and did nothing. So I removed it altogether from DmdAnal. * I moved some code around in DmdAnal and Demand. (There are no actual changes in dmdFix.) * I changed the API of DmsAnal.dmdAnalRhsLetDown to return a StrictSig rather than a decorated Id * I removed the dead function peelTsFuns from Demand Performance effects: Nofib: 0.0% changes. Not surprising, because they don't use recursive products Perf tests T12227: 1% increase in compiler allocation, becuase $cto gets w/w'd. It did not w/w before because it takes a deeply nested argument, so the worker gets too many args, so we abandon w/w altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough) With this patch we trim the demands. That is not strictly necessary (since these Generic type constructors are like tuples -- they can't cause a loop) but the net result is that we now w/w $cto which is fine. UniqLoop: 16% decrease in /runtime/ allocation. The UniqSupply is a recursive product, so currently we abandon all strictness on 'churn'. With this patch 'churn' gets useful strictness, and we w/w it. Hooray Metric Decrease: UniqLoop Metric Increase: T12227 - - - - - 87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00 Add introductory prose for Data.Traversable - - - - - 9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00 Fix #12073: Add MonadFix Q instance - - - - - 220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00 testsuite: Increase size of T12150 As noted in #18319, this test was previously very fragile. Increase its size to make it more likely that its fails with its newly-increased acceptance threshold. Metric Increase: T12150 - - - - - 8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00 gitlab-ci: Always push perf notes Previously we ci.sh would run with `set -e` implying that we wouldn't push perf notes if the testsuite were to fail, even if it *only* failed due to perf notes. This rendered the whole performance testing story quite fragile as a single regressing commit would cause every successive commit to fail since a new baseline would not be uploaded. Fix this by ensuring that we always push performance notes. - - - - - 7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00 gitlab-ci: Eliminate redundant push of CI metrics - - - - - a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00 Use HsForAllTelescope to avoid inferred, visible foralls Currently, `HsForAllTy` permits the combination of `ForallVis` and `Inferred`, but you can't actually typecheck code that uses it (e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a new `HsForAllTelescope` data type that makes a type-level distinction between visible and invisible `forall`s such that visible `forall`s do not track `Specificity`. That part of the patch is actually quite small; the rest is simply changing consumers of `HsType` to accommodate this new type. Fixes #18235. Bumps the `haddock` submodule. - - - - - c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00 winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges. The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00 codeGen: Don't discard live case binders in unsafeEqualityProof logic Previously CoreToStg would unconditionally discard cases of the form: case unsafeEqualityProof of wild { _ -> rhs } and rather replace the whole thing with `rhs`. However, in some cases (see #18227) the case binder is still live, resulting in unbound occurrences in `rhs`. Fix this by only discarding the case if the case binder is dead. Fixes #18227. - - - - - e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00 testsuite: Add tests for #18227 T18227A is the original issue which gave rise to the ticket and depends upon bytestring. T18227B is a minimized reproducer. - - - - - 8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Fix rts include and library paths Fixes two bugs: * (?) and (<>) associated in a surprising way * We neglected to include libdw paths in the rts configure flags - - - - - bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Drop redundant GHC arguments Cabal should already be passing this arguments to GHC. - - - - - 01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00 FFI: Fix pass small ints in foreign call wrappers The Haskell calling convention requires integer parameters smaller than wordsize to be promoted to wordsize (where the upper bits are don't care). To access such small integer parameter read a word from the parameter array and then cast that word to the small integer target type. Fixes #15933 - - - - - 502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00 Fix "ndecreasingIndentation" in manual (#18116) - - - - - 9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00 Use foldl' in unionManyUniqDSets - - - - - 761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00 Load .lo as well. Some archives contain so called linker objects, with the affectionate .lo suffic. For example the musl libc.a will come in that form. We still want to load those objects, hence we should not discard them and look for .lo as well. Ultimately we might want to fix this proerly by looking at the file magic. - - - - - cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00 User's Guide: KnownNat evidence is Natural This bit of documentation got outdated after commit 1fcede43d2b30f33b7505e25eb6b1f321be0407f - - - - - d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00 Fix typos and formatting in user guide - - - - - 56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00 Resolve TODO - - - - - 3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00 Rename TcHoleErrors to GHC.Tc.Errors.Hole - - - - - d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00 hadrian: Build with threaded runtime if available See #16873. - - - - - 0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00 T16190: only measure bytes_allocated Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics fluctuate by 13%. - - - - - 4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00 docs: fix formatting in users guide - - - - - eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00 Move CLabel assertions into smart constructors (#17957) It avoids using DynFlags in the Outputable instance of Clabel to check assertions at pretty-printing time. - - - - - 7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00 base: Bump to 4.15.0.0 - - - - - 20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00 configure: Use grep -q instead of --quiet The latter is apparently not supported by busybox. - - - - - 40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00 Linear types (#15981) This is the first step towards implementation of the linear types proposal (https://github.com/ghc-proposals/ghc-proposals/pull/111). It features * A language extension -XLinearTypes * Syntax for linear functions in the surface language * Linearity checking in Core Lint, enabled with -dlinear-core-lint * Core-to-core passes are mostly compatible with linearity * Fields in a data type can be linear or unrestricted; linear fields have multiplicity-polymorphic constructors. If -XLinearTypes is disabled, the GADT syntax defaults to linear fields The following items are not yet supported: * a # m -> b syntax (only prefix FUN is supported for now) * Full multiplicity inference (multiplicities are really only checked) * Decent linearity error messages * Linear let, where, and case expressions in the surface language (each of these currently introduce the unrestricted variant) * Multiplicity-parametric fields * Syntax for annotating lambda-bound or let-bound with a multiplicity * Syntax for non-linear/multiple-field-multiplicity records * Linear projections for records with a single linear field * Linear pattern synonyms * Multiplicity coercions (test LinearPolyType) A high-level description can be found at https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation Following the link above you will find a description of the changes made to Core. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Matthew Pickering * Arnaud Spiwack With contributions from: * Mark Barbone * Alexander Vershilov Updates haddock submodule. - - - - - 6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00 Various performance improvements This implements several general performance improvements to GHC, to offset the effect of the linear types change. General optimisations: - Add a `coreFullView` function which iterates `coreView` on the head. This avoids making function recursive solely because the iterate `coreView` themselves. As a consequence, this functions can be inlined, and trigger case-of-known constructor (_e.g._ `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`, `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`, `tyConAppTyCon_maybe`). The common pattern about all these functions is that they are almost always used as views, and immediately consumed by a case expression. This commit also mark them asx `INLINE`. - In `subst_ty` add a special case for nullary `TyConApp`, which avoid allocations altogether. - Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This required quite a bit of module shuffling. case. `myTyConApp` enforces crucial sharing, which was lost during substitution. See also !2952 . - Make `subst_ty` stricter. - In `eqType` (specifically, in `nonDetCmpType`), add a special case, tested first, for the very common case of nullary `TyConApp`. `nonDetCmpType` has been made `INLINE` otherwise it is actually a regression. This is similar to the optimisations in !2952. Linear-type specific optimisations: - Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in the definition of the pattern synonyms `One` and `Many`. - Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`: `Multiplicity` now import `Type` normally, rather than from the `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the `One` and `Many` pattern synonyms. - Make `updateIdTypeAndMult` strict in its type and multiplicity - The `scaleIdBy` gets a specialised definition rather than being an alias to `scaleVarBy` - `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type, Type)` instead of `Type -> Maybe (Scaled Type, Type)` - Remove the `MultMul` pattern synonym in favour of a view `isMultMul` because pattern synonyms appear not to inline well. - in `eqType`, in a `FunTy`, compare multiplicities last: they are almost always both `Many`, so it helps failing faster. - Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the instances of `TyConApp ManyDataConTy []` are physically the same. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Arnaud Spiwack Metric Decrease: haddock.base T12227 T12545 T12990 T1969 T3064 T5030 T9872b Metric Increase: haddock.base haddock.Cabal haddock.compiler T12150 T12234 T12425 T12707 T13035 T13056 T15164 T16190 T18304 T1969 T3064 T3294 T5631 T5642 T5837 T6048 T9020 T9233 T9675 T9872a T9961 WWRec - - - - - 57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Remove integer-simple integer-simple uses lists of words (`[Word]`) to represent big numbers instead of ByteArray#: * it is less efficient than the newer ghc-bignum native backend * it isn't compatible with the big number representation that is now shared by all the ghc-bignum backends (based on the one that was used only in integer-gmp before). As a consequence, we simply drop integer-simple - - - - - 9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00 ghc-bignum library ghc-bignum is a newer package that aims to replace the legacy integer-simple and integer-gmp packages. * it supports several backends. In particular GMP is still supported and most of the code from integer-gmp has been merged in the "gmp" backend. * the pure Haskell "native" backend is new and is much faster than the previous pure Haskell implementation provided by integer-simple * new backends are easier to write because they only have to provide a few well defined functions. All the other code is common to all backends. In particular they all share the efficient small/big number distinction previously used only in integer-gmp. * backends can all be tested against the "native" backend with a simple Cabal flag. Backends are only allowed to differ in performance, their results should be the same. * Add `integer-gmp` compat package: provide some pattern synonyms and function aliases for those in `ghc-bignum`. It is intended to avoid breaking packages that depend on `integer-gmp` internals. Update submodules: text, bytestring Metric Decrease: Conversions ManyAlternatives ManyConstructors Naperian T10359 T10547 T10678 T12150 T12227 T12234 T12425 T13035 T13719 T14936 T1969 T4801 T4830 T5237 T5549 T5837 T8766 T9020 parsing001 space_leak_001 T16190 haddock.base On ARM and i386, T17499 regresses (+6% > 5%). On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%). Metric Increase: T17499 T13701 - - - - - 96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update compiler Thanks to ghc-bignum, the compiler can be simplified: * Types and constructors of Integer and Natural can be wired-in. It means that we don't have to query them from interfaces. It also means that numeric literals don't have to carry their type with them. * The same code is used whatever ghc-bignum backend is enabled. In particular, conversion of bignum literals into final Core expressions is now much more straightforward. Bignum closure inspection too. * GHC itself doesn't depend on any integer-* package anymore * The `integerLibrary` setting is gone. - - - - - 0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `base` package * GHC.Natural isn't implemented in `base` anymore. It is provided by ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural primitives in `base` without fearing issues with built-in rewrite rules (cf #15286) * `base` doesn't conditionally depend on an integer-* package anymore, it depends on ghc-bignum * Some duplicated code in integer-* can now be factored in GHC.Float * ghc-bignum tries to use a uniform naming convention so most of the other changes are renaming - - - - - aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `make` based build system * replace integer-* package selection with ghc-bignum backend selection - - - - - f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update testsuite * support detection of slow ghc-bignum backend (to replace the detection of integer-simple use). There are still some test cases that the native backend doesn't handle efficiently enough. * remove tests for GMP only functions that have been removed from ghc-bignum * fix test results showing dependent packages (e.g. integer-gmp) or showing suggested instances * fix test using Integer/Natural API or showing internal names - - - - - dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update Hadrian * support ghc-bignum backend selection in flavours and command-line * support ghc-bignum "--check" flag (compare results of selected backend against results of the native one) in flavours and command-line (e.g. pass --bignum=check-gmp" to check the "gmp" backend) * remove the hack to workaround #15286 * build GMP only when the gmp backend is used * remove hacks to workaround `text` package flags about integer-*. We fix `text` to use ghc-bignum unconditionally in another patch - - - - - fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Bump bytestring and text submodules - - - - - 1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00 docs: mention -hiedir in docs for -outputdir [skip ci] - - - - - 729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00 Hadrian: fix build on Mac OS Catalina (#17798) - - - - - 95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00 Relax allocation threshold for T12150. This test performs little work, so the most minor allocation changes often cause the test to fail. Increasing the threshold to 2% should help with this. - - - - - 8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00 hadrian: Bump pinned cabal.project to an existent index-state - - - - - 08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00 Fix uninitialized field read in Linker.c Valgrind report of the bug when running the test `linker_unload`: ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522) ==29666== by 0x36C0600: loadArchive (LoadArchive.c:626) ==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload) ==29666== ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507) ==29666== by 0x369CA8D: loadObj_ (Linker.c:1536) ==29666== by 0x369CB17: loadObj (Linker.c:1557) ==29666== by 0x3866BC: main (linker_unload.c:33) The problem is `mkOc` allocates a new `ObjectCode` and calls `setOcInitialStatus` without initializing the `status` field. `setOcInitialStatus` reads the field as first thing: static void setOcInitialStatus(ObjectCode* oc) { if (oc->status == OBJECT_DONT_RESOLVE) return; if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; } } `setOcInitialStatus` is unsed in two places for two different purposes: in `mkOc` where we don't have the `status` field initialized yet (`mkOc` is supposed to initialize it), and `loadOc` where we do have `status` field initialized and we want to update it. Instead of splitting the function into two functions which are both called just once I inline the functions in the use sites and remove it. Fixes #18342 - - - - - da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00 fix windows bootstrap due to linker changes - - - - - 2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00 DynFlags: store default depth in SDocContext (#17957) It avoids having to use DynFlags to reach for pprUserLength. - - - - - d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00 Move tablesNextToCode field into Platform tablesNextToCode is a platform setting and doesn't belong into DynFlags (#17957). Doing this is also a prerequisite to fix #14335 where we deal with two platforms (target and host) that may have different platform settings. - - - - - 809caedf by John Ericson at 2020-06-23T22:47:37-04:00 Switch from HscSource to IsBootInterface for module lookup in GhcMake We look up modules by their name, and not their contents. There is no way to separately reference a signature vs regular module; you get what you get. Only boot files can be referenced indepenently with `import {-# SOURCE #-}`. - - - - - 7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Cmm: introduce SAVE_REGS/RESTORE_REGS We don't want to save both Fn and Dn register sets on x86-64 as they are aliased to the same arch register (XMMn). Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]` which makes a set of Cmm registers alive so that they cover all arch registers used to pass parameter, we could have Fn, Dn and XMMn alive at the same time. It made the LLVM code generator choke (see #17920). Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of registers. - - - - - 2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00 CmmToC: don't add extern decl to parsed Cmm data Previously, if a .cmm file *not in the RTS* contained something like: ```cmm section "rodata" { msg : bits8[] "Test\n"; } ``` It would get compiled by CmmToC into: ```c ERW_(msg); const char msg[] = "Test\012"; ``` and fail with: ``` /tmp/ghc32129_0/ghc_4.hc:5:12: error: error: conflicting types for \u2018msg\u2019 const char msg[] = "Test\012"; ^~~ In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error: /tmp/ghc32129_0/ghc_4.hc:4:6: error: note: previous declaration of \u2018msg\u2019 was here ERW_(msg); ^ /builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error: note: in definition of macro \u2018ERW_\u2019 #define ERW_(X) extern StgWordArray (X) ^ ``` See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes Now we don't generate these extern declarations (ERW_, etc.) for top-level data. It shouldn't change anything for the RTS (the only place we use .cmm files) as it is already special cased in `GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit extern declarations when needed. Note that it allows `cgrun069` test to pass with CmmToC (cf #15467). - - - - - 5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00 LLVM: refactor and comment register padding code (#17920) - - - - - cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Add tests for #17920 Metric Decrease: T12150 T12234 - - - - - a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00 Fix issue #18262 by zonking constraints after solving Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results. - - - - - 181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00 Fix a buglet in Simplify.simplCast This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal - - - - - 625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00 Two small tweaks to Coercion.simplifyArgsWorker These tweaks affect the inner loop of simplifyArgsWorker, which in turn is called from the flattener in Flatten.hs. This is a key perf bottleneck to T9872{a,b,c,d}. These two small changes have a modest but useful benefit. No change in functionality whatsoever. Relates to #18354 - - - - - b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00 Don't use timesInt2# with GHC < 8.11 (fix #18358) - - - - - 7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00 Fix invalid printf format - - - - - a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00 Add missing entry to freeNamesItem (#18369) - - - - - 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - 13827447 by Ben Gamari at 2020-10-31T21:05:23-04:00 gitlab-ci: Add usage message to ci.sh - - - - - 80105a93 by Ben Gamari at 2020-10-31T21:13:10-04:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234. - - - - - 17 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Builtin/RebindableNames.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2136430dd8efbe1426eb0b761ad02bb63548e64...80105a93849b832c8223af3c23aa6fb505db4edf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2136430dd8efbe1426eb0b761ad02bb63548e64...80105a93849b832c8223af3c23aa6fb505db4edf 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 Sun Nov 1 01:45:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 21:45:44 -0400 Subject: [Git][ghc/ghc][wip/T17609] nativeGen: Deduplicate DWARF strings Message-ID: <5f9e13482f8b7_785ac4d9201942f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: ebf4de37 by Ben Gamari at 2020-10-31T21:41:21-04:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - 3 changed files: - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs Changes: ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -12,6 +12,7 @@ import GHC.Cmm.DebugBlock import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Platform +import GHC.Types.SrcLoc import GHC.Types.Unique import GHC.Types.Unique.Supply @@ -46,11 +47,12 @@ dwarfGen config modLoc us blocks = do compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + producer = dwarfStringFromString $ cProjectName ++ " " ++ cProjectVersion dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) - , dwName = fromMaybe "" (ml_hs_file modLoc) - , dwCompDir = addTrailingPathSeparator compPath - , dwProducer = cProjectName ++ " " ++ cProjectVersion + , dwName = dwarfStringFromString $ fromMaybe "" (ml_hs_file modLoc) + , dwCompDir = dwarfStringFromString $ addTrailingPathSeparator compPath + , dwProducer = producer , dwLowLabel = lowLabel , dwHighLabel = highLabel , dwLineLabel = dwarfLineLabel @@ -76,6 +78,9 @@ dwarfGen config modLoc us blocks = do , compileUnitFooter platform unitU ] + -- .debug_str section: Strings + let stringsSct = dwarfStringsSection (dwarfInfoStrings dwarfUnit) + -- .debug_line section: Generated mainly by the assembler, but we -- need to label it let lineSct = dwarfLineSection platform $$ @@ -92,7 +97,7 @@ dwarfGen config modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection platform $$ pprDwarfARanges platform aranges' unitU - return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') + return (infoSct $$ stringsSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. -- With split sections, each proc needs its own entry, since they may get @@ -177,7 +182,7 @@ parent, B. procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) - , dwName = case dblSourceTick prc of + , dwName = dwarfStringFromString $ case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) , dwLabel = dblCLabel prc @@ -208,7 +213,13 @@ blockToDwarf blk | otherwise = Nothing -- block was optimized out tickToDwarf :: Tickish () -> [DwarfInfo] -tickToDwarf (SourceNote ss _) = [DwarfSrcNote ss] +tickToDwarf (SourceNote ss _) = + [DwarfSrcNote { dwSpanFile = dwarfStringFromFastString (srcSpanFile ss) + , dwSpanStartLine = srcSpanStartLine ss + , dwSpanStartCol = srcSpanStartCol ss + , dwSpanEndLine = srcSpanEndLine ss + , dwSpanEndCol = srcSpanEndCol ss + }] tickToDwarf _ = [] -- | Generates the data for the debug frame section, which encodes the ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -86,12 +86,14 @@ dW_CHILDREN_no, dW_CHILDREN_yes :: Word8 dW_CHILDREN_no = 0 dW_CHILDREN_yes = 1 -dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, dW_FORM_string, dW_FORM_flag, +dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, + dW_FORM_strp,dW_FORM_string, dW_FORM_flag, dW_FORM_block1, dW_FORM_ref4, dW_FORM_ref_addr, dW_FORM_flag_present :: Word dW_FORM_addr = 0x01 dW_FORM_data2 = 0x05 dW_FORM_data4 = 0x06 dW_FORM_string = 0x08 +dW_FORM_strp = 0x0e dW_FORM_flag = 0x0c dW_FORM_block1 = 0x0a dW_FORM_ref_addr = 0x10 ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -2,12 +2,19 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RecordWildCards #-} module GHC.CmmToAsm.Dwarf.Types ( -- * Dwarf information DwarfInfo(..) , pprDwarfInfo , pprAbbrevDecls + , dwarfInfoStrings + -- * Dwarf Strings section + , DwarfString + , dwarfStringsSection + , dwarfStringFromString + , dwarfStringFromFastString -- * Dwarf address range table , DwarfARange(..) , pprDwarfARanges @@ -32,18 +39,14 @@ import GHC.Prelude import GHC.Cmm.DebugBlock import GHC.Cmm.CLabel import GHC.Cmm.Expr ( GlobalReg(..) ) -import GHC.Utils.Encoding import GHC.Data.FastString import GHC.Utils.Outputable import GHC.Platform import GHC.Types.Unique import GHC.Platform.Reg -import GHC.Types.SrcLoc -import GHC.Utils.Misc import GHC.CmmToAsm.Dwarf.Constants -import qualified Data.ByteString as BS import qualified Control.Monad.Trans.State.Strict as S import Control.Monad (zipWithM, join) import Data.Bits @@ -53,18 +56,46 @@ import Data.Char import GHC.Platform.Regs +-- | A string in the DWARF @.debug_str@ section. +newtype DwarfString = DwarfString FastString + +dwarfStringFromString :: String -> DwarfString +dwarfStringFromString = dwarfStringFromFastString . fsLit + +dwarfStringFromFastString :: FastString -> DwarfString +dwarfStringFromFastString = DwarfString + +dwarfStringSymbol :: DwarfString -> SDoc +dwarfStringSymbol (DwarfString fs) = + text "_dbgfs_" <> ppr (getUnique fs) + +debugStrSection :: SDoc +debugStrSection = text ".debug_str" + +pprDwarfString :: Platform -> DwarfString -> SDoc +pprDwarfString plat s = + sectionOffset plat (dwarfStringSymbol s) debugStrSection + +dwarfStringsSection :: [DwarfString] -> SDoc +dwarfStringsSection xs = + text ".section" <+> debugStrSection $$ hcat (map string xs) + where + string :: DwarfString -> SDoc + string dstr@(DwarfString fstr) = + dwarfStringSymbol dstr <> colon $$ pprFastString fstr + -- | Individual dwarf records. Each one will be encoded as an entry in -- the @.debug_info@ section. data DwarfInfo = DwarfCompileUnit { dwChildren :: [DwarfInfo] - , dwName :: String - , dwProducer :: String - , dwCompDir :: String + , dwName :: DwarfString + , dwProducer :: DwarfString + , dwCompDir :: DwarfString , dwLowLabel :: CLabel , dwHighLabel :: CLabel , dwLineLabel :: PtrString } | DwarfSubprogram { dwChildren :: [DwarfInfo] - , dwName :: String + , dwName :: DwarfString , dwLabel :: CLabel , dwParent :: Maybe CLabel -- ^ label of DIE belonging to the parent tick @@ -73,9 +104,23 @@ data DwarfInfo , dwLabel :: CLabel , dwMarker :: Maybe CLabel } - | DwarfSrcNote { dwSrcSpan :: RealSrcSpan + | DwarfSrcNote { dwSpanFile :: !DwarfString + , dwSpanStartLine :: !Int + , dwSpanStartCol :: !Int + , dwSpanEndLine :: !Int + , dwSpanEndCol :: !Int } +-- | 'DwarfStrings' mentioned by the given 'DwarfInfo'. +dwarfInfoStrings :: DwarfInfo -> [DwarfString] +dwarfInfoStrings dwinfo = + case dwinfo of + DwarfCompileUnit {..} -> [dwName, dwProducer, dwCompDir] ++ foldMap dwarfInfoStrings dwChildren + DwarfSubprogram {..} -> [dwName] ++ foldMap dwarfInfoStrings dwChildren + DwarfBlock {..} -> foldMap dwarfInfoStrings dwChildren + DwarfSrcNote {..} -> [dwSpanFile] + + -- | Abbreviation codes used for encoding above records in the -- @.debug_info@ section. data DwarfAbbrev @@ -138,7 +183,7 @@ pprAbbrevDecls platform haveDebugLine = , (dW_AT_high_pc, dW_FORM_addr) ] $$ mkAbbrev DwAbbrGhcSrcNote dW_TAG_ghc_src_note dW_CHILDREN_no - [ (dW_AT_ghc_span_file, dW_FORM_string) + [ (dW_AT_ghc_span_file, dW_FORM_strp) , (dW_AT_ghc_span_start_line, dW_FORM_data4) , (dW_AT_ghc_span_start_col, dW_FORM_data2) , (dW_AT_ghc_span_end_line, dW_FORM_data4) @@ -174,10 +219,10 @@ pprDwarfInfoOpen :: Platform -> Bool -> DwarfInfo -> SDoc pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowLabel highLabel lineLbl) = pprAbbrev DwAbbrCompileUnit - $$ pprString name - $$ pprString producer + $$ pprDwarfString platform name + $$ pprDwarfString platform producer $$ pprData4 dW_LANG_Haskell - $$ pprString compDir + $$ pprDwarfString platform compDir $$ pprWord platform (pdoc platform lowLabel) $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc @@ -186,7 +231,7 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = pdoc platform (mkAsmTempDieLabel label) <> colon $$ pprAbbrev abbrev - $$ pprString name + $$ pprDwarfString platform name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) @@ -209,13 +254,13 @@ pprDwarfInfoOpen platform _ (DwarfBlock _ label (Just marker)) = $$ pprLabelString platform label $$ pprWord platform (pdoc platform marker) $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel marker) -pprDwarfInfoOpen _ _ (DwarfSrcNote ss) = +pprDwarfInfoOpen platform _ (DwarfSrcNote {..}) = pprAbbrev DwAbbrGhcSrcNote - $$ pprString' (ftext $ srcSpanFile ss) - $$ pprData4 (fromIntegral $ srcSpanStartLine ss) - $$ pprHalf (fromIntegral $ srcSpanStartCol ss) - $$ pprData4 (fromIntegral $ srcSpanEndLine ss) - $$ pprHalf (fromIntegral $ srcSpanEndCol ss) + $$ pprDwarfString platform dwSpanFile + $$ pprData4 (fromIntegral dwSpanStartLine) + $$ pprHalf (fromIntegral dwSpanStartCol) + $$ pprData4 (fromIntegral dwSpanEndLine) + $$ pprHalf (fromIntegral dwSpanEndCol) -- | Close a DWARF info record with children pprDwarfInfoClose :: SDoc @@ -584,12 +629,8 @@ pprString' :: SDoc -> SDoc pprString' str = text "\t.asciz \"" <> str <> char '"' -- | Generate a string constant. We take care to escape the string. -pprString :: String -> SDoc -pprString str - = pprString' $ hcat $ map escapeChar $ - if str `lengthIs` utf8EncodedLength str - then str - else map (chr . fromIntegral) $ BS.unpack $ bytesFS $ mkFastString str +pprFastString :: FastString -> SDoc +pprFastString = pprString' . hcat . map escapeChar . unpackFS -- | Escape a single non-unicode character escapeChar :: Char -> SDoc View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ebf4de37f4bd55a592f7477c1d76263ec0c26399 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ebf4de37f4bd55a592f7477c1d76263ec0c26399 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 Sun Nov 1 02:15:35 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 22:15:35 -0400 Subject: [Git][ghc/ghc][wip/bump-time] 29 commits: Fix `instance Bounded a => Bounded (Down a)` (#18716) Message-ID: <5f9e1a4756ef5_7855a4e534196398@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - 6fe6d014 by Ben Gamari at 2020-10-31T22:15:07-04:00 Bump time submodule to 1.11 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/WorkWrap.hs - − compiler/GHC/Core/PatSyn.hs-boot The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/19897f63e22f01fa7781ce862addf2225b08dc42...6fe6d014faa71dea36a38bf366ef2e8402e3bd0d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/19897f63e22f01fa7781ce862addf2225b08dc42...6fe6d014faa71dea36a38bf366ef2e8402e3bd0d 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 Sun Nov 1 02:31:41 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 31 Oct 2020 22:31:41 -0400 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] 2 commits: Fix typos in 8.10.2 changelog Message-ID: <5f9e1e0d6cd66_785f6c23841977a9@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 929e09ed by toonn at 2020-10-22T22:12:43-04:00 Fix typos in 8.10.2 changelog Replace an "as well" missing "as" with "and" in 4.1 Highlights. Add missing apostrophe in "user's guide", insert space in "work around" and dash in "cost-center" in 4.2.2 Runtime system. - - - - - cc085aef by Ben Gamari at 2020-10-31T22:31:33-04:00 Bump Cabal submodule to 3.2.1.0 - - - - - 16 changed files: - docs/users_guide/8.10.2-notes.rst - libraries/Cabal - libraries/ghc-prim/ghc-prim.cabal - testsuite/tests/backpack/cabal/T16219/backpack-issue.cabal - testsuite/tests/backpack/cabal/bkpcabal01/bkpcabal01.cabal - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.cabal - testsuite/tests/backpack/cabal/bkpcabal03/asig1/asig1.cabal - testsuite/tests/backpack/cabal/bkpcabal03/asig2/asig2.cabal - testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in1 - testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in2 - testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in1 - testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in2 - testsuite/tests/backpack/cabal/bkpcabal05/bkpcabal05.cabal - testsuite/tests/backpack/cabal/bkpcabal06/bkpcabal06.cabal - testsuite/tests/backpack/cabal/bkpcabal07/bkpcabal07.cabal - testsuite/tests/cabal/cabal01/test.cabal Changes: ===================================== docs/users_guide/8.10.2-notes.rst ===================================== @@ -22,7 +22,7 @@ Highlights (:ghc-ticket:`18033`). - Fixes a few specialiser regressions (:ghc-ticket:`17810`, - :ghc-ticket:`18120`) as well introduces a variety of miscellaneous + :ghc-ticket:`18120`) and introduces a variety of miscellaneous specialiser improvements (:ghc-ticket:`16473`, :ghc-ticket:`17930`, :ghc-ticket:`17966`) @@ -48,7 +48,7 @@ Runtime system effect of :rts-flag:`--nonmoving-gc`. - The RTS now allows the user to specify a minimum time between idle GCs with - the :rts-flag:`-Iw ⟨seconds⟩` flag. 8.10.1 contained a users guide reference + the :rts-flag:`-Iw ⟨seconds⟩` flag. 8.10.1 contained a user's guide reference to this flag but did not include the associated implementation. - A memory leak in the cost-center profiler has been fixed @@ -57,10 +57,10 @@ Runtime system - A potential integer overflow in the compact normal form import logic has been fixed (:ghc-ticket:`16992`) - - We now workaround a Linux kernel bug in the implementation of timerfd which + - We now work around a Linux kernel bug in the implementation of timerfd which could previously result in program crashes (:ghc-ticket:`18033`) - - The cost center profiler's JSON output backend now escapes backslashes + - The cost-center profiler's JSON output backend now escapes backslashes correctly (:ghc-ticket:`18438`) - A variety of linker issues on ARM platforms have been fixed. ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit df65caf90ff79894dacecf73a642452aaabcc0a5 +Subproject commit 48bf10787e27364730dd37a42b603cee8d6af7ee ===================================== libraries/ghc-prim/ghc-prim.cabal ===================================== @@ -1,4 +1,4 @@ -cabal-version: 2.1 +cabal-version: 2.2 name: ghc-prim version: 0.6.1 -- NOTE: Don't forget to update ./changelog.md ===================================== testsuite/tests/backpack/cabal/T16219/backpack-issue.cabal ===================================== @@ -1,8 +1,9 @@ +cabal-version: 2.2 name: backpack-issue version: 0.1.0.0 -- synopsis: -- description: -license: BSD3 +license: BSD-3-Clause license-file: LICENSE author: Isaac Elliott maintainer: isaace71295 at gmail.com @@ -10,7 +11,6 @@ maintainer: isaace71295 at gmail.com -- category: build-type: Simple extra-source-files: CHANGELOG.md -cabal-version: >=2 library library-a signatures: A.Sig ===================================== testsuite/tests/backpack/cabal/bkpcabal01/bkpcabal01.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal01 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library impl exposed-modules: H, I ===================================== testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal01 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library p signatures: H ===================================== testsuite/tests/backpack/cabal/bkpcabal03/asig1/asig1.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: asig1 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: base ===================================== testsuite/tests/backpack/cabal/bkpcabal03/asig2/asig2.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: asig2 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: base ===================================== testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in1 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal03 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: asig1, base ===================================== testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in2 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal03 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: asig1, asig2, base ===================================== testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in1 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal04 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library p signatures: A ===================================== testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in2 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal04 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library p signatures: A ===================================== testsuite/tests/backpack/cabal/bkpcabal05/bkpcabal05.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal05 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library signatures: A ===================================== testsuite/tests/backpack/cabal/bkpcabal06/bkpcabal06.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal06 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: 2.0 library sig signatures: P ===================================== testsuite/tests/backpack/cabal/bkpcabal07/bkpcabal07.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal06 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=2.0 library indef signatures: P ===================================== testsuite/tests/cabal/cabal01/test.cabal ===================================== @@ -1,3 +1,4 @@ +Cabal-Version: 2.2 Name: test Version: 1.0 Exposed-Modules: A View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ddea40611cf3fb7d6ec50c817e6ddd209427428b...cc085aefd9d72da6aff5c5305a6b864398f95ec3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ddea40611cf3fb7d6ec50c817e6ddd209427428b...cc085aefd9d72da6aff5c5305a6b864398f95ec3 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 Sun Nov 1 05:10:37 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 01:10:37 -0400 Subject: [Git][ghc/ghc][master] testsuite: Add performance test for #18698 Message-ID: <5f9e434db0e11_785eaa2bf820659b@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - 2 changed files: - + testsuite/tests/perf/compiler/T18698/T18698.hs - + testsuite/tests/perf/compiler/T18698/all.T Changes: ===================================== testsuite/tests/perf/compiler/T18698/T18698.hs ===================================== @@ -0,0 +1,85 @@ +{-# LANGUAGE StrictData #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ScopedTypeVariables #-} + +module Blowup (Ps(..)) where + +import Data.Coerce +import Data.Semigroup (Semigroup(..), Last(..)) + +-- N.B. This was original Data.Semigroup.Option, which was deprecated +newtype Option a = Option (Maybe a) + +instance Semigroup a => Semigroup (Option a) where + (<>) = coerce ((<>) :: Maybe a -> Maybe a -> Maybe a) + stimes _ (Option Nothing) = Option Nothing + stimes n (Option (Just a)) = case compare n 0 of + LT -> error "stimes: Option, negative multiplier" + EQ -> Option Nothing + GT -> Option (Just (stimes n a)) + +-- | @since 4.9.0.0 +instance Semigroup a => Monoid (Option a) where + mempty = Option Nothing + +data Ps = Ps + { _p1 :: Maybe Double + , _p2 :: Maybe Double + , _p3 :: Maybe Double + , _p4 :: Maybe Double + , _p5 :: Maybe Double + , _p6 :: Maybe Double + , _p7 :: Maybe Double + , _p8 :: Maybe Double + , _p9 :: Maybe Double + , _p10 :: Maybe Double + , _p11 :: Maybe Double + , _p12 :: Maybe Double + , _p13 :: Maybe Double + , _p14 :: Maybe Double + , _p15 :: Maybe Double + , _p16 :: Maybe Double + , _p17 :: Maybe Double + , _p18 :: Maybe Double + , _p19 :: Maybe Double + , _p20 :: Maybe Double + , _pa :: Maybe (String, String) + } + +instance Semigroup Ps where + (<>) (Ps p_1 p_2 p_3 p_4 p_5 p_6 p_7 p_8 p_9 + p_10 p_11 p_12 p_13 p_14 p_15 p_16 p_17 p_18 p_19 p_20 + pa) + (Ps p_1' p_2' p_3' p_4' p_5' p_6' p_7' p_8' p_9' + p_10' p_11' p_12' p_13' p_14' p_15' p_16' p_17' p_18' p_19' p_20' + pa') + = Ps (f p_1 p_1') + (f p_2 p_2') + (f p_3 p_3') + (f p_4 p_4') + (f p_5 p_5') + (f p_6 p_6') + (f p_7 p_7') + (f p_8 p_8') + (f p_9 p_9') + (f p_10 p_10') + (f p_11 p_11') + (f p_12 p_12') + (f p_13 p_13') + (f p_14 p_14') + (f p_15 p_15') + (f p_16 p_16') + (f p_17 p_17') + (f p_18 p_18') + (f p_19 p_19') + (f p_20 p_20') + (f pa pa') + + where + f :: forall a. Maybe a -> Maybe a -> Maybe a +#if defined(COERCE) + f = coerce ((<>) :: Option (Last a) -> Option (Last a) -> Option (Last a)) +#else + f _ y@(Just _) = y + f x _ = x +#endif ===================================== testsuite/tests/perf/compiler/T18698/all.T ===================================== @@ -0,0 +1,15 @@ +test('T18698a', + [collect_compiler_residency(15), + collect_compiler_stats('bytes allocated', 1), + extra_files(['T18698.hs']) + ], + multimod_compile, + ['T18698', '-O2 -v0']) + +test('T18698b', + [collect_compiler_residency(15), + collect_compiler_stats('bytes allocated', 1), + extra_files(['T18698.hs']) + ], + multimod_compile, + ['T18698', '-O2 -v0 -DCOERCE']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd4abdc953427e084e7ecba89db64860f6859822 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd4abdc953427e084e7ecba89db64860f6859822 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 Sun Nov 1 05:11:20 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 01:11:20 -0400 Subject: [Git][ghc/ghc][master] Add the proper HLint rules and remove redundant keywords from compiler Message-ID: <5f9e4378bab01_785f19c634209623@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Driver/Backpack.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dfd27445308d1ed2df8826c2a045130e918e8192 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dfd27445308d1ed2df8826c2a045130e918e8192 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 Sun Nov 1 05:42:06 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 01:42:06 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: testsuite: Add performance test for #18698 Message-ID: <5f9e4aae70362_785104f7af82153be@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - a0876ae1 by Hécate at 2020-11-01T01:41:59-04:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - 2af9fb1b by Ben Gamari at 2020-11-01T01:42:00-04:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Driver/Backpack.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe686293c201f0b214a9dc8a94534d08fdbbdcf5...2af9fb1b5b7054302c7883b9d98e03e006cf7089 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe686293c201f0b214a9dc8a94534d08fdbbdcf5...2af9fb1b5b7054302c7883b9d98e03e006cf7089 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 Sun Nov 1 07:30:49 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Sun, 01 Nov 2020 02:30:49 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-ncg] 5 commits: [CmmSized Int] move Int32# section. Message-ID: <5f9e6429d681b_7853fb6404840f02240f8@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC Commits: beba3454 by Moritz Angermann at 2020-10-28T15:25:02+08:00 [CmmSized Int] move Int32# section. - - - - - 8aef9557 by Moritz Angermann at 2020-10-28T15:58:35+08:00 [CmmSized Word] W8/W16/W32 - - - - - 88764dd4 by Moritz Angermann at 2020-10-28T17:16:33+08:00 [CmmSize Word] pt 2 - - - - - dade52f5 by Moritz Angermann at 2020-11-01T15:09:55+08:00 [CmmSize Wor] pt 3 - - - - - 80115ada by Moritz Angermann at 2020-11-01T15:30:18+08:00 [CmmSized] bump submoudles - - - - - 28 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/HsToCore/PmCheck/Oracle.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring - libraries/ghc-bignum/ghc-bignum.cabal - libraries/ghc-compact/ghc-compact.cabal - libraries/ghc-heap/ghc-heap.cabal.in - libraries/ghc-prim/ghc-prim.cabal - libraries/ghci/GHCi/BreakArray.hs - libraries/ghci/ghci.cabal.in - libraries/text Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -336,7 +336,7 @@ basicKnownKeyNames -- FFI primitive types that are not wired-in. stablePtrTyConName, ptrTyConName, funPtrTyConName, int8TyConName, int16TyConName, int32TyConName, int64TyConName, - word16TyConName, word32TyConName, word64TyConName, + word8TyConName, word16TyConName, word32TyConName, word64TyConName, -- Others otherwiseIdName, inlineIdName, @@ -1468,7 +1468,8 @@ int32TyConName = tcQual gHC_INT (fsLit "Int32") int32TyConKey int64TyConName = tcQual gHC_INT (fsLit "Int64") int64TyConKey -- Word module -word16TyConName, word32TyConName, word64TyConName :: Name +word8TyConName, word16TyConName, word32TyConName, word64TyConName :: Name +word8TyConName = tcQual gHC_WORD (fsLit "Word8") word8TyConKey word16TyConName = tcQual gHC_WORD (fsLit "Word16") word16TyConKey word32TyConName = tcQual gHC_WORD (fsLit "Word32") word32TyConKey word64TyConName = tcQual gHC_WORD (fsLit "Word64") word64TyConKey ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -54,9 +54,6 @@ module GHC.Builtin.Types ( -- * Word wordTyCon, wordDataCon, wordTyConName, wordTy, - -- * Word8 - word8TyCon, word8DataCon, word8TyConName, word8Ty, - -- * List listTyCon, listTyCon_RDR, listTyConName, listTyConKey, nilDataCon, nilDataConName, nilDataConKey, @@ -248,7 +245,6 @@ wiredInTyCons = [ -- Units are not treated like other tuples, because they , floatTyCon , intTyCon , wordTyCon - , word8TyCon , listTyCon , orderingTyCon , maybeTyCon @@ -352,11 +348,9 @@ nothingDataConName = mkWiredInDataConName UserSyntax gHC_MAYBE (fsLit "Nothing") justDataConName = mkWiredInDataConName UserSyntax gHC_MAYBE (fsLit "Just") justDataConKey justDataCon -wordTyConName, wordDataConName, word8TyConName, word8DataConName :: Name +wordTyConName, wordDataConName :: Name wordTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "Word") wordTyConKey wordTyCon wordDataConName = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "W#") wordDataConKey wordDataCon -word8TyConName = mkWiredInTyConName UserSyntax gHC_WORD (fsLit "Word8") word8TyConKey word8TyCon -word8DataConName = mkWiredInDataConName UserSyntax gHC_WORD (fsLit "W8#") word8DataConKey word8DataCon floatTyConName, floatDataConName, doubleTyConName, doubleDataConName :: Name floatTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "Float") floatTyConKey floatTyCon @@ -1543,17 +1537,6 @@ wordTyCon = pcTyCon wordTyConName wordDataCon :: DataCon wordDataCon = pcDataCon wordDataConName [] [wordPrimTy] wordTyCon -word8Ty :: Type -word8Ty = mkTyConTy word8TyCon - -word8TyCon :: TyCon -word8TyCon = pcTyCon word8TyConName - (Just (CType NoSourceText Nothing - (NoSourceText, fsLit "HsWord8"))) [] - [word8DataCon] -word8DataCon :: DataCon -word8DataCon = pcDataCon word8DataConName [] [wordPrimTy] word8TyCon - floatTy :: Type floatTy = mkTyConTy floatTyCon ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -332,8 +332,8 @@ section "Word8#" primtype Word8# -primop Word8Extend "extendWord8#" GenPrimOp Word8# -> Word# -primop Word8Narrow "narrowWord8#" GenPrimOp Word# -> Word8# +primop Word8ExtendOp "extendWord8#" GenPrimOp Word8# -> Word# +primop Word8NarrowOp "narrowWord8#" GenPrimOp Word# -> Word8# primop Word8NotOp "notWord8#" GenPrimOp Word8# -> Word8# @@ -407,16 +407,6 @@ primop Int16LeOp "leInt16#" Compare Int16# -> Int16# -> Int# primop Int16LtOp "ltInt16#" Compare Int16# -> Int16# -> Int# primop Int16NeOp "neInt16#" Compare Int16# -> Int16# -> Int# ------------------------------------------------------------------------- -section "Int32#" - {Operations on 32-bit integers.} ------------------------------------------------------------------------- - -primtype Int32# - -primop Int32ExtendOp "extendInt32#" GenPrimOp Int32# -> Int# -primop Int32NarrowOp "narrowInt32#" GenPrimOp Int# -> Int32# - ------------------------------------------------------------------------ section "Word16#" {Operations on 16-bit unsigned integers.} @@ -424,8 +414,8 @@ section "Word16#" primtype Word16# -primop Word16Extend "extendWord16#" GenPrimOp Word16# -> Word# -primop Word16Narrow "narrowWord16#" GenPrimOp Word# -> Word16# +primop Word16ExtendOp "extendWord16#" GenPrimOp Word16# -> Word# +primop Word16NarrowOp "narrowWord16#" GenPrimOp Word# -> Word16# primop Word16NotOp "notWord16#" GenPrimOp Word16# -> Word16# @@ -458,6 +448,26 @@ primop Word16LeOp "leWord16#" Compare Word16# -> Word16# -> Int# primop Word16LtOp "ltWord16#" Compare Word16# -> Word16# -> Int# primop Word16NeOp "neWord16#" Compare Word16# -> Word16# -> Int# +------------------------------------------------------------------------ +section "Int32#" + {Operations on 32-bit integers.} +------------------------------------------------------------------------ + +primtype Int32# + +primop Int32ExtendOp "extendInt32#" GenPrimOp Int32# -> Int# +primop Int32NarrowOp "narrowInt32#" GenPrimOp Int# -> Int32# + +------------------------------------------------------------------------ +section "Word32#" + {Operations on 32-bit unsigned integers.} +------------------------------------------------------------------------ + +primtype Word32# + +primop Word32ExtendOp "extendWord32#" GenPrimOp Word32# -> Word# +primop Word32NarrowOp "narrowWord32#" GenPrimOp Word# -> Word32# + #if WORD_SIZE_IN_BITS < 64 ------------------------------------------------------------------------ section "Int64#" ===================================== compiler/GHC/CmmToAsm/Ppr.hs ===================================== @@ -1,4 +1,4 @@ -{-# LANGUAGE MagicHash #-} +{-# LANGUAGE CPP, MagicHash #-} ----------------------------------------------------------------------------- -- @@ -38,9 +38,17 @@ import Data.Word import Data.Bits import Data.ByteString (ByteString) import qualified Data.ByteString as BS -import GHC.Exts +import GHC.Exts hiding (extendWord8#) import GHC.Word +#if MIN_VERSION_ghc_prim(0,8,0) +import GHC.Base (extendWord8#) +#else +import GHC.Prim (Word#) +extendWord8# :: Word# -> Word# +extendWord8# w = w +#endif + -- ----------------------------------------------------------------------------- -- Converting floating-point literals to integrals for printing @@ -103,7 +111,7 @@ pprASCII str -- we know that the Chars we create are in the ASCII range -- so we bypass the check in "chr" chr' :: Word8 -> Char - chr' (W8# w#) = C# (chr# (word2Int# w#)) + chr' (W8# w#) = C# (chr# (word2Int# (extendWord8# w#))) octal :: Word8 -> String octal w = [ chr' (ord0 + (w `unsafeShiftR` 6) .&. 0x07) ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -214,10 +214,10 @@ primOpRules nm = \case , narrowSubsumesAnd AndIOp Int32NarrowOp 32 ] -- Int64NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndIOp Int64NarrowOp 64 ] - -- Word8Narrow -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word8Narrow 8 ] - -- Word16Narrow -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word16Narrow 16 ] - -- Word32Narrow -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word32Narrow 32 ] - -- Word64Narrow -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word64Narrow 64 ] + -- Word8NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word8NarrowOp 8 ] + -- Word16NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word16NarrowOp 16 ] + -- Word32NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word32NarrowOp 32 ] + -- Word64NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word64NarrowOp 64 ] WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform wordToIntLit , inversePrimOp IntToWordOp ] ===================================== compiler/GHC/HsToCore/PmCheck/Oracle.hs ===================================== @@ -1235,7 +1235,7 @@ inhabitationCandidates MkDelta{ delta_ty_st = ty_st } ty = do -- | All these types are trivially inhabited triviallyInhabitedTyCons :: UniqSet TyCon triviallyInhabitedTyCons = mkUniqSet [ - charTyCon, doubleTyCon, floatTyCon, intTyCon, wordTyCon, word8TyCon + charTyCon, doubleTyCon, floatTyCon, intTyCon, wordTyCon ] isTyConTriviallyInhabited :: TyCon -> Bool ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -2750,13 +2750,14 @@ repTyVarSig (MkC bndr) = rep2 tyVarSigName [bndr] -- Literals repLiteral :: HsLit GhcRn -> MetaM (Core TH.Lit) -repLiteral (HsStringPrim _ bs) - = do platform <- getPlatform - word8_ty <- lookupType word8TyConName - let w8s = unpack bs - w8s_expr = map (\w8 -> mkCoreConApps word8DataCon - [mkWordLit platform (toInteger w8)]) w8s - rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr] +-- XXX this needs fixing. +-- repLiteral (HsStringPrim _ bs) +-- = do platform <- getPlatform +-- word8_ty <- lookupType word8TyConName +-- let w8s = unpack bs +-- w8s_expr = map (\w8 -> mkCoreConApps word8DataCon +-- [mkWordLit platform (toInteger w8)]) w8s +-- rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr] repLiteral lit = do lit' <- case lit of HsIntPrim _ i -> mk_integer i ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1190,8 +1190,8 @@ emitPrimOp dflags primop = case primop of -- Word8# unsigned ops - Word8Extend -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - Word8Narrow -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) + Word8ExtendOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) + Word8NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) Word8NotOp -> \args -> opTranslate args (MO_Not W8) Word8AddOp -> \args -> opTranslate args (MO_Add W8) Word8SubOp -> \args -> opTranslate args (MO_Sub W8) @@ -1224,15 +1224,10 @@ emitPrimOp dflags primop = case primop of Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) Int16NeOp -> \args -> opTranslate args (MO_Ne W16) --- Int32# signed ops - - Int32ExtendOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - Int32NarrowOp -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) - -- Word16# unsigned ops - Word16Extend -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - Word16Narrow -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) + Word16ExtendOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) + Word16NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) Word16NotOp -> \args -> opTranslate args (MO_Not W16) Word16AddOp -> \args -> opTranslate args (MO_Add W16) Word16SubOp -> \args -> opTranslate args (MO_Sub W16) @@ -1247,6 +1242,16 @@ emitPrimOp dflags primop = case primop of Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) Word16NeOp -> \args -> opTranslate args (MO_Ne W16) +-- Int32# signed ops + + Int32ExtendOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) + Int32NarrowOp -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) + +-- Word32# unsigned ops + + Word32ExtendOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) + Word32NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) + -- Char# ops CharEqOp -> \args -> opTranslate args (MO_Eq (wordWidth platform)) ===================================== compiler/ghc.cabal.in ===================================== @@ -58,6 +58,7 @@ Library Exposed: False Build-Depends: base >= 4.11 && < 4.16, + ghc-prim >= 0.5.0 && < 0.9, deepseq >= 1.4 && < 1.5, directory >= 1 && < 1.4, process >= 1 && < 1.7, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -59,7 +59,7 @@ Executable ghc -- NB: this is never built by the bootstrapping GHC+libraries Build-depends: deepseq == 1.4.*, - ghc-prim >= 0.5.0 && < 0.8, + ghc-prim >= 0.5.0 && < 0.9, ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, ===================================== libraries/array ===================================== @@ -1 +1 @@ -Subproject commit eac14efeb5883ab18195b2eb6167f19853b59e88 +Subproject commit 2cb74575a736fc8a8cf01ac7ce3664343559ac86 ===================================== libraries/base/GHC/Float.hs ===================================== @@ -1394,7 +1394,7 @@ castWord32ToFloat :: Word32 -> Float castWord32ToFloat (W32# w#) = F# (stgWord32ToFloat w#) foreign import prim "stg_word32ToFloatzh" - stgWord32ToFloat :: Word# -> Float# + stgWord32ToFloat :: Word32# -> Float# -- | @'castFloatToWord32' f@ does a bit-for-bit copy from a floating-point value @@ -1407,7 +1407,7 @@ castFloatToWord32 :: Float -> Word32 castFloatToWord32 (F# f#) = W32# (stgFloatToWord32 f#) foreign import prim "stg_floatToWord32zh" - stgFloatToWord32 :: Float# -> Word# + stgFloatToWord32 :: Float# -> Word32# ===================================== libraries/base/GHC/IO/Encoding/UTF16.hs ===================================== @@ -342,8 +342,8 @@ utf16le_encode chr2 :: Word16 -> Word16 -> Char chr2 (W16# a#) (W16# b#) = C# (chr# (upper# +# lower# +# 0x10000#)) where - !x# = word2Int# a# - !y# = word2Int# b# + !x# = word2Int# (extendWord16# a#) + !y# = word2Int# (extendWord16# b#) !upper# = uncheckedIShiftL# (x# -# 0xD800#) 10# !lower# = y# -# 0xDC00# {-# INLINE chr2 #-} @@ -356,4 +356,3 @@ validate2 :: Word16 -> Word16 -> Bool validate2 x1 x2 = x1 >= 0xD800 && x1 <= 0xDBFF && x2 >= 0xDC00 && x2 <= 0xDFFF {-# INLINE validate2 #-} - ===================================== libraries/base/GHC/IO/Encoding/UTF32.hs ===================================== @@ -309,10 +309,10 @@ chr4 :: Word8 -> Word8 -> Word8 -> Word8 -> Char chr4 (W8# x1#) (W8# x2#) (W8# x3#) (W8# x4#) = C# (chr# (z1# +# z2# +# z3# +# z4#)) where - !y1# = word2Int# x1# - !y2# = word2Int# x2# - !y3# = word2Int# x3# - !y4# = word2Int# x4# + !y1# = word2Int# (extendWord8# x1#) + !y2# = word2Int# (extendWord8# x2#) + !y3# = word2Int# (extendWord8# x3#) + !y4# = word2Int# (extendWord8# x4#) !z1# = uncheckedIShiftL# y1# 24# !z2# = uncheckedIShiftL# y2# 16# !z3# = uncheckedIShiftL# y3# 8# @@ -333,4 +333,3 @@ validate :: Char -> Bool validate c = (x1 >= 0x0 && x1 < 0xD800) || (x1 > 0xDFFF && x1 <= 0x10FFFF) where x1 = ord c {-# INLINE validate #-} - ===================================== libraries/base/GHC/IO/Encoding/UTF8.hs ===================================== @@ -11,7 +11,7 @@ -- Module : GHC.IO.Encoding.UTF8 -- Copyright : (c) The University of Glasgow, 2009 -- License : see libraries/base/LICENSE --- +-- -- Maintainer : libraries at haskell.org -- Stability : internal -- Portability : non-portable @@ -144,17 +144,17 @@ bom1 = 0xbb bom2 = 0xbf utf8_decode :: DecodeBuffer -utf8_decode +utf8_decode input at Buffer{ bufRaw=iraw, bufL=ir0, bufR=iw, bufSize=_ } output at Buffer{ bufRaw=oraw, bufL=_, bufR=ow0, bufSize=os } - = let + = let loop !ir !ow | ow >= os = done OutputUnderflow ir ow | ir >= iw = done InputUnderflow ir ow | otherwise = do c0 <- readWord8Buf iraw ir case c0 of - _ | c0 <= 0x7f -> do + _ | c0 <= 0x7f -> do ow' <- writeCharBuf oraw ow (unsafeChr (fromIntegral c0)) loop (ir+1) ow' | c0 >= 0xc0 && c0 <= 0xc1 -> invalid -- Overlong forms @@ -170,7 +170,7 @@ utf8_decode 2 -> do -- check for an error even when we don't have -- the full sequence yet (#3341) c1 <- readWord8Buf iraw (ir+1) - if not (validate3 c0 c1 0x80) + if not (validate3 c0 c1 0x80) then invalid else done InputUnderflow ir ow _ -> do c1 <- readWord8Buf iraw (ir+1) @@ -215,7 +215,7 @@ utf8_encode :: EncodeBuffer utf8_encode input at Buffer{ bufRaw=iraw, bufL=ir0, bufR=iw, bufSize=_ } output at Buffer{ bufRaw=oraw, bufL=_, bufR=ow0, bufSize=os } - = let + = let done why !ir !ow = return (why, if ir == iw then input{ bufL=0, bufR=0 } else input{ bufL=ir }, @@ -255,7 +255,7 @@ utf8_encode -- ----------------------------------------------------------------------------- -- UTF-8 primitives, lifted from Data.Text.Fusion.Utf8 - + ord2 :: Char -> (Word8,Word8) ord2 c = assert (n >= 0x80 && n <= 0x07ff) (x1,x2) where @@ -283,8 +283,8 @@ ord4 c = assert (n >= 0x10000) (x1,x2,x3,x4) chr2 :: Word8 -> Word8 -> Char chr2 (W8# x1#) (W8# x2#) = C# (chr# (z1# +# z2#)) where - !y1# = word2Int# x1# - !y2# = word2Int# x2# + !y1# = word2Int# (extendWord8# x1#) + !y2# = word2Int# (extendWord8# x2#) !z1# = uncheckedIShiftL# (y1# -# 0xC0#) 6# !z2# = y2# -# 0x80# {-# INLINE chr2 #-} @@ -292,9 +292,9 @@ chr2 (W8# x1#) (W8# x2#) = C# (chr# (z1# +# z2#)) chr3 :: Word8 -> Word8 -> Word8 -> Char chr3 (W8# x1#) (W8# x2#) (W8# x3#) = C# (chr# (z1# +# z2# +# z3#)) where - !y1# = word2Int# x1# - !y2# = word2Int# x2# - !y3# = word2Int# x3# + !y1# = word2Int# (extendWord8# x1#) + !y2# = word2Int# (extendWord8# x2#) + !y3# = word2Int# (extendWord8# x3#) !z1# = uncheckedIShiftL# (y1# -# 0xE0#) 12# !z2# = uncheckedIShiftL# (y2# -# 0x80#) 6# !z3# = y3# -# 0x80# @@ -304,10 +304,10 @@ chr4 :: Word8 -> Word8 -> Word8 -> Word8 -> Char chr4 (W8# x1#) (W8# x2#) (W8# x3#) (W8# x4#) = C# (chr# (z1# +# z2# +# z3# +# z4#)) where - !y1# = word2Int# x1# - !y2# = word2Int# x2# - !y3# = word2Int# x3# - !y4# = word2Int# x4# + !y1# = word2Int# (extendWord8# x1#) + !y2# = word2Int# (extendWord8# x2#) + !y3# = word2Int# (extendWord8# x3#) + !y4# = word2Int# (extendWord8# x4#) !z1# = uncheckedIShiftL# (y1# -# 0xF0#) 18# !z2# = uncheckedIShiftL# (y2# -# 0x80#) 12# !z3# = uncheckedIShiftL# (y3# -# 0x80#) 6# @@ -346,7 +346,7 @@ validate4 :: Word8 -> Word8 -> Word8 -> Word8 -> Bool validate4 x1 x2 x3 x4 = validate4_1 || validate4_2 || validate4_3 - where + where validate4_1 = x1 == 0xF0 && between x2 0x90 0xBF && between x3 0x80 0xBF && @@ -359,4 +359,3 @@ validate4 x1 x2 x3 x4 = validate4_1 || between x2 0x80 0x8F && between x3 0x80 0xBF && between x4 0x80 0xBF - ===================================== libraries/base/GHC/Int.hs ===================================== @@ -431,7 +431,7 @@ instance FiniteBits Int16 where countTrailingZeros (I16# x#) = I# (word2Int# (ctz16# (int2Word# (extendInt16# x#)))) {-# RULES -"fromIntegral/Word8->Int16" fromIntegral = \(W8# x#) -> I16# (narrowInt16# (word2Int# x#)) +"fromIntegral/Word8->Int16" fromIntegral = \(W8# x#) -> I16# (narrowInt16# (word2Int# (extendWord8# x#))) "fromIntegral/Int8->Int16" fromIntegral = \(I8# x#) -> I16# (narrowInt16# (extendInt8# x#)) "fromIntegral/Int16->Int16" fromIntegral = id :: Int16 -> Int16 "fromIntegral/a->Int16" fromIntegral = \x -> case fromIntegral x of I# x# -> I16# (narrowInt16# x#) @@ -641,8 +641,8 @@ instance FiniteBits Int32 where countTrailingZeros (I32# x#) = I# (word2Int# (ctz32# (int2Word# (extendInt32# x#)))) {-# RULES -"fromIntegral/Word8->Int32" fromIntegral = \(W8# x#) -> I32# (narrowInt32# (word2Int# x#)) -"fromIntegral/Word16->Int32" fromIntegral = \(W16# x#) -> I32# (narrowInt32# (word2Int# x#)) +"fromIntegral/Word8->Int32" fromIntegral = \(W8# x#) -> I32# (narrowInt32# (word2Int# (extendWord8# x#))) +"fromIntegral/Word16->Int32" fromIntegral = \(W16# x#) -> I32# (narrowInt32# (word2Int# (extendWord16# x#))) "fromIntegral/Int8->Int32" fromIntegral = \(I8# x#) -> I32# (narrowInt32# (extendInt8# x#)) "fromIntegral/Int16->Int32" fromIntegral = \(I16# x#) -> I32# (narrowInt32# (extendInt16# x#)) "fromIntegral/Int32->Int32" fromIntegral = id :: Int32 -> Int32 ===================================== libraries/base/GHC/Storable.hs ===================================== @@ -93,15 +93,15 @@ readStablePtrOffPtr (Ptr a) (I# i) readInt8OffPtr (Ptr a) (I# i) = IO $ \s -> case readInt8OffAddr# a i s of (# s2, x #) -> (# s2, I8# (narrowInt8# x) #) readWord8OffPtr (Ptr a) (I# i) - = IO $ \s -> case readWord8OffAddr# a i s of (# s2, x #) -> (# s2, W8# x #) + = IO $ \s -> case readWord8OffAddr# a i s of (# s2, x #) -> (# s2, W8# (narrowWord8# x) #) readInt16OffPtr (Ptr a) (I# i) = IO $ \s -> case readInt16OffAddr# a i s of (# s2, x #) -> (# s2, I16# (narrowInt16# x) #) readWord16OffPtr (Ptr a) (I# i) - = IO $ \s -> case readWord16OffAddr# a i s of (# s2, x #) -> (# s2, W16# x #) + = IO $ \s -> case readWord16OffAddr# a i s of (# s2, x #) -> (# s2, W16# (narrowWord16# x) #) readInt32OffPtr (Ptr a) (I# i) = IO $ \s -> case readInt32OffAddr# a i s of (# s2, x #) -> (# s2, I32# (narrowInt32# x) #) readWord32OffPtr (Ptr a) (I# i) - = IO $ \s -> case readWord32OffAddr# a i s of (# s2, x #) -> (# s2, W32# x #) + = IO $ \s -> case readWord32OffAddr# a i s of (# s2, x #) -> (# s2, W32# (narrowWord32# x) #) readInt64OffPtr (Ptr a) (I# i) = IO $ \s -> case readInt64OffAddr# a i s of (# s2, x #) -> (# s2, I64# x #) readWord64OffPtr (Ptr a) (I# i) @@ -143,15 +143,15 @@ writeStablePtrOffPtr (Ptr a) (I# i) (StablePtr x) writeInt8OffPtr (Ptr a) (I# i) (I8# x) = IO $ \s -> case writeInt8OffAddr# a i (extendInt8# x) s of s2 -> (# s2, () #) writeWord8OffPtr (Ptr a) (I# i) (W8# x) - = IO $ \s -> case writeWord8OffAddr# a i x s of s2 -> (# s2, () #) + = IO $ \s -> case writeWord8OffAddr# a i (extendWord8# x) s of s2 -> (# s2, () #) writeInt16OffPtr (Ptr a) (I# i) (I16# x) = IO $ \s -> case writeInt16OffAddr# a i (extendInt16# x) s of s2 -> (# s2, () #) writeWord16OffPtr (Ptr a) (I# i) (W16# x) - = IO $ \s -> case writeWord16OffAddr# a i x s of s2 -> (# s2, () #) + = IO $ \s -> case writeWord16OffAddr# a i (extendWord16# x) s of s2 -> (# s2, () #) writeInt32OffPtr (Ptr a) (I# i) (I32# x) = IO $ \s -> case writeInt32OffAddr# a i (extendInt32# x) s of s2 -> (# s2, () #) writeWord32OffPtr (Ptr a) (I# i) (W32# x) - = IO $ \s -> case writeWord32OffAddr# a i x s of s2 -> (# s2, () #) + = IO $ \s -> case writeWord32OffAddr# a i (extendWord32# x) s of s2 -> (# s2, () #) writeInt64OffPtr (Ptr a) (I# i) (I64# x) = IO $ \s -> case writeInt64OffAddr# a i x s of s2 -> (# s2, () #) writeWord64OffPtr (Ptr a) (I# i) (W64# x) ===================================== libraries/base/GHC/Word.hs ===================================== @@ -67,7 +67,10 @@ import GHC.Show -- Word8 is represented in the same way as Word. Operations may assume -- and must ensure that it holds only values from its logical range. -data {-# CTYPE "HsWord8" #-} Word8 = W8# Word# +data {-# CTYPE "HsWord8" #-} Word8 + = W8# Word8# + + -- ^ 8-bit unsigned integer type -- See GHC.Classes#matching_overloaded_methods_in_rules @@ -77,8 +80,8 @@ instance Eq Word8 where (/=) = neWord8 eqWord8, neWord8 :: Word8 -> Word8 -> Bool -eqWord8 (W8# x) (W8# y) = isTrue# (x `eqWord#` y) -neWord8 (W8# x) (W8# y) = isTrue# (x `neWord#` y) +eqWord8 (W8# x) (W8# y) = isTrue# ((extendWord8# x) `eqWord#` (extendWord8# y)) +neWord8 (W8# x) (W8# y) = isTrue# ((extendWord8# x) `neWord#` (extendWord8# y)) {-# INLINE [1] eqWord8 #-} {-# INLINE [1] neWord8 #-} @@ -94,10 +97,10 @@ instance Ord Word8 where {-# INLINE [1] ltWord8 #-} {-# INLINE [1] leWord8 #-} gtWord8, geWord8, ltWord8, leWord8 :: Word8 -> Word8 -> Bool -(W8# x) `gtWord8` (W8# y) = isTrue# (x `gtWord#` y) -(W8# x) `geWord8` (W8# y) = isTrue# (x `geWord#` y) -(W8# x) `ltWord8` (W8# y) = isTrue# (x `ltWord#` y) -(W8# x) `leWord8` (W8# y) = isTrue# (x `leWord#` y) +(W8# x) `gtWord8` (W8# y) = isTrue# ((extendWord8# x) `gtWord#` (extendWord8# y)) +(W8# x) `geWord8` (W8# y) = isTrue# ((extendWord8# x) `geWord#` (extendWord8# y)) +(W8# x) `ltWord8` (W8# y) = isTrue# ((extendWord8# x) `ltWord#` (extendWord8# y)) +(W8# x) `leWord8` (W8# y) = isTrue# ((extendWord8# x) `leWord#` (extendWord8# y)) -- | @since 2.01 instance Show Word8 where @@ -105,14 +108,14 @@ instance Show Word8 where -- | @since 2.01 instance Num Word8 where - (W8# x#) + (W8# y#) = W8# (narrow8Word# (x# `plusWord#` y#)) - (W8# x#) - (W8# y#) = W8# (narrow8Word# (x# `minusWord#` y#)) - (W8# x#) * (W8# y#) = W8# (narrow8Word# (x# `timesWord#` y#)) - negate (W8# x#) = W8# (narrow8Word# (int2Word# (negateInt# (word2Int# x#)))) + (W8# x#) + (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `plusWord#` (extendWord8# y#))) + (W8# x#) - (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `minusWord#` (extendWord8# y#))) + (W8# x#) * (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `timesWord#` (extendWord8# y#))) + negate (W8# x#) = W8# (narrowWord8# (int2Word# (negateInt# (word2Int# ((extendWord8# x#)))))) abs x = x signum 0 = 0 signum _ = 1 - fromInteger i = W8# (narrow8Word# (integerToWord# i)) + fromInteger i = W8# (narrowWord8# (integerToWord# i)) -- | @since 2.01 instance Real Word8 where @@ -128,35 +131,36 @@ instance Enum Word8 where | otherwise = predError "Word8" toEnum i@(I# i#) | i >= 0 && i <= fromIntegral (maxBound::Word8) - = W8# (int2Word# i#) + = W8# (narrowWord8# (int2Word# i#)) | otherwise = toEnumError "Word8" i (minBound::Word8, maxBound::Word8) - fromEnum (W8# x#) = I# (word2Int# x#) + fromEnum (W8# x#) = I# (word2Int# (extendWord8# x#)) enumFrom = boundedEnumFrom enumFromThen = boundedEnumFromThen -- | @since 2.01 instance Integral Word8 where quot (W8# x#) y@(W8# y#) - | y /= 0 = W8# (x# `quotWord#` y#) + | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `quotWord#` (extendWord8# y#))) | otherwise = divZeroError rem (W8# x#) y@(W8# y#) - | y /= 0 = W8# (x# `remWord#` y#) + | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `remWord#` (extendWord8# y#))) | otherwise = divZeroError div (W8# x#) y@(W8# y#) - | y /= 0 = W8# (x# `quotWord#` y#) + | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `quotWord#` (extendWord8# y#))) | otherwise = divZeroError mod (W8# x#) y@(W8# y#) - | y /= 0 = W8# (x# `remWord#` y#) + | y /= 0 = W8# (narrowWord8# ((extendWord8# x#) `remWord#` (extendWord8# y#))) | otherwise = divZeroError quotRem (W8# x#) y@(W8# y#) - | y /= 0 = case x# `quotRemWord#` y# of + | y /= 0 = case (extendWord8# x#) `quotRemWord#` (extendWord8# y#) of (# q, r #) -> - (W8# q, W8# r) + (W8# (narrowWord8# q), W8# (narrowWord8# r)) | otherwise = divZeroError divMod (W8# x#) y@(W8# y#) - | y /= 0 = (W8# (x# `quotWord#` y#), W8# (x# `remWord#` y#)) + | y /= 0 = (W8# (narrowWord8# ((extendWord8# x#) `quotWord#` (extendWord8# y#))) + ,W8# (narrowWord8# ((extendWord8# x#) `remWord#` (extendWord8# y#)))) | otherwise = divZeroError - toInteger (W8# x#) = IS (word2Int# x#) + toInteger (W8# x#) = IS (word2Int# (extendWord8# x#)) -- | @since 2.01 instance Bounded Word8 where @@ -176,33 +180,33 @@ instance Bits Word8 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (W8# x#) .&. (W8# y#) = W8# (x# `and#` y#) - (W8# x#) .|. (W8# y#) = W8# (x# `or#` y#) - (W8# x#) `xor` (W8# y#) = W8# (x# `xor#` y#) - complement (W8# x#) = W8# (x# `xor#` mb#) + (W8# x#) .&. (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `and#` (extendWord8# y#))) + (W8# x#) .|. (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `or#` (extendWord8# y#))) + (W8# x#) `xor` (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `xor#` (extendWord8# y#))) + complement (W8# x#) = W8# (narrowWord8# ((extendWord8# x#) `xor#` (extendWord8# mb#))) where !(W8# mb#) = maxBound (W8# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = W8# (narrow8Word# (x# `shiftL#` i#)) - | otherwise = W8# (x# `shiftRL#` negateInt# i#) + | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftL#` i#)) + | otherwise = W8# (narrowWord8# ((extendWord8# x#) `shiftRL#` negateInt# i#)) (W8# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = W8# (narrow8Word# (x# `shiftL#` i#)) + | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftL#` i#)) | otherwise = overflowError (W8# x#) `unsafeShiftL` (I# i#) = - W8# (narrow8Word# (x# `uncheckedShiftL#` i#)) + W8# (narrowWord8# ((extendWord8# x#) `uncheckedShiftL#` i#)) (W8# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = W8# (x# `shiftRL#` i#) + | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftRL#` i#)) | otherwise = overflowError - (W8# x#) `unsafeShiftR` (I# i#) = W8# (x# `uncheckedShiftRL#` i#) + (W8# x#) `unsafeShiftR` (I# i#) = W8# (narrowWord8# ((extendWord8# x#) `uncheckedShiftRL#` i#)) (W8# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = W8# x# - | otherwise = W8# (narrow8Word# ((x# `uncheckedShiftL#` i'#) `or#` - (x# `uncheckedShiftRL#` (8# -# i'#)))) + | otherwise = W8# (narrowWord8# (((extendWord8# x#) `uncheckedShiftL#` i'#) `or#` + ((extendWord8# x#) `uncheckedShiftRL#` (8# -# i'#)))) where !i'# = word2Int# (int2Word# i# `and#` 7##) bitSizeMaybe i = Just (finiteBitSize i) bitSize i = finiteBitSize i isSigned _ = False - popCount (W8# x#) = I# (word2Int# (popCnt8# x#)) + popCount (W8# x#) = I# (word2Int# (popCnt8# (extendWord8# x#))) bit = bitDefault testBit = testBitDefault @@ -211,14 +215,14 @@ instance FiniteBits Word8 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize _ = 8 - countLeadingZeros (W8# x#) = I# (word2Int# (clz8# x#)) - countTrailingZeros (W8# x#) = I# (word2Int# (ctz8# x#)) + countLeadingZeros (W8# x#) = I# (word2Int# (clz8# (extendWord8# x#))) + countTrailingZeros (W8# x#) = I# (word2Int# (ctz8# (extendWord8# x#))) {-# RULES "fromIntegral/Word8->Word8" fromIntegral = id :: Word8 -> Word8 "fromIntegral/Word8->Integer" fromIntegral = toInteger :: Word8 -> Integer -"fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrow8Word# x#) -"fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# x#) +"fromIntegral/a->Word8" fromIntegral = \x -> case fromIntegral x of W# x# -> W8# (narrowWord8# x#) +"fromIntegral/Word8->a" fromIntegral = \(W8# x#) -> fromIntegral (W# (extendWord8# x#)) #-} {-# RULES @@ -258,7 +262,7 @@ instance FiniteBits Word8 where -- Word16 is represented in the same way as Word. Operations may assume -- and must ensure that it holds only values from its logical range. -data {-# CTYPE "HsWord16" #-} Word16 = W16# Word# +data {-# CTYPE "HsWord16" #-} Word16 = W16# Word16# -- ^ 16-bit unsigned integer type -- See GHC.Classes#matching_overloaded_methods_in_rules @@ -268,8 +272,8 @@ instance Eq Word16 where (/=) = neWord16 eqWord16, neWord16 :: Word16 -> Word16 -> Bool -eqWord16 (W16# x) (W16# y) = isTrue# (x `eqWord#` y) -neWord16 (W16# x) (W16# y) = isTrue# (x `neWord#` y) +eqWord16 (W16# x) (W16# y) = isTrue# ((extendWord16# x) `eqWord#` (extendWord16# y)) +neWord16 (W16# x) (W16# y) = isTrue# ((extendWord16# x) `neWord#` (extendWord16# y)) {-# INLINE [1] eqWord16 #-} {-# INLINE [1] neWord16 #-} @@ -285,10 +289,10 @@ instance Ord Word16 where {-# INLINE [1] ltWord16 #-} {-# INLINE [1] leWord16 #-} gtWord16, geWord16, ltWord16, leWord16 :: Word16 -> Word16 -> Bool -(W16# x) `gtWord16` (W16# y) = isTrue# (x `gtWord#` y) -(W16# x) `geWord16` (W16# y) = isTrue# (x `geWord#` y) -(W16# x) `ltWord16` (W16# y) = isTrue# (x `ltWord#` y) -(W16# x) `leWord16` (W16# y) = isTrue# (x `leWord#` y) +(W16# x) `gtWord16` (W16# y) = isTrue# ((extendWord16# x) `gtWord#` (extendWord16# y)) +(W16# x) `geWord16` (W16# y) = isTrue# ((extendWord16# x) `geWord#` (extendWord16# y)) +(W16# x) `ltWord16` (W16# y) = isTrue# ((extendWord16# x) `ltWord#` (extendWord16# y)) +(W16# x) `leWord16` (W16# y) = isTrue# ((extendWord16# x) `leWord#` (extendWord16# y)) -- | @since 2.01 instance Show Word16 where @@ -296,14 +300,14 @@ instance Show Word16 where -- | @since 2.01 instance Num Word16 where - (W16# x#) + (W16# y#) = W16# (narrow16Word# (x# `plusWord#` y#)) - (W16# x#) - (W16# y#) = W16# (narrow16Word# (x# `minusWord#` y#)) - (W16# x#) * (W16# y#) = W16# (narrow16Word# (x# `timesWord#` y#)) - negate (W16# x#) = W16# (narrow16Word# (int2Word# (negateInt# (word2Int# x#)))) + (W16# x#) + (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `plusWord#` (extendWord16# y#))) + (W16# x#) - (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `minusWord#` (extendWord16# y#))) + (W16# x#) * (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `timesWord#` (extendWord16# y#))) + negate (W16# x#) = W16# (narrowWord16# (int2Word# (negateInt# (word2Int# (extendWord16# x#))))) abs x = x signum 0 = 0 signum _ = 1 - fromInteger i = W16# (narrow16Word# (integerToWord# i)) + fromInteger i = W16# (narrowWord16# (integerToWord# i)) -- | @since 2.01 instance Real Word16 where @@ -319,35 +323,36 @@ instance Enum Word16 where | otherwise = predError "Word16" toEnum i@(I# i#) | i >= 0 && i <= fromIntegral (maxBound::Word16) - = W16# (int2Word# i#) + = W16# (narrowWord16# (int2Word# i#)) | otherwise = toEnumError "Word16" i (minBound::Word16, maxBound::Word16) - fromEnum (W16# x#) = I# (word2Int# x#) + fromEnum (W16# x#) = I# (word2Int# (extendWord16# x#)) enumFrom = boundedEnumFrom enumFromThen = boundedEnumFromThen -- | @since 2.01 instance Integral Word16 where quot (W16# x#) y@(W16# y#) - | y /= 0 = W16# (x# `quotWord#` y#) + | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `quotWord#` (extendWord16# y#))) | otherwise = divZeroError rem (W16# x#) y@(W16# y#) - | y /= 0 = W16# (x# `remWord#` y#) + | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `remWord#` (extendWord16# y#))) | otherwise = divZeroError div (W16# x#) y@(W16# y#) - | y /= 0 = W16# (x# `quotWord#` y#) + | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `quotWord#` (extendWord16# y#))) | otherwise = divZeroError mod (W16# x#) y@(W16# y#) - | y /= 0 = W16# (x# `remWord#` y#) + | y /= 0 = W16# (narrowWord16# ((extendWord16# x#) `remWord#` (extendWord16# y#))) | otherwise = divZeroError quotRem (W16# x#) y@(W16# y#) - | y /= 0 = case x# `quotRemWord#` y# of + | y /= 0 = case (extendWord16# x#) `quotRemWord#` (extendWord16# y#) of (# q, r #) -> - (W16# q, W16# r) + (W16# (narrowWord16# q), W16# (narrowWord16# r)) | otherwise = divZeroError divMod (W16# x#) y@(W16# y#) - | y /= 0 = (W16# (x# `quotWord#` y#), W16# (x# `remWord#` y#)) + | y /= 0 = (W16# (narrowWord16# ((extendWord16# x#) `quotWord#` (extendWord16# y#))) + ,W16# (narrowWord16# ((extendWord16# x#) `remWord#` (extendWord16# y#)))) | otherwise = divZeroError - toInteger (W16# x#) = IS (word2Int# x#) + toInteger (W16# x#) = IS (word2Int# (extendWord16# x#)) -- | @since 2.01 instance Bounded Word16 where @@ -367,33 +372,33 @@ instance Bits Word16 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (W16# x#) .&. (W16# y#) = W16# (x# `and#` y#) - (W16# x#) .|. (W16# y#) = W16# (x# `or#` y#) - (W16# x#) `xor` (W16# y#) = W16# (x# `xor#` y#) - complement (W16# x#) = W16# (x# `xor#` mb#) + (W16# x#) .&. (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `and#` (extendWord16# y#))) + (W16# x#) .|. (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `or#` (extendWord16# y#))) + (W16# x#) `xor` (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `xor#` (extendWord16# y#))) + complement (W16# x#) = W16# (narrowWord16# ((extendWord16# x#) `xor#` (extendWord16# mb#))) where !(W16# mb#) = maxBound (W16# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = W16# (narrow16Word# (x# `shiftL#` i#)) - | otherwise = W16# (x# `shiftRL#` negateInt# i#) + | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftL#` i#)) + | otherwise = W16# (narrowWord16# ((extendWord16# x#) `shiftRL#` negateInt# i#)) (W16# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = W16# (narrow16Word# (x# `shiftL#` i#)) + | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftL#` i#)) | otherwise = overflowError (W16# x#) `unsafeShiftL` (I# i#) = - W16# (narrow16Word# (x# `uncheckedShiftL#` i#)) + W16# (narrowWord16# ((extendWord16# x#) `uncheckedShiftL#` i#)) (W16# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = W16# (x# `shiftRL#` i#) + | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftRL#` i#)) | otherwise = overflowError - (W16# x#) `unsafeShiftR` (I# i#) = W16# (x# `uncheckedShiftRL#` i#) + (W16# x#) `unsafeShiftR` (I# i#) = W16# (narrowWord16# ((extendWord16# x#) `uncheckedShiftRL#` i#)) (W16# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = W16# x# - | otherwise = W16# (narrow16Word# ((x# `uncheckedShiftL#` i'#) `or#` - (x# `uncheckedShiftRL#` (16# -# i'#)))) + | otherwise = W16# (narrowWord16# (((extendWord16# x#) `uncheckedShiftL#` i'#) `or#` + ((extendWord16# x#) `uncheckedShiftRL#` (16# -# i'#)))) where !i'# = word2Int# (int2Word# i# `and#` 15##) bitSizeMaybe i = Just (finiteBitSize i) bitSize i = finiteBitSize i isSigned _ = False - popCount (W16# x#) = I# (word2Int# (popCnt16# x#)) + popCount (W16# x#) = I# (word2Int# (popCnt16# (extendWord16# x#))) bit = bitDefault testBit = testBitDefault @@ -402,21 +407,21 @@ instance FiniteBits Word16 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize _ = 16 - countLeadingZeros (W16# x#) = I# (word2Int# (clz16# x#)) - countTrailingZeros (W16# x#) = I# (word2Int# (ctz16# x#)) + countLeadingZeros (W16# x#) = I# (word2Int# (clz16# (extendWord16# x#))) + countTrailingZeros (W16# x#) = I# (word2Int# (ctz16# (extendWord16# x#))) -- | Reverse order of bytes in 'Word16'. -- -- @since 4.7.0.0 byteSwap16 :: Word16 -> Word16 -byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#)) +byteSwap16 (W16# w#) = W16# (narrowWord16# (byteSwap16# (extendWord16# w#))) {-# RULES -"fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# x# +"fromIntegral/Word8->Word16" fromIntegral = \(W8# x#) -> W16# (narrowWord16# (extendWord8# x#)) "fromIntegral/Word16->Word16" fromIntegral = id :: Word16 -> Word16 "fromIntegral/Word16->Integer" fromIntegral = toInteger :: Word16 -> Integer -"fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrow16Word# x#) -"fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# x#) +"fromIntegral/a->Word16" fromIntegral = \x -> case fromIntegral x of W# x# -> W16# (narrowWord16# x#) +"fromIntegral/Word16->a" fromIntegral = \(W16# x#) -> fromIntegral (W# (extendWord16# x#)) #-} {-# RULES @@ -492,7 +497,7 @@ byteSwap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#)) #endif -data {-# CTYPE "HsWord32" #-} Word32 = W32# Word# +data {-# CTYPE "HsWord32" #-} Word32 = W32# Word32# -- ^ 32-bit unsigned integer type -- See GHC.Classes#matching_overloaded_methods_in_rules @@ -502,8 +507,8 @@ instance Eq Word32 where (/=) = neWord32 eqWord32, neWord32 :: Word32 -> Word32 -> Bool -eqWord32 (W32# x) (W32# y) = isTrue# (x `eqWord#` y) -neWord32 (W32# x) (W32# y) = isTrue# (x `neWord#` y) +eqWord32 (W32# x) (W32# y) = isTrue# ((extendWord32# x) `eqWord#` (extendWord32# y)) +neWord32 (W32# x) (W32# y) = isTrue# ((extendWord32# x) `neWord#` (extendWord32# y)) {-# INLINE [1] eqWord32 #-} {-# INLINE [1] neWord32 #-} @@ -519,21 +524,21 @@ instance Ord Word32 where {-# INLINE [1] ltWord32 #-} {-# INLINE [1] leWord32 #-} gtWord32, geWord32, ltWord32, leWord32 :: Word32 -> Word32 -> Bool -(W32# x) `gtWord32` (W32# y) = isTrue# (x `gtWord#` y) -(W32# x) `geWord32` (W32# y) = isTrue# (x `geWord#` y) -(W32# x) `ltWord32` (W32# y) = isTrue# (x `ltWord#` y) -(W32# x) `leWord32` (W32# y) = isTrue# (x `leWord#` y) +(W32# x) `gtWord32` (W32# y) = isTrue# ((extendWord32# x) `gtWord#` (extendWord32# y)) +(W32# x) `geWord32` (W32# y) = isTrue# ((extendWord32# x) `geWord#` (extendWord32# y)) +(W32# x) `ltWord32` (W32# y) = isTrue# ((extendWord32# x) `ltWord#` (extendWord32# y)) +(W32# x) `leWord32` (W32# y) = isTrue# ((extendWord32# x) `leWord#` (extendWord32# y)) -- | @since 2.01 instance Num Word32 where - (W32# x#) + (W32# y#) = W32# (narrow32Word# (x# `plusWord#` y#)) - (W32# x#) - (W32# y#) = W32# (narrow32Word# (x# `minusWord#` y#)) - (W32# x#) * (W32# y#) = W32# (narrow32Word# (x# `timesWord#` y#)) - negate (W32# x#) = W32# (narrow32Word# (int2Word# (negateInt# (word2Int# x#)))) + (W32# x#) + (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `plusWord#` (extendWord32# y#))) + (W32# x#) - (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `minusWord#` (extendWord32# y#))) + (W32# x#) * (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `timesWord#` (extendWord32# y#))) + negate (W32# x#) = W32# (narrowWord32# (int2Word# (negateInt# (word2Int# (extendWord32# x#))))) abs x = x signum 0 = 0 signum _ = 1 - fromInteger i = W32# (narrow32Word# (integerToWord# i)) + fromInteger i = W32# (narrowWord32# (integerToWord# i)) -- | @since 2.01 instance Enum Word32 where @@ -548,19 +553,19 @@ instance Enum Word32 where #if WORD_SIZE_IN_BITS > 32 && i <= fromIntegral (maxBound::Word32) #endif - = W32# (int2Word# i#) + = W32# (narrowWord32# (int2Word# i#)) | otherwise = toEnumError "Word32" i (minBound::Word32, maxBound::Word32) #if WORD_SIZE_IN_BITS == 32 fromEnum x@(W32# x#) | x <= fromIntegral (maxBound::Int) - = I# (word2Int# x#) + = I# (word2Int# (extendWord32# x#)) | otherwise = fromEnumError "Word32" x enumFrom = integralEnumFrom enumFromThen = integralEnumFromThen enumFromTo = integralEnumFromTo enumFromThenTo = integralEnumFromThenTo #else - fromEnum (W32# x#) = I# (word2Int# x#) + fromEnum (W32# x#) = I# (word2Int# (extendWord32# x#)) enumFrom = boundedEnumFrom enumFromThen = boundedEnumFromThen #endif @@ -568,33 +573,34 @@ instance Enum Word32 where -- | @since 2.01 instance Integral Word32 where quot (W32# x#) y@(W32# y#) - | y /= 0 = W32# (x# `quotWord#` y#) + | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `quotWord#` (extendWord32# y#))) | otherwise = divZeroError rem (W32# x#) y@(W32# y#) - | y /= 0 = W32# (x# `remWord#` y#) + | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `remWord#` (extendWord32# y#))) | otherwise = divZeroError div (W32# x#) y@(W32# y#) - | y /= 0 = W32# (x# `quotWord#` y#) + | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `quotWord#` (extendWord32# y#))) | otherwise = divZeroError mod (W32# x#) y@(W32# y#) - | y /= 0 = W32# (x# `remWord#` y#) + | y /= 0 = W32# (narrowWord32# ((extendWord32# x#) `remWord#` (extendWord32# y#))) | otherwise = divZeroError quotRem (W32# x#) y@(W32# y#) - | y /= 0 = case x# `quotRemWord#` y# of + | y /= 0 = case (extendWord32# x#) `quotRemWord#` (extendWord32# y#) of (# q, r #) -> - (W32# q, W32# r) + (W32# (narrowWord32# q), W32# (narrowWord32# r)) | otherwise = divZeroError divMod (W32# x#) y@(W32# y#) - | y /= 0 = (W32# (x# `quotWord#` y#), W32# (x# `remWord#` y#)) + | y /= 0 = (W32# (narrowWord32# ((extendWord32# x#) `quotWord#` (extendWord32# y#))) + ,W32# (narrowWord32# ((extendWord32# x#) `remWord#` (extendWord32# y#)))) | otherwise = divZeroError toInteger (W32# x#) #if WORD_SIZE_IN_BITS == 32 | isTrue# (i# >=# 0#) = IS i# - | otherwise = integerFromWord# x# + | otherwise = integerFromWord# (extendWord32# x#) where !i# = word2Int# x# #else - = IS (word2Int# x#) + = IS (word2Int# (extendWord32# x#)) #endif -- | @since 2.01 @@ -604,33 +610,33 @@ instance Bits Word32 where {-# INLINE testBit #-} {-# INLINE popCount #-} - (W32# x#) .&. (W32# y#) = W32# (x# `and#` y#) - (W32# x#) .|. (W32# y#) = W32# (x# `or#` y#) - (W32# x#) `xor` (W32# y#) = W32# (x# `xor#` y#) - complement (W32# x#) = W32# (x# `xor#` mb#) + (W32# x#) .&. (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `and#` (extendWord32# y#))) + (W32# x#) .|. (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `or#` (extendWord32# y#))) + (W32# x#) `xor` (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `xor#` (extendWord32# y#))) + complement (W32# x#) = W32# (narrowWord32# ((extendWord32# x#) `xor#` (extendWord32# mb#))) where !(W32# mb#) = maxBound (W32# x#) `shift` (I# i#) - | isTrue# (i# >=# 0#) = W32# (narrow32Word# (x# `shiftL#` i#)) - | otherwise = W32# (x# `shiftRL#` negateInt# i#) + | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftL#` i#)) + | otherwise = W32# (narrowWord32# ((extendWord32# x#) `shiftRL#` negateInt# i#)) (W32# x#) `shiftL` (I# i#) - | isTrue# (i# >=# 0#) = W32# (narrow32Word# (x# `shiftL#` i#)) + | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftL#` i#)) | otherwise = overflowError (W32# x#) `unsafeShiftL` (I# i#) = - W32# (narrow32Word# (x# `uncheckedShiftL#` i#)) + W32# (narrowWord32# ((extendWord32# x#) `uncheckedShiftL#` i#)) (W32# x#) `shiftR` (I# i#) - | isTrue# (i# >=# 0#) = W32# (x# `shiftRL#` i#) + | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftRL#` i#)) | otherwise = overflowError - (W32# x#) `unsafeShiftR` (I# i#) = W32# (x# `uncheckedShiftRL#` i#) + (W32# x#) `unsafeShiftR` (I# i#) = W32# (narrowWord32# ((extendWord32# x#) `uncheckedShiftRL#` i#)) (W32# x#) `rotate` (I# i#) | isTrue# (i'# ==# 0#) = W32# x# - | otherwise = W32# (narrow32Word# ((x# `uncheckedShiftL#` i'#) `or#` - (x# `uncheckedShiftRL#` (32# -# i'#)))) + | otherwise = W32# (narrowWord32# (((extendWord32# x#) `uncheckedShiftL#` i'#) `or#` + ((extendWord32# x#) `uncheckedShiftRL#` (32# -# i'#)))) where !i'# = word2Int# (int2Word# i# `and#` 31##) bitSizeMaybe i = Just (finiteBitSize i) bitSize i = finiteBitSize i isSigned _ = False - popCount (W32# x#) = I# (word2Int# (popCnt32# x#)) + popCount (W32# x#) = I# (word2Int# (popCnt32# (extendWord32# x#))) bit = bitDefault testBit = testBitDefault @@ -639,16 +645,16 @@ instance FiniteBits Word32 where {-# INLINE countLeadingZeros #-} {-# INLINE countTrailingZeros #-} finiteBitSize _ = 32 - countLeadingZeros (W32# x#) = I# (word2Int# (clz32# x#)) - countTrailingZeros (W32# x#) = I# (word2Int# (ctz32# x#)) + countLeadingZeros (W32# x#) = I# (word2Int# (clz32# (extendWord32# x#))) + countTrailingZeros (W32# x#) = I# (word2Int# (ctz32# (extendWord32# x#))) {-# RULES -"fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# x# -"fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# x# +"fromIntegral/Word8->Word32" fromIntegral = \(W8# x#) -> W32# (narrowWord32# (extendWord8# x#)) +"fromIntegral/Word16->Word32" fromIntegral = \(W16# x#) -> W32# (narrowWord32# (extendWord16# x#)) "fromIntegral/Word32->Word32" fromIntegral = id :: Word32 -> Word32 "fromIntegral/Word32->Integer" fromIntegral = toInteger :: Word32 -> Integer -"fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrow32Word# x#) -"fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# x#) +"fromIntegral/a->Word32" fromIntegral = \x -> case fromIntegral x of W# x# -> W32# (narrowWord32# x#) +"fromIntegral/Word32->a" fromIntegral = \(W32# x#) -> fromIntegral (W# (extendWord32# x#)) #-} -- | @since 2.01 @@ -679,7 +685,7 @@ instance Ix Word32 where -- -- @since 4.7.0.0 byteSwap32 :: Word32 -> Word32 -byteSwap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#)) +byteSwap32 (W32# w#) = W32# (narrowWord32# (byteSwap32# (extendWord32# w#))) ------------------------------------------------------------------------ -- type Word64 @@ -1050,19 +1056,19 @@ byteSwap64 (W64# w#) = W64# (byteSwap# w#) -- -- @since 4.12.0.0 bitReverse8 :: Word8 -> Word8 -bitReverse8 (W8# w#) = W8# (narrow8Word# (bitReverse8# w#)) +bitReverse8 (W8# w#) = W8# (narrowWord8# (bitReverse8# (extendWord8# w#))) -- | Reverse the order of the bits in a 'Word16'. -- -- @since 4.12.0.0 bitReverse16 :: Word16 -> Word16 -bitReverse16 (W16# w#) = W16# (narrow16Word# (bitReverse16# w#)) +bitReverse16 (W16# w#) = W16# (narrowWord16# (bitReverse16# (extendWord16# w#))) -- | Reverse the order of the bits in a 'Word32'. -- -- @since 4.12.0.0 bitReverse32 :: Word32 -> Word32 -bitReverse32 (W32# w#) = W32# (narrow32Word# (bitReverse32# w#)) +bitReverse32 (W32# w#) = W32# (narrowWord32# (bitReverse32# (extendWord32# w#))) -- | Reverse the order of the bits in a 'Word64'. -- ===================================== libraries/base/base.cabal ===================================== @@ -88,7 +88,7 @@ Library build-depends: rts == 1.0, - ghc-prim >= 0.5.1.0 && < 0.8, + ghc-prim >= 0.5.1.0 && < 0.9, ghc-bignum >= 1.0 && < 2.0 exposed-modules: ===================================== libraries/binary ===================================== @@ -1 +1 @@ -Subproject commit dfaf780596328c9184758452b78288e8f405fcc1 +Subproject commit ddee463e99fcda352f497d5fc925a72a1cf24faa ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit e6cb01e2ec0bfdd19298418c85f220925a9fa307 +Subproject commit 9e542456b9b5514de7574774e47932c0bedd5b43 ===================================== libraries/ghc-bignum/ghc-bignum.cabal ===================================== @@ -80,7 +80,7 @@ library ForeignFunctionInterface build-depends: - ghc-prim >= 0.5.1.0 && < 0.8 + ghc-prim >= 0.5.1.0 && < 0.9 hs-source-dirs: src/ include-dirs: include/ ===================================== libraries/ghc-compact/ghc-compact.cabal ===================================== @@ -36,7 +36,7 @@ library UnboxedTuples CPP - build-depends: ghc-prim >= 0.5.3 && < 0.8, + build-depends: ghc-prim >= 0.5.3 && < 0.9, base >= 4.9.0 && < 4.16, bytestring >= 0.10.6.0 ghc-options: -Wall ===================================== libraries/ghc-heap/ghc-heap.cabal.in ===================================== @@ -23,7 +23,7 @@ library default-language: Haskell2010 build-depends: base >= 4.9.0 && < 5.0 - , ghc-prim > 0.2 && < 0.8 + , ghc-prim > 0.2 && < 0.9 , rts == 1.0.* ghc-options: -Wall ===================================== libraries/ghc-prim/ghc-prim.cabal ===================================== @@ -1,6 +1,6 @@ cabal-version: 2.2 name: ghc-prim -version: 0.7.0 +version: 0.8.0 -- NOTE: Don't forget to update ./changelog.md license: BSD-3-Clause license-file: LICENSE ===================================== libraries/ghci/GHCi/BreakArray.hs ===================================== @@ -32,10 +32,19 @@ import Control.Monad import Data.Word import GHC.Word -import GHC.Exts +import GHC.Exts hiding (extendWord8#, narrowWord8#) import GHC.IO ( IO(..) ) import System.IO.Unsafe ( unsafeDupablePerformIO ) +#if MIN_VERSION_ghc_prim(0,8,0) +import GHC.Base (extendWord8#, narrowWord8#) +#else +import GHC.Prim (Word#) +narrowWord8#, extendWord8# :: Word# -> Word# +narrowWord8# w = w +extendWord8# w = w +#endif + data BreakArray = BA (MutableByteArray# RealWorld) breakOff, breakOn :: Word8 @@ -96,7 +105,7 @@ newBreakArray entries@(I# sz) = do case breakOff of W8# off -> do let loop n | isTrue# (n ==# sz) = return () - | otherwise = do writeBA# array n off; loop (n +# 1#) + | otherwise = do writeBA# array n (extendWord8# off); loop (n +# 1#) loop 0# return $ BA array @@ -105,11 +114,11 @@ writeBA# array i word = IO $ \s -> case writeWord8Array# array i word s of { s -> (# s, () #) } writeBreakArray :: BreakArray -> Int -> Word8 -> IO () -writeBreakArray (BA array) (I# i) (W8# word) = writeBA# array i word +writeBreakArray (BA array) (I# i) (W8# word) = writeBA# array i (extendWord8# word) readBA# :: MutableByteArray# RealWorld -> Int# -> IO Word8 readBA# array i = IO $ \s -> - case readWord8Array# array i s of { (# s, c #) -> (# s, W8# c #) } + case readWord8Array# array i s of { (# s, c #) -> (# s, W8# (narrowWord8# c) #) } readBreakArray :: BreakArray -> Int -> IO Word8 readBreakArray (BA array) (I# i) = readBA# array i ===================================== libraries/ghci/ghci.cabal.in ===================================== @@ -73,6 +73,7 @@ library Build-Depends: array == 0.5.*, base >= 4.8 && < 4.16, + ghc-prim >= 0.5.0 && < 0.9, binary == 0.8.*, bytestring == 0.10.*, containers >= 0.5 && < 0.7, ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit 80cb9ee2eb7141171171318bbd6760fe80012524 +Subproject commit 9ead2aba5ac72f4acc74b12ec45972f865600916 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/170903093be2a26ee527a68354a0d6bca4264e50...80115ada7822e3c3006a2290a60492f6dbc6f205 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/170903093be2a26ee527a68354a0d6bca4264e50...80115ada7822e3c3006a2290a60492f6dbc6f205 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 Sun Nov 1 11:53:59 2020 From: gitlab at gitlab.haskell.org (Sven Tennie) Date: Sun, 01 Nov 2020 06:53:59 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] Fix compile errors Message-ID: <5f9ea1d75dbab_7853fb643f0a0942366f0@gitlab.haskell.org.mail> Sven Tennie pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC Commits: c3c9d159 by Sven Tennie at 2020-11-01T12:53:46+01:00 Fix compile errors This commit will be squashed. - - - - - 2 changed files: - rts/CloneStack.c - rts/CloneStack.h Changes: ===================================== rts/CloneStack.c ===================================== @@ -44,12 +44,13 @@ static StgStack* cloneStackChunk(Capability* capability, const StgStack* stack) StgStack* cloneStack(Capability* capability, const StgStack* stack) { StgStack *top_stack = cloneStackChunk(capability, stack); - StgStack last_stack = top_stack; + StgStack *last_stack = top_stack; while (true) { // check whether the stack ends in an underflow frame - StgPtr top = last_stack->stack + last_stack->stack_size - StgUnderflowFrame *frame = ((StgUnderflowFrame *)top)[-1]; - if (frame->header.info == &stg_UNDERFLOW_FRAME_info) { + StgPtr top = last_stack->stack + last_stack->stack_size; + StgUnderflowFrame *underFlowFrame = ((StgUnderflowFrame *) top); + StgUnderflowFrame *frame = underFlowFrame--; + if (frame->info == &stg_stack_underflow_frame_info) { StgStack *s = cloneStackChunk(capability, frame->next_chunk); frame->next_chunk = s; last_stack = s; @@ -96,9 +97,8 @@ void handleCloneStackMessage(MessageCloneStack *msg){ #else // !defined(THREADED_RTS) GNU_ATTRIBUTE(__noreturn__) -void sendCloneStackMessage(StgTSO *tso STG_UNUSED, HsStablePtr mvar STG_UNUSED) { +void sendCloneStackMessage(StgTSO *tso STG_UNUSED, HsStablePtr mvar STG_UNUSED) { barf("Sending CloneStackMessages is only available in threaded RTS!"); } #endif // end !defined(THREADED_RTS) - ===================================== rts/CloneStack.h ===================================== @@ -12,12 +12,12 @@ extern StgClosure DLL_IMPORT_DATA_VARNAME(base_GHCziStackziCloneStack_StackSnaps StgStack* cloneStack(Capability* capability, const StgStack* stack); +void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar); + #include "BeginPrivate.h" #if defined(THREADED_RTS) void handleCloneStackMessage(MessageCloneStack *msg); #endif -void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar); - #include "EndPrivate.h" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3c9d1596531997621dfa4a39cdafa16578c8228 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c3c9d1596531997621dfa4a39cdafa16578c8228 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 Sun Nov 1 13:52:16 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 08:52:16 -0500 Subject: [Git][ghc/ghc][master] Fix a leak in `transpose` Message-ID: <5f9ebd901554d_785edd5dac244496@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - 4 changed files: - libraries/base/Data/OldList.hs - + libraries/base/tests/T18642.hs - + libraries/base/tests/T18642.stdout - libraries/base/tests/all.T Changes: ===================================== libraries/base/Data/OldList.hs ===================================== @@ -547,19 +547,57 @@ intercalate xs xss = concat (intersperse xs xss) -- -- >>> transpose [[10,11],[20],[],[30,31,32]] -- [[10,20,30],[11,31],[32]] -transpose :: [[a]] -> [[a]] -transpose [] = [] -transpose ([] : xss) = transpose xss -transpose ((x:xs) : xss) = (x : hds) : transpose (xs : tls) +transpose :: [[a]] -> [[a]] +transpose [] = [] +transpose ([] : xss) = transpose xss +transpose ((x : xs) : xss) = combine x hds xs tls where -- We tie the calculations of heads and tails together -- to prevent heads from leaking into tails and vice versa. -- unzip makes the selector thunk arrangements we need to -- ensure everything gets cleaned up properly. - (hds, tls) = unzip [(hd, tl) | (hd:tl) <- xss] + (hds, tls) = unzip [(hd, tl) | hd : tl <- xss] + combine y h ys t = (y:h) : transpose (ys:t) + {-# NOINLINE combine #-} + {- Implementation note: + If the bottom part of the function was written as such: + + ``` + transpose ((x : xs) : xss) = (x:hds) : transpose (xs:tls) + where + (hds,tls) = hdstls + hdstls = unzip [(hd, tl) | hd : tl <- xss] + {-# NOINLINE hdstls #-} + ``` + Here are the steps that would take place: + + 1. We allocate a thunk, `hdstls`, representing the result of unzipping. + 2. We allocate selector thunks, `hds` and `tls`, that deconstruct `hdstls`. + 3. Install `hds` as the tail of the result head and pass `xs:tls` to + the recursive call in the result tail. + + Once optimised, this code would amount to: + + ``` + transpose ((x : xs) : xss) = (x:hds) : (let tls = snd hdstls in transpose (xs:tls)) + where + hds = fst hdstls + hdstls = unzip [(hd, tl) | hd : tl <- xss] + {-# NOINLINE hdstls #-} + ``` + + In particular, GHC does not produce the `tls` selector thunk immediately; + rather, it waits to do so until the tail of the result is actually demanded. + So when `hds` is demanded, that does not resolve `snd hdstls`; the tail of the + result keeps `hdstls` alive. + + By writing `combine` and making it NOINLINE, we prevent GHC from delaying + the selector thunk allocation, requiring that `hds` and `tls` are actually + allocated to be passed to `combine`. + -} --- | The 'partition' function takes a predicate a list and returns +-- | The 'partition' function takes a predicate and a list, and returns -- the pair of lists of elements which do and do not satisfy the -- predicate, respectively; i.e., -- ===================================== libraries/base/tests/T18642.hs ===================================== @@ -0,0 +1,27 @@ +{-# LANGUAGE NumericUnderscores #-} +module Main where + +import Data.List (transpose, foldl') +import GHC.Stats +import System.Exit + +thingy :: [[[Int]]] +thingy = [ [[1],[2]], [[1..10^7], [3]]] + +thingy2 :: [[[Int]]] +thingy2 = [ [[1],[2]], [[3], [2..10^7+1]]] + +main = do + htr : ttr <- pure $ transpose thingy + print $ even $ foldl' (+) 0 . head . tail $ htr + + htr2 : ttr2 <- pure $ transpose thingy2 + print $ even $ foldl' (+) 0 . head . tail . head $ ttr2 + + maxLiveBytes <- max_live_bytes <$> getRTSStats + if (maxLiveBytes) < 200_000 + then putStrLn "Test is running in the expected residency limit" + else do + putStrLn $ "Test is running with " <> show maxLiveBytes <> " bytes of residency!" + exitFailure + ===================================== libraries/base/tests/T18642.stdout ===================================== @@ -0,0 +1,3 @@ +True +True +Test is running in the expected residency limit ===================================== libraries/base/tests/all.T ===================================== @@ -260,3 +260,4 @@ test('T16943b', normal, compile_and_run, ['']) test('T17499', [collect_stats('bytes allocated',5)], compile_and_run, ['-O -w']) test('T16643', normal, compile_and_run, ['']) test('clamp', normal, compile_and_run, ['']) +test('T18642', extra_run_opts('+RTS -T -RTS'), compile_and_run, ['-O2']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce1bb9959e2465db1c3880f3c532ae7e1be39b41 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce1bb9959e2465db1c3880f3c532ae7e1be39b41 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 Sun Nov 1 13:52:50 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 08:52:50 -0500 Subject: [Git][ghc/ghc][master] Scav: Use bd->gen_no instead of bd->gen->no Message-ID: <5f9ebdb299224_7853fb65ddcc1a42470b7@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 1 changed file: - rts/sm/Scav.c Changes: ===================================== rts/sm/Scav.c ===================================== @@ -435,7 +435,7 @@ scavenge_block (bdescr *bd) saved_eager_promotion = gct->eager_promotion; gct->failed_to_evac = false; - ws = &gct->gens[bd->gen->no]; + ws = &gct->gens[bd->gen_no]; p = bd->u.scan; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e63db32c7eb089985a1a7279a0a886a32d70ac0e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e63db32c7eb089985a1a7279a0a886a32d70ac0e 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 Sun Nov 1 13:58:15 2020 From: gitlab at gitlab.haskell.org (Sven Tennie) Date: Sun, 01 Nov 2020 08:58:15 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] Fix test - Expect cloned stack to be not dirty Message-ID: <5f9ebef72e9c6_785fa5f460248498@gitlab.haskell.org.mail> Sven Tennie pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC Commits: 7223c484 by Sven Tennie at 2020-11-01T14:57:58+01:00 Fix test - Expect cloned stack to be not dirty This commit will be squashed. - - - - - 2 changed files: - testsuite/tests/rts/cloneStackLib.c - testsuite/tests/rts/cloneThreadStack.hs Changes: ===================================== testsuite/tests/rts/cloneStackLib.c ===================================== @@ -20,10 +20,6 @@ void expectStacksToBeEqual(StgStack *clonedStack, StgTSO *tso) { barf("Expected same stack_size!"); } - if(liveStack->dirty != clonedStack->dirty){ - barf("Expected same dirty flags!"); - } - if(liveStack->marking != clonedStack->marking){ barf("Expected same marking flags!"); } @@ -35,6 +31,12 @@ void expectStacksToBeEqual(StgStack *clonedStack, StgTSO *tso) { } } +void expectStackToBeNotDirty(StgStack *stack) { + if(stack->dirty != 0) { + barf("Expected stack to be not dirty. But dirty flag was set to %u", stack->dirty); + } +} + void expectClosureTypes(StgStack *stack, unsigned int types[], size_t typesSize){ StgPtr sp = stack->sp; StgPtr spBottom = stack->stack + stack->stack_size; ===================================== testsuite/tests/rts/cloneThreadStack.hs ===================================== @@ -10,6 +10,8 @@ import GHC.Conc foreign import ccall "expectStacksToBeEqual" expectStacksToBeEqual:: StackSnapshot# -> ThreadId# -> IO () +foreign import ccall "expectStackToBeNotDirty" expectStackToBeNotDirty:: StackSnapshot# -> IO () + main :: IO () main = do mVarToBeBlockedOn <- newEmptyMVar @@ -22,6 +24,7 @@ main = do let (StackSnapshot stack) = stackSnapshot let (ThreadId tid#) = threadId expectStacksToBeEqual stack tid# + expectStackToBeNotDirty stack immediatelyBlocking :: MVar Int -> IO () immediatelyBlocking mVarToBeBlockedOn = do View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7223c48466d501a077f0331ae4f390269310d984 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7223c48466d501a077f0331ae4f390269310d984 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 Sun Nov 1 16:15:32 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 11:15:32 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/ghc-8.10-backports Message-ID: <5f9edf2453205_7853fb627c25020256320@gitlab.haskell.org.mail> Ben Gamari deleted branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC -- 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 Sun Nov 1 16:15:36 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 11:15:36 -0500 Subject: [Git][ghc/ghc][ghc-8.10] Bump Cabal submodule to 3.2.1.0 Message-ID: <5f9edf2822d2e_7853fb627c2502025656a@gitlab.haskell.org.mail> Ben Gamari pushed to branch ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: cc085aef by Ben Gamari at 2020-10-31T22:31:33-04:00 Bump Cabal submodule to 3.2.1.0 - - - - - 15 changed files: - libraries/Cabal - libraries/ghc-prim/ghc-prim.cabal - testsuite/tests/backpack/cabal/T16219/backpack-issue.cabal - testsuite/tests/backpack/cabal/bkpcabal01/bkpcabal01.cabal - testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.cabal - testsuite/tests/backpack/cabal/bkpcabal03/asig1/asig1.cabal - testsuite/tests/backpack/cabal/bkpcabal03/asig2/asig2.cabal - testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in1 - testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in2 - testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in1 - testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in2 - testsuite/tests/backpack/cabal/bkpcabal05/bkpcabal05.cabal - testsuite/tests/backpack/cabal/bkpcabal06/bkpcabal06.cabal - testsuite/tests/backpack/cabal/bkpcabal07/bkpcabal07.cabal - testsuite/tests/cabal/cabal01/test.cabal Changes: ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit df65caf90ff79894dacecf73a642452aaabcc0a5 +Subproject commit 48bf10787e27364730dd37a42b603cee8d6af7ee ===================================== libraries/ghc-prim/ghc-prim.cabal ===================================== @@ -1,4 +1,4 @@ -cabal-version: 2.1 +cabal-version: 2.2 name: ghc-prim version: 0.6.1 -- NOTE: Don't forget to update ./changelog.md ===================================== testsuite/tests/backpack/cabal/T16219/backpack-issue.cabal ===================================== @@ -1,8 +1,9 @@ +cabal-version: 2.2 name: backpack-issue version: 0.1.0.0 -- synopsis: -- description: -license: BSD3 +license: BSD-3-Clause license-file: LICENSE author: Isaac Elliott maintainer: isaace71295 at gmail.com @@ -10,7 +11,6 @@ maintainer: isaace71295 at gmail.com -- category: build-type: Simple extra-source-files: CHANGELOG.md -cabal-version: >=2 library library-a signatures: A.Sig ===================================== testsuite/tests/backpack/cabal/bkpcabal01/bkpcabal01.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal01 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library impl exposed-modules: H, I ===================================== testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal01 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library p signatures: H ===================================== testsuite/tests/backpack/cabal/bkpcabal03/asig1/asig1.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: asig1 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: base ===================================== testsuite/tests/backpack/cabal/bkpcabal03/asig2/asig2.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: asig2 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: base ===================================== testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in1 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal03 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: asig1, base ===================================== testsuite/tests/backpack/cabal/bkpcabal03/bkpcabal03.cabal.in2 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal03 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library build-depends: asig1, asig2, base ===================================== testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in1 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal04 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library p signatures: A ===================================== testsuite/tests/backpack/cabal/bkpcabal04/bkpcabal04.cabal.in2 ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal04 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library p signatures: A ===================================== testsuite/tests/backpack/cabal/bkpcabal05/bkpcabal05.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal05 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=1.25 library signatures: A ===================================== testsuite/tests/backpack/cabal/bkpcabal06/bkpcabal06.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal06 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: 2.0 library sig signatures: P ===================================== testsuite/tests/backpack/cabal/bkpcabal07/bkpcabal07.cabal ===================================== @@ -1,10 +1,10 @@ +cabal-version: 2.2 name: bkpcabal06 version: 0.1.0.0 -license: BSD3 +license: BSD-3-Clause author: Edward Z. Yang maintainer: ezyang at cs.stanford.edu build-type: Simple -cabal-version: >=2.0 library indef signatures: P ===================================== testsuite/tests/cabal/cabal01/test.cabal ===================================== @@ -1,3 +1,4 @@ +Cabal-Version: 2.2 Name: test Version: 1.0 Exposed-Modules: A View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc085aefd9d72da6aff5c5305a6b864398f95ec3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc085aefd9d72da6aff5c5305a6b864398f95ec3 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 Sun Nov 1 16:24:00 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 11:24:00 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Fix a leak in `transpose` Message-ID: <5f9ee120c370a_7853fb61ddc2f0426662d@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - cff96950 by Ben Gamari at 2020-11-01T11:23:51-05:00 gitlab-ci: Add usage message to ci.sh - - - - - ade2f9a7 by Ben Gamari at 2020-11-01T11:23:51-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234. - - - - - 58eae6f7 by GHC GitLab CI at 2020-11-01T11:23:51-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - ba741557 by Ben Gamari at 2020-11-01T11:23:52-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 13 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - hadrian/src/Builder.hs - hadrian/src/Settings/Builders/RunTest.hs - libraries/base/Data/OldList.hs - + libraries/base/tests/T18642.hs - + libraries/base/tests/T18642.stdout - libraries/base/tests/all.T - rts/sm/Scav.c - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk Changes: ===================================== .gitlab-ci.yml ===================================== @@ -257,6 +257,20 @@ validate-x86_64-linux-deb9-unreg-hadrian: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build needs: [lint-linters, lint-submods] ===================================== .gitlab/ci.sh ===================================== @@ -2,6 +2,8 @@ # shellcheck disable=SC2230 # This is the primary driver of the GitLab CI infrastructure. +# Run `ci.sh usage` for usage information. + set -e -o pipefail @@ -17,6 +19,56 @@ fi source $TOP/.gitlab/common.sh +function usage() { + cat < /dev/null; then @@ -53,11 +105,11 @@ function setup_locale() { function mingw_init() { case "$MSYSTEM" in MINGW32) - triple="i386-unknown-mingw32" + target_triple="i386-unknown-mingw32" boot_triple="i386-unknown-mingw32" # triple of bootstrap GHC ;; MINGW64) - triple="x86_64-unknown-mingw32" + target_triple="x86_64-unknown-mingw32" boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC ;; *) @@ -320,8 +372,8 @@ function configure() { end_section "booting" local target_args="" - if [[ -n "$triple" ]]; then - target_args="--target=$triple" + if [[ -n "$target_triple" ]]; then + target_args="--target=$target_triple" fi start_section "configuring" @@ -367,6 +419,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -387,6 +444,11 @@ function build_hadrian() { } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -473,9 +535,15 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in + usage) usage ;; setup) setup && cleanup_submodules ;; configure) configure ;; build_make) build_make ;; ===================================== hadrian/src/Builder.hs ===================================== @@ -304,6 +304,11 @@ instance H.Builder Builder where Makeindex -> unit $ cmd' [Cwd output] [path] (buildArgs ++ [input]) Tar _ -> cmd' buildOptions echo [path] buildArgs + + -- RunTest produces a very large amount of (colorised) output; + -- Don't attempt to capture it. + RunTest -> cmd echo [path] buildArgs + _ -> cmd' echo [path] buildArgs -- TODO: Some builders are required only on certain platforms. For example, ===================================== hadrian/src/Settings/Builders/RunTest.hs ===================================== @@ -102,6 +102,7 @@ runTestBuilderArgs = builder RunTest ? do -- TODO: set CABAL_MINIMAL_BUILD/CABAL_PLUGIN_BUILD mconcat [ arg $ "testsuite/driver/runtests.py" , pure [ "--rootdir=" ++ testdir | testdir <- rootdirs ] + , arg "--top", arg (top -/- "testsuite") , arg "-e", arg $ "windows=" ++ show windowsHost , arg "-e", arg $ "darwin=" ++ show osxHost , arg "-e", arg $ "config.local=False" @@ -129,7 +130,6 @@ runTestBuilderArgs = builder RunTest ? do , arg "-e", arg $ "config.ghc_dynamic_by_default=" ++ show hasDynamicByDefault , arg "-e", arg $ "config.ghc_dynamic=" ++ show hasDynamic - , arg "-e", arg $ "config.top=" ++ show (top -/- "testsuite") , arg "-e", arg $ "config.wordsize=" ++ show wordsize , arg "-e", arg $ "config.os=" ++ show os , arg "-e", arg $ "config.arch=" ++ show arch ===================================== libraries/base/Data/OldList.hs ===================================== @@ -547,19 +547,57 @@ intercalate xs xss = concat (intersperse xs xss) -- -- >>> transpose [[10,11],[20],[],[30,31,32]] -- [[10,20,30],[11,31],[32]] -transpose :: [[a]] -> [[a]] -transpose [] = [] -transpose ([] : xss) = transpose xss -transpose ((x:xs) : xss) = (x : hds) : transpose (xs : tls) +transpose :: [[a]] -> [[a]] +transpose [] = [] +transpose ([] : xss) = transpose xss +transpose ((x : xs) : xss) = combine x hds xs tls where -- We tie the calculations of heads and tails together -- to prevent heads from leaking into tails and vice versa. -- unzip makes the selector thunk arrangements we need to -- ensure everything gets cleaned up properly. - (hds, tls) = unzip [(hd, tl) | (hd:tl) <- xss] + (hds, tls) = unzip [(hd, tl) | hd : tl <- xss] + combine y h ys t = (y:h) : transpose (ys:t) + {-# NOINLINE combine #-} + {- Implementation note: + If the bottom part of the function was written as such: + + ``` + transpose ((x : xs) : xss) = (x:hds) : transpose (xs:tls) + where + (hds,tls) = hdstls + hdstls = unzip [(hd, tl) | hd : tl <- xss] + {-# NOINLINE hdstls #-} + ``` + Here are the steps that would take place: + + 1. We allocate a thunk, `hdstls`, representing the result of unzipping. + 2. We allocate selector thunks, `hds` and `tls`, that deconstruct `hdstls`. + 3. Install `hds` as the tail of the result head and pass `xs:tls` to + the recursive call in the result tail. + + Once optimised, this code would amount to: + + ``` + transpose ((x : xs) : xss) = (x:hds) : (let tls = snd hdstls in transpose (xs:tls)) + where + hds = fst hdstls + hdstls = unzip [(hd, tl) | hd : tl <- xss] + {-# NOINLINE hdstls #-} + ``` + + In particular, GHC does not produce the `tls` selector thunk immediately; + rather, it waits to do so until the tail of the result is actually demanded. + So when `hds` is demanded, that does not resolve `snd hdstls`; the tail of the + result keeps `hdstls` alive. + + By writing `combine` and making it NOINLINE, we prevent GHC from delaying + the selector thunk allocation, requiring that `hds` and `tls` are actually + allocated to be passed to `combine`. + -} --- | The 'partition' function takes a predicate a list and returns +-- | The 'partition' function takes a predicate and a list, and returns -- the pair of lists of elements which do and do not satisfy the -- predicate, respectively; i.e., -- ===================================== libraries/base/tests/T18642.hs ===================================== @@ -0,0 +1,27 @@ +{-# LANGUAGE NumericUnderscores #-} +module Main where + +import Data.List (transpose, foldl') +import GHC.Stats +import System.Exit + +thingy :: [[[Int]]] +thingy = [ [[1],[2]], [[1..10^7], [3]]] + +thingy2 :: [[[Int]]] +thingy2 = [ [[1],[2]], [[3], [2..10^7+1]]] + +main = do + htr : ttr <- pure $ transpose thingy + print $ even $ foldl' (+) 0 . head . tail $ htr + + htr2 : ttr2 <- pure $ transpose thingy2 + print $ even $ foldl' (+) 0 . head . tail . head $ ttr2 + + maxLiveBytes <- max_live_bytes <$> getRTSStats + if (maxLiveBytes) < 200_000 + then putStrLn "Test is running in the expected residency limit" + else do + putStrLn $ "Test is running with " <> show maxLiveBytes <> " bytes of residency!" + exitFailure + ===================================== libraries/base/tests/T18642.stdout ===================================== @@ -0,0 +1,3 @@ +True +True +Test is running in the expected residency limit ===================================== libraries/base/tests/all.T ===================================== @@ -260,3 +260,4 @@ test('T16943b', normal, compile_and_run, ['']) test('T17499', [collect_stats('bytes allocated',5)], compile_and_run, ['-O -w']) test('T16643', normal, compile_and_run, ['']) test('clamp', normal, compile_and_run, ['']) +test('T18642', extra_run_opts('+RTS -T -RTS'), compile_and_run, ['-O2']) ===================================== rts/sm/Scav.c ===================================== @@ -435,7 +435,7 @@ scavenge_block (bdescr *bd) saved_eager_promotion = gct->eager_promotion; gct->failed_to_evac = false; - ws = &gct->gens[bd->gen->no]; + ws = &gct->gens[bd->gen_no]; p = bd->u.scan; ===================================== testsuite/driver/runtests.py ===================================== @@ -14,6 +14,7 @@ import tempfile import time import re import traceback +from pathlib import Path # We don't actually need subprocess in runtests.py, but: # * We do need it in testlibs.py @@ -56,6 +57,7 @@ parser = argparse.ArgumentParser(description="GHC's testsuite driver") perf_group = parser.add_mutually_exclusive_group() parser.add_argument("-e", action='append', help="A string to execute from the command line.") +parser.add_argument("--top", type=Path, help="path to top of testsuite/ tree") parser.add_argument("--config-file", action="append", help="config file") parser.add_argument("--config", action='append', help="config field") parser.add_argument("--rootdir", action='append', help="root of tree containing tests (default: .)") @@ -104,6 +106,9 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +if args.top: + config.top = args.top + if args.only: config.only = args.only config.run_only_some_tests = True @@ -277,7 +282,7 @@ testopts_local.x = TestOptions() # if timeout == -1 then we try to calculate a sensible value if config.timeout == -1: - config.timeout = int(read_no_crs(config.top + '/timeout/calibrate.out')) + config.timeout = int(read_no_crs(config.top / 'timeout' / 'calibrate.out')) print('Timeout is ' + str(config.timeout)) print('Known ways: ' + ', '.join(config.other_ways)) ===================================== testsuite/driver/testglobals.py ===================================== @@ -22,7 +22,7 @@ class TestConfig: def __init__(self): # Where the testsuite root is - self.top = '' + self.top = Path('.') # Directories below which to look for test description files (foo.T) self.rootdirs = [] ===================================== testsuite/driver/testlib.py ===================================== @@ -1110,7 +1110,7 @@ def do_test(name: TestName, dst_makefile = in_testdir('Makefile') if src_makefile.exists(): makefile = src_makefile.read_text(encoding='UTF-8') - makefile = re.sub('TOP=.*', 'TOP=' + config.top, makefile, 1) + makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1) dst_makefile.write_text(makefile, encoding='UTF-8') if opts.pre_cmd: ===================================== testsuite/mk/test.mk ===================================== @@ -256,13 +256,13 @@ endif RUNTEST_OPTS += \ --rootdir=. \ --config-file=$(CONFIG) \ + --top="$(TOP_ABS)" \ -e 'config.platform="$(TARGETPLATFORM)"' \ -e 'config.os="$(TargetOS_CPP)"' \ -e 'config.arch="$(TargetARCH_CPP)"' \ -e 'config.wordsize="$(WORDSIZE)"' \ -e 'config.timeout=int($(TIMEOUT)) or config.timeout' \ - -e 'config.exeext="$(exeext)"' \ - -e 'config.top="$(TOP_ABS)"' + -e 'config.exeext="$(exeext)"' # Wrap non-empty program paths in quotes, because they may contain spaces. Do # it here, so we don't have to (and don't forget to do it) in the .T test View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2af9fb1b5b7054302c7883b9d98e03e006cf7089...ba7415574a201a4db0f839ef0906982b751c92e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2af9fb1b5b7054302c7883b9d98e03e006cf7089...ba7415574a201a4db0f839ef0906982b751c92e4 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 Sun Nov 1 16:37:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 11:37:09 -0500 Subject: [Git][ghc/ghc][wip/local-symbols-2] 32 commits: Fix `instance Bounded a => Bounded (Down a)` (#18716) Message-ID: <5f9ee4355e16_7853fb5dd42aa2c26876e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/local-symbols-2 at Glasgow Haskell Compiler / GHC Commits: 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - 42b01d8d by Ben Gamari at 2020-11-01T16:36:45+00:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 285dddec by Ben Gamari at 2020-11-01T16:36:45+00:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - 521cb6fe by Ben Gamari at 2020-11-01T16:36:45+00:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-all-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - d43f05ca by Ben Gamari at 2020-11-01T16:36:45+00:00 Enable -fexpose-all-symbols when debug level >=2 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/FloatIn.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3071f569b9383d58e966929f784278fe38f6eed...d43f05ca139076d33befc5bf41f51e702d38bd54 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3071f569b9383d58e966929f784278fe38f6eed...d43f05ca139076d33befc5bf41f51e702d38bd54 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 Sun Nov 1 16:44:41 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 11:44:41 -0500 Subject: [Git][ghc/ghc][wip/T18854] Document that ccall convention doesn't support varargs Message-ID: <5f9ee5f95e92b_7853fb5f205ca20269981@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18854 at Glasgow Haskell Compiler / GHC Commits: 4e6975d4 by Ben Gamari at 2020-11-01T11:44:25-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 5 changed files: - docs/users_guide/exts/ffi.rst - testsuite/tests/rts/T5423.hs - testsuite/tests/rts/T5423.stdout - testsuite/tests/rts/T5423_c.c - testsuite/tests/rts/T5423_cmm.cmm Changes: ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -83,6 +83,21 @@ For more details on the implementation see the Paper: Last known to be accessible `here `_. +Varargs not supported by ``ccall`` calling convention +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Note that functions requiring varargs arguments are unsupported by the ``ccall`` +calling convention. Foreign imports needing to call such functions should rather +use the ``capi`` convention, giving an explicit signature for the needed +call-pattern. For instance, one could write: :: + + foreign import "capi" "printf" + my_printf :: Ptr CChar -> CInt -> IO () + + printInt :: CInt -> IO () + printInt n = my_printf "printed number %d" n + + .. _ffi-ghcexts: GHC extensions to the FFI Chapter ===================================== testsuite/tests/rts/T5423.hs ===================================== @@ -1,3 +1,5 @@ +-- | Verify that @foreign import prim@ calls with more than 10 arguments +-- are lowered correctly. {-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-} ===================================== testsuite/tests/rts/T5423.stdout ===================================== @@ -1,2 +1,2 @@ -111 112 113 114 115 116 117 118 119 120 +111 112 113 114 115 116 117 118 119 120 120 ===================================== testsuite/tests/rts/T5423_c.c ===================================== @@ -1,6 +1,34 @@ +#include #include void flush_stdout(void) { fflush(stdout); } + +void print_it( + StgWord r1, + StgWord r2, + StgWord r3, + StgWord r4, + StgWord r5, + StgWord r6, + StgWord r7, + StgWord r8, + StgWord r9, + StgWord r10 + ) +{ + printf("%" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word "\n", + r1, r2, r3, r4, r5, + r6, r7, r8, r9, r10); +} ===================================== testsuite/tests/rts/T5423_cmm.cmm ===================================== @@ -10,7 +10,6 @@ test (W_ r1, W_ r9, W_ r10) { - foreign "C" printf("%d %d %d %d %d %d %d %d %d %d\n", - r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); + foreign "C" print_it(r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); return (r10); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e6975d409f2ce29ff29f08dae80aea6b7cf1640 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e6975d409f2ce29ff29f08dae80aea6b7cf1640 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 Sun Nov 1 16:45:06 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 11:45:06 -0500 Subject: [Git][ghc/ghc][wip/backports] 2 commits: [macOS] improved runpath handling Message-ID: <5f9ee612e3051_7853fb5f205ca20270853@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/backports at Glasgow Haskell Compiler / GHC Commits: 7644d85c by Moritz Angermann at 2020-10-30T10:59:36-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) (cherry picked from commit 89a753308deb2c7ed012e875e220b1d39e1798d8) Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3d7f5ec8 by Alan Zimmerman at 2020-11-01T11:45:02-05:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' (cherry picked from commit c15b5f25ad54164c951e797ecbd10d0df1cf4ba6) - - - - - 19 changed files: - aclocal.m4 - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Runtime/Linker.hs - compiler/GHC/Settings.hs - compiler/GHC/Settings/IO.hs - compiler/GHC/SysTools.hs - compiler/GHC/SysTools/Tasks.hs - configure.ac - docs/users_guide/phases.rst - hadrian/cfg/system.config.in - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - includes/ghc.mk - mk/config.mk.in - testsuite/tests/rts/all.T Changes: ===================================== aclocal.m4 ===================================== @@ -586,6 +586,18 @@ AC_DEFUN([FP_SETTINGS], else SettingsOptCommand="$OptCmd" fi + if test -z "$OtoolCmd" + then + SettingsOtoolCommand="otool" + else + SettingsOtoolCommand="$OtoolCmd" + fi + if test -z "$InstallNameToolCmd" + then + SettingsInstallNameToolCommand="install_name_tool" + else + SettingsInstallNameToolCommand="$InstallNameToolCmd" + fi SettingsCCompilerFlags="$CONF_CC_OPTS_STAGE2" SettingsCxxCompilerFlags="$CONF_CXX_OPTS_STAGE2" SettingsCCompilerLinkFlags="$CONF_GCC_LINKER_OPTS_STAGE2" @@ -604,6 +616,8 @@ AC_DEFUN([FP_SETTINGS], AC_SUBST(SettingsMergeObjectsFlags) AC_SUBST(SettingsArCommand) AC_SUBST(SettingsRanlibCommand) + AC_SUBST(SettingsOtoolCommand) + AC_SUBST(SettingsInstallNameToolCommand) AC_SUBST(SettingsDllWrapCommand) AC_SUBST(SettingsWindresCommand) AC_SUBST(SettingsLibtoolCommand) ===================================== compiler/GHC/Driver/Pipeline.hs ===================================== @@ -391,7 +391,56 @@ compileEmptyStub dflags hsc_env basename location mod_name = do -- --------------------------------------------------------------------------- -- Link - +-- +-- Note [Dynamic linking on macOS] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Since macOS Sierra (10.14), the dynamic system linker enforces +-- a limit on the Load Commands. Specifically the Load Command Size +-- Limit is at 32K (32768). The Load Commands contain the install +-- name, dependencies, runpaths, and a few other commands. We however +-- only have control over the install name, dependencies and runpaths. +-- +-- The install name is the name by which this library will be +-- referenced. This is such that we do not need to bake in the full +-- absolute location of the library, and can move the library around. +-- +-- The dependency commands contain the install names from of referenced +-- libraries. Thus if a libraries install name is @rpath/libHS...dylib, +-- that will end up as the dependency. +-- +-- Finally we have the runpaths, which informs the linker about the +-- directories to search for the referenced dependencies. +-- +-- The system linker can do recursive linking, however using only the +-- direct dependencies conflicts with ghc's ability to inline across +-- packages, and as such would end up with unresolved symbols. +-- +-- Thus we will pass the full dependency closure to the linker, and then +-- ask the linker to remove any unused dynamic libraries (-dead_strip_dylibs). +-- +-- We still need to add the relevant runpaths, for the dynamic linker to +-- lookup the referenced libraries though. The linker (ld64) does not +-- have any option to dead strip runpaths; which makes sense as runpaths +-- can be used for dependencies of dependencies as well. +-- +-- The solution we then take in GHC is to not pass any runpaths to the +-- linker at link time, but inject them after the linking. For this to +-- work we'll need to ask the linker to create enough space in the header +-- to add more runpaths after the linking (-headerpad 8000). +-- +-- After the library has been linked by $LD (usually ld64), we will use +-- otool to inspect the libraries left over after dead stripping, compute +-- the relevant runpaths, and inject them into the linked product using +-- the install_name_tool command. +-- +-- This strategy should produce the smallest possible set of load commands +-- while still retaining some form of relocatability via runpaths. +-- +-- The only way I can see to reduce the load command size further would be +-- by shortening the library names, or start putting libraries into the same +-- folders, such that one runpath would be sufficient for multiple/all +-- libraries. link :: GhcLink -- interactive or batch -> DynFlags -- dynamic flags -> Bool -- attempt linking in batch mode? @@ -1766,9 +1815,12 @@ linkBinary' staticLink dflags o_files dep_units = do rc_objs <- maybeCreateManifest dflags output_fn - let link = if staticLink - then GHC.SysTools.runLibtool - else GHC.SysTools.runLink + let link dflags args | staticLink = GHC.SysTools.runLibtool dflags args + | platformOS platform == OSDarwin + = GHC.SysTools.runLink dflags args >> GHC.SysTools.runInjectRPaths dflags pkg_lib_paths output_fn + | otherwise + = GHC.SysTools.runLink dflags args + link dflags ( map GHC.SysTools.Option verbFlags ++ [ GHC.SysTools.Option "-o" @@ -1835,7 +1887,13 @@ linkBinary' staticLink dflags o_files dep_units = do ++ pkg_link_opts ++ pkg_framework_opts ++ (if platformOS platform == OSDarwin - then [ "-Wl,-dead_strip_dylibs" ] + -- dead_strip_dylibs, will remove unused dylibs, and thus save + -- space in the load commands. The -headerpad is necessary so + -- that we can inject more @rpath's later for the left over + -- libraries during runInjectRpaths phase. + -- + -- See Note [Dynamic linking on macOS]. + then [ "-Wl,-dead_strip_dylibs", "-Wl,-headerpad,8000" ] else []) )) ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -147,8 +147,8 @@ module GHC.Driver.Session ( versionedAppDir, versionedFilePath, extraGccViaCFlags, globalPackageDatabasePath, pgm_L, pgm_P, pgm_F, pgm_c, pgm_a, pgm_l, pgm_lm, pgm_dll, pgm_T, - pgm_windres, pgm_libtool, pgm_ar, pgm_ranlib, pgm_lo, pgm_lc, - pgm_lcc, pgm_i, + pgm_windres, pgm_libtool, pgm_ar, pgm_otool, pgm_install_name_tool, + pgm_ranlib, pgm_lo, pgm_lc, pgm_lcc, pgm_i, opt_L, opt_P, opt_F, opt_c, opt_cxx, opt_a, opt_l, opt_lm, opt_i, opt_P_signature, opt_windres, opt_lo, opt_lc, opt_lcc, @@ -950,6 +950,10 @@ pgm_lcc :: DynFlags -> (String,[Option]) pgm_lcc dflags = toolSettings_pgm_lcc $ toolSettings dflags pgm_ar :: DynFlags -> String pgm_ar dflags = toolSettings_pgm_ar $ toolSettings dflags +pgm_otool :: DynFlags -> String +pgm_otool dflags = toolSettings_pgm_otool $ toolSettings dflags +pgm_install_name_tool :: DynFlags -> String +pgm_install_name_tool dflags = toolSettings_pgm_install_name_tool $ toolSettings dflags pgm_ranlib :: DynFlags -> String pgm_ranlib dflags = toolSettings_pgm_ranlib $ toolSettings dflags pgm_lo :: DynFlags -> (String,[Option]) @@ -2393,6 +2397,10 @@ dynamic_flags_deps = [ $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_libtool = f } , make_ord_flag defFlag "pgmar" $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ar = f } + , make_ord_flag defFlag "pgmotool" + $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_otool = f} + , make_ord_flag defFlag "pgminstall_name_tool" + $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_install_name_tool = f} , make_ord_flag defFlag "pgmranlib" $ hasArg $ \f -> alterToolSettings $ \s -> s { toolSettings_pgm_ranlib = f } @@ -3903,7 +3911,6 @@ defaultFlags settings Opt_OmitYields, Opt_PrintBindContents, Opt_ProfCountEntries, - Opt_RPath, Opt_SharedImplib, Opt_SimplPreInlining, Opt_VersionMacros @@ -3914,6 +3921,8 @@ defaultFlags settings ++ default_PIC platform + ++ default_RPath platform + ++ concatMap (wayGeneralFlags platform) (defaultWays settings) ++ validHoleFitDefaults @@ -3954,6 +3963,29 @@ default_PIC platform = -- information. _ -> [] + +-- We usually want to use RPath, except on macOS (OSDarwin). On recent macOS +-- versions the number of load commands we can embed in a dynamic library is +-- restricted. Hence since b592bd98ff2 we rely on -dead_strip_dylib to only +-- link the needed dylibs instead of linking the full dependency closure. +-- +-- If we split the library linking into injecting -rpath and -l @rpath/... +-- components, we will reduce the number of libraries we link, however we will +-- still inject one -rpath entry for each library, independent of their use. +-- That is, we even inject -rpath values for libraries that we dead_strip in +-- the end. As such we can run afoul of the load command size limit simply +-- by polluting the load commands with RPATH entries. +-- +-- Thus, we disable Opt_RPath by default on OSDarwin. The savvy user can always +-- enable it with -use-rpath if they so wish. +-- +-- See Note [Dynamic linking on macOS] + +default_RPath :: Platform -> [GeneralFlag] +default_RPath platform | platformOS platform == OSDarwin = [] +default_RPath _ = [Opt_RPath] + + -- General flags that are switched on/off when other general flags are switched -- on impliedGFlags :: [(GeneralFlag, TurnOnFlag, GeneralFlag)] ===================================== compiler/GHC/Parser.y ===================================== @@ -1961,17 +1961,18 @@ type :: { LHsType GhcPs } [mu AnnRarrow $2] } | btype mult '->' ctype {% hintLinear (getLoc $2) - >> ams $1 [mj AnnMult $2,mu AnnRarrow $3] -- See Note [GADT decl discards annotations] - >> ams (sLL $1 $> $ HsFunTy noExtField ((unLoc $2) (toUnicode $3)) $1 $4) - [mj AnnMult $2,mu AnnRarrow $3] } + >> let (arr, ann) = (unLoc $2) (toUnicode $3) + in (ams $1 [ann,mu AnnRarrow $3] -- See Note [GADT decl discards annotations] + >> ams (sLL $1 $> $ HsFunTy noExtField arr $1 $4) + [ann,mu AnnRarrow $3]) } | btype '->.' ctype {% hintLinear (getLoc $2) >> ams $1 [mu AnnLollyU $2] -- See Note [GADT decl discards annotations] >> ams (sLL $1 $> $ HsFunTy noExtField (HsLinearArrow UnicodeSyntax) $1 $3) [mu AnnLollyU $2] } -mult :: { Located (IsUnicodeSyntax -> HsArrow GhcPs) } - : PREFIX_PERCENT atype { sLL $1 $> (\u -> mkMultTy u $2) } +mult :: { Located (IsUnicodeSyntax -> (HsArrow GhcPs, AddAnn)) } + : PREFIX_PERCENT atype { sLL $1 $> (\u -> mkMultTy u $1 $2) } btype :: { LHsType GhcPs } : tyapps {% mergeOps (unLoc $1) } ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -302,7 +302,7 @@ data AnnKeywordId | AnnMdo | AnnMinus -- ^ '-' | AnnModule - | AnnMult -- ^ '%1' + | AnnPercentOne -- ^ '%1' -- for HsLinearArrow | AnnNewtype | AnnName -- ^ where a name loses its location in the AST, this carries it | AnnOf @@ -319,6 +319,7 @@ data AnnKeywordId | AnnDollarDollar -- ^ prefix '$$' -- TemplateHaskell | AnnPackageName | AnnPattern + | AnnPercent -- ^ '%' -- for HsExplicitMult | AnnProc | AnnQualified | AnnRarrow -- ^ '->' ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -3069,9 +3069,10 @@ mkLHsOpTy x op y = let loc = getLoc x `combineSrcSpans` getLoc op `combineSrcSpans` getLoc y in L loc (mkHsOpTy x op y) -mkMultTy :: IsUnicodeSyntax -> LHsType GhcPs -> HsArrow GhcPs -mkMultTy u (L _ (HsTyLit _ (HsNumTy _ 1))) = HsLinearArrow u -mkMultTy u t = HsExplicitMult u t +mkMultTy :: IsUnicodeSyntax -> Located Token -> LHsType GhcPs -> (HsArrow GhcPs, AddAnn) +mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy _ 1))) + = (HsLinearArrow u, AddAnn AnnPercentOne (combineLocs tok t)) +mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok)) ----------------------------------------------------------------------------- -- Token symbols ===================================== compiler/GHC/Runtime/Linker.hs ===================================== @@ -927,20 +927,22 @@ dynLoadObjs hsc_env pls at PersistentLinkerState{..} objs = do ldInputs = concatMap (\l -> [ Option ("-l" ++ l) ]) (nub $ snd <$> temp_sos) - ++ concatMap (\lp -> [ Option ("-L" ++ lp) - , Option "-Xlinker" - , Option "-rpath" - , Option "-Xlinker" - , Option lp ]) + ++ concatMap (\lp -> Option ("-L" ++ lp) + : if gopt Opt_RPath dflags + then [ Option "-Xlinker" + , Option "-rpath" + , Option "-Xlinker" + , Option lp ] + else []) (nub $ fst <$> temp_sos) ++ concatMap - (\lp -> - [ Option ("-L" ++ lp) - , Option "-Xlinker" - , Option "-rpath" - , Option "-Xlinker" - , Option lp - ]) + (\lp -> Option ("-L" ++ lp) + : if gopt Opt_RPath dflags + then [ Option "-Xlinker" + , Option "-rpath" + , Option "-Xlinker" + , Option lp ] + else []) minus_big_ls -- See Note [-Xlinker -rpath vs -Wl,-rpath] ++ map (\l -> Option ("-l" ++ l)) minus_ls, ===================================== compiler/GHC/Settings.hs ===================================== @@ -36,6 +36,8 @@ module GHC.Settings , sPgm_windres , sPgm_libtool , sPgm_ar + , sPgm_otool + , sPgm_install_name_tool , sPgm_ranlib , sPgm_lo , sPgm_lc @@ -109,6 +111,8 @@ data ToolSettings = ToolSettings , toolSettings_pgm_windres :: String , toolSettings_pgm_libtool :: String , toolSettings_pgm_ar :: String + , toolSettings_pgm_otool :: String + , toolSettings_pgm_install_name_tool :: String , toolSettings_pgm_ranlib :: String , -- | LLVM: opt llvm optimiser toolSettings_pgm_lo :: (String, [Option]) @@ -222,6 +226,10 @@ sPgm_libtool :: Settings -> String sPgm_libtool = toolSettings_pgm_libtool . sToolSettings sPgm_ar :: Settings -> String sPgm_ar = toolSettings_pgm_ar . sToolSettings +sPgm_otool :: Settings -> String +sPgm_otool = toolSettings_pgm_otool . sToolSettings +sPgm_install_name_tool :: Settings -> String +sPgm_install_name_tool = toolSettings_pgm_install_name_tool . sToolSettings sPgm_ranlib :: Settings -> String sPgm_ranlib = toolSettings_pgm_ranlib . sToolSettings sPgm_lo :: Settings -> (String, [Option]) ===================================== compiler/GHC/Settings/IO.hs ===================================== @@ -116,6 +116,8 @@ initSettings top_dir = do windres_path <- getToolSetting "windres command" libtool_path <- getToolSetting "libtool command" ar_path <- getToolSetting "ar command" + otool_path <- getToolSetting "otool command" + install_name_tool_path <- getToolSetting "install_name_tool command" ranlib_path <- getToolSetting "ranlib command" -- TODO this side-effect doesn't belong here. Reading and parsing the settings @@ -192,6 +194,8 @@ initSettings top_dir = do , toolSettings_pgm_windres = windres_path , toolSettings_pgm_libtool = libtool_path , toolSettings_pgm_ar = ar_path + , toolSettings_pgm_otool = otool_path + , toolSettings_pgm_install_name_tool = install_name_tool_path , toolSettings_pgm_ranlib = ranlib_path , toolSettings_pgm_lo = (lo_prog,[]) , toolSettings_pgm_lc = (lc_prog,[]) ===================================== compiler/GHC/SysTools.hs ===================================== @@ -254,7 +254,10 @@ linkDynLib dflags0 o_files dep_packages | ( osElfTarget (platformOS (targetPlatform dflags)) || osMachOTarget (platformOS (targetPlatform dflags)) ) && dynLibLoader dflags == SystemDependent && - WayDyn `Set.member` ways dflags + -- Only if we want dynamic libraries + WayDyn `Set.member` ways dflags && + -- Only use RPath if we explicitly asked for it + gopt Opt_RPath dflags = ["-L" ++ l, "-Xlinker", "-rpath", "-Xlinker", l] -- See Note [-Xlinker -rpath vs -Wl,-rpath] | otherwise = ["-L" ++ l] @@ -379,8 +382,15 @@ linkDynLib dflags0 o_files dep_packages ++ map Option pkg_lib_path_opts ++ map Option pkg_link_opts ++ map Option pkg_framework_opts - ++ [ Option "-Wl,-dead_strip_dylibs" ] + -- dead_strip_dylibs, will remove unused dylibs, and thus save + -- space in the load commands. The -headerpad is necessary so + -- that we can inject more @rpath's later for the leftover + -- libraries in the runInjectRpaths phase below. + -- + -- See Note [Dynamic linking on macOS] + ++ [ Option "-Wl,-dead_strip_dylibs", Option "-Wl,-headerpad,8000" ] ) + runInjectRPaths dflags pkg_lib_paths output_fn _ -> do ------------------------------------------------------------------- -- Making a DSO ===================================== compiler/GHC/SysTools/Tasks.hs ===================================== @@ -28,6 +28,10 @@ import GHC.CmmToLlvm.Base (LlvmVersion, llvmVersionStr, supportedLlvmVersion, pa import GHC.SysTools.Process import GHC.SysTools.Info +import Control.Monad (join, forM, filterM) +import System.Directory (doesFileExist) +import System.FilePath (()) + {- ************************************************************************ * * @@ -237,6 +241,41 @@ figureLlvmVersion dflags = traceToolCommand dflags "llc" $ do return Nothing) +-- | On macOS we rely on the linkers @-dead_strip_dylibs@ flag to remove unused +-- libraries from the dynamic library. We do this to reduce the number of load +-- commands that end up in the dylib, and has been limited to 32K (32768) since +-- macOS Sierra (10.14). +-- +-- @-dead_strip_dylibs@ does not dead strip @-rpath@ entries, as such passing +-- @-l@ and @-rpath@ to the linker will result in the unnecesasry libraries not +-- being included in the load commands, however the @-rpath@ entries are all +-- forced to be included. This can lead to 100s of @-rpath@ entries being +-- included when only a handful of libraries end up being truely linked. +-- +-- Thus after building the library, we run a fixup phase where we inject the +-- @-rpath@ for each found library (in the given library search paths) into the +-- dynamic library through @-add_rpath at . +-- +-- See Note [Dynamic linking on macOS] +runInjectRPaths :: DynFlags -> [FilePath] -> FilePath -> IO () +runInjectRPaths dflags lib_paths dylib = do + info <- lines <$> askOtool dflags Nothing [Option "-L", Option dylib] + -- filter the output for only the libraries. And then drop the @rpath prefix. + let libs = fmap (drop 7) $ filter (isPrefixOf "@rpath") $ fmap (head.words) $ info + -- find any pre-existing LC_PATH items + info <- fmap words.lines <$> askOtool dflags Nothing [Option "-l", Option dylib] + let paths = concatMap f info + where f ("path":p:_) = [p] + f _ = [] + lib_paths' = [ p | p <- lib_paths, not (p `elem` paths) ] + -- only find those rpaths, that aren't already in the library. + rpaths <- nub.sort.join <$> forM libs (\f -> filterM (\l -> doesFileExist (l f)) lib_paths') + -- inject the rpaths + case rpaths of + [] -> return () + _ -> runInstallNameTool dflags $ map Option $ "-add_rpath":(intersperse "-add_rpath" rpaths) ++ [dylib] + + runLink :: DynFlags -> [Option] -> IO () runLink dflags args = traceToolCommand dflags "linker" $ do -- See Note [Run-time linker info] @@ -329,6 +368,17 @@ runAr dflags cwd args = traceToolCommand dflags "ar" $ do let ar = pgm_ar dflags runSomethingFiltered dflags id "Ar" ar args cwd Nothing +askOtool :: DynFlags -> Maybe FilePath -> [Option] -> IO String +askOtool dflags mb_cwd args = do + let otool = pgm_otool dflags + runSomethingWith dflags "otool" otool args $ \real_args -> + readCreateProcessWithExitCode' (proc otool real_args){ cwd = mb_cwd } + +runInstallNameTool :: DynFlags -> [Option] -> IO () +runInstallNameTool dflags args = do + let tool = pgm_install_name_tool dflags + runSomethingFiltered dflags id "Install Name Tool" tool args Nothing Nothing + runRanlib :: DynFlags -> [Option] -> IO () runRanlib dflags args = traceToolCommand dflags "ranlib" $ do let ranlib = pgm_ranlib dflags ===================================== configure.ac ===================================== @@ -696,6 +696,18 @@ else fi AC_SUBST([LibtoolCmd]) +dnl ** Which otool to use on macOS +dnl -------------------------------------------------------------- +AC_CHECK_TARGET_TOOL([OTOOL], [otool]) +OtoolCmd="$OTOOL" +AC_SUBST(OtoolCmd) + +dnl ** Which install_name_tool to use on macOS +dnl -------------------------------------------------------------- +AC_CHECK_TARGET_TOOL([INSTALL_NAME_TOOL], [install_name_tool]) +InstallNameToolCmd="$INSTALL_NAME_TOOL" +AC_SUBST(InstallNameToolCmd) + # Here is where we re-target which specific version of the LLVM # tools we are looking for. In the past, GHC supported a number of # versions of LLVM simultaneously, but that stopped working around @@ -1519,6 +1531,8 @@ echo "\ libtool : $LibtoolCmd objdump : $ObjdumpCmd ranlib : $RanlibCmd + otool : $OtoolCmd + install_name_tool : $InstallNameToolCmd windres : $WindresCmd dllwrap : $DllWrapCmd genlib : $GenlibCmd ===================================== docs/users_guide/phases.rst ===================================== @@ -95,6 +95,24 @@ given compilation phase: Use ⟨cmd⟩ as the pre-processor (with :ghc-flag:`-F` only). +.. ghc-flag:: -pgmotool ⟨cmd⟩ + :shortdesc: Use ⟨cmd⟩ as the program to inspect mach-o dylibs on macOS + :type: dynamic + :category: phase-programs + + Use ⟨cmd⟩ as the program to inspect mach-o dynamic libraries and + executables to read the dynamic library dependencies. We will compute + the necessary ``runpath``s to embed for the dependencies based on the + result of the ``otool`` call. + +.. ghc-flag:: -pgminstall_name_tool ⟨cmd⟩ + :shortdesc: Use ⟨cmd⟩ as the program to inject ``runpath`` into mach-o dylibs on macOS + :type: dynamic + :category: phase-programs + + Use ⟨cmd⟩ as the program to inject ``runpath``s into mach-o dynamic + libraries and executables. As detected by the ``otool`` call. + .. ghc-flag:: -pgmwindres ⟨cmd⟩ :shortdesc: Use ⟨cmd⟩ as the program for embedding manifests on Windows. :type: dynamic ===================================== hadrian/cfg/system.config.in ===================================== @@ -149,6 +149,8 @@ settings-merge-objects-command = @SettingsMergeObjectsCommand@ settings-merge-objects-flags = @SettingsMergeObjectsFlags@ settings-ar-command = @SettingsArCommand@ settings-ranlib-command = @SettingsRanlibCommand@ +settings-otool-command = @SettingsOtoolCommand@ +settings-install_name_tool-command = @SettingsInstallNameToolCommand@ settings-dll-wrap-command = @SettingsDllWrapCommand@ settings-windres-command = @SettingsWindresCommand@ settings-libtool-command = @SettingsLibtoolCommand@ ===================================== hadrian/src/Oracles/Setting.hs ===================================== @@ -114,6 +114,8 @@ data SettingsFileSetting | SettingsFileSetting_MergeObjectsFlags | SettingsFileSetting_ArCommand | SettingsFileSetting_RanlibCommand + | SettingsFileSetting_OtoolCommand + | SettingsFileSetting_InstallNameToolCommand | SettingsFileSetting_DllWrapCommand | SettingsFileSetting_WindresCommand | SettingsFileSetting_LibtoolCommand @@ -199,6 +201,8 @@ settingsFileSetting key = lookupValueOrError configFile $ case key of SettingsFileSetting_MergeObjectsFlags -> "settings-merge-objects-flags" SettingsFileSetting_ArCommand -> "settings-ar-command" SettingsFileSetting_RanlibCommand -> "settings-ranlib-command" + SettingsFileSetting_OtoolCommand -> "settings-otool-command" + SettingsFileSetting_InstallNameToolCommand -> "settings-install_name_tool-command" SettingsFileSetting_DllWrapCommand -> "settings-dll-wrap-command" SettingsFileSetting_WindresCommand -> "settings-windres-command" SettingsFileSetting_LibtoolCommand -> "settings-libtool-command" ===================================== hadrian/src/Rules/Generate.hs ===================================== @@ -298,6 +298,8 @@ generateSettings = do , ("ar flags", expr $ lookupValueOrError configFile "ar-args") , ("ar supports at file", expr $ yesNo <$> flag ArSupportsAtFile) , ("ranlib command", expr $ settingsFileSetting SettingsFileSetting_RanlibCommand) + , ("otool command", expr $ settingsFileSetting SettingsFileSetting_OtoolCommand) + , ("install_name_tool command", expr $ settingsFileSetting SettingsFileSetting_InstallNameToolCommand) , ("touch command", expr $ settingsFileSetting SettingsFileSetting_TouchCommand) , ("dllwrap command", expr $ settingsFileSetting SettingsFileSetting_DllWrapCommand) , ("windres command", expr $ settingsFileSetting SettingsFileSetting_WindresCommand) ===================================== includes/ghc.mk ===================================== @@ -229,6 +229,8 @@ $(includes_SETTINGS) : includes/Makefile | $$(dir $$@)/. @echo ',("ar flags", "$(ArArgs)")' >> $@ @echo ',("ar supports at file", "$(ArSupportsAtFile)")' >> $@ @echo ',("ranlib command", "$(SettingsRanlibCommand)")' >> $@ + @echo ',("otool command", "$(SettingsOtoolCommand)")' >> $@ + @echo ',("install_name_tool command", "$(SettingsInstallNameToolCommand)")' >> $@ @echo ',("touch command", "$(SettingsTouchCommand)")' >> $@ @echo ',("dllwrap command", "$(SettingsDllWrapCommand)")' >> $@ @echo ',("windres command", "$(SettingsWindresCommand)")' >> $@ ===================================== mk/config.mk.in ===================================== @@ -503,6 +503,8 @@ SettingsLdFlags = @SettingsLdFlags@ SettingsMergeObjectsCommand = @SettingsMergeObjectsCommand@ SettingsMergeObjectsFlags = @SettingsMergeObjectsFlags@ SettingsArCommand = @SettingsArCommand@ +SettingsOtoolCommand = @SettingsOtoolCommand@ +SettingsInstallNameToolCommand = @SettingsInstallNameToolCommand@ SettingsRanlibCommand = @SettingsRanlibCommand@ SettingsDllWrapCommand = @SettingsDllWrapCommand@ SettingsWindresCommand = @SettingsWindresCommand@ ===================================== testsuite/tests/rts/all.T ===================================== @@ -406,7 +406,7 @@ test('T16514', unless(opsys('mingw32'), skip), compile_and_run, ['T16514_c.cpp - test('test-zeroongc', extra_run_opts('-DZ'), compile_and_run, ['-debug']) test('T13676', - [when(opsys('darwin') or opsys('mingw32'), expect_broken(17447)), + [when(opsys('mingw32'), expect_broken(17447)), extra_files(['T13676.hs'])], ghci_script, ['T13676.script']) test('InitEventLogging', View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bfacd220c208c2e3e4975092ac1b917b744d85dd...3d7f5ec8232d9053b192cb94b19c5d5e85bc46f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bfacd220c208c2e3e4975092ac1b917b744d85dd...3d7f5ec8232d9053b192cb94b19c5d5e85bc46f4 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 Sun Nov 1 17:53:27 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 12:53:27 -0500 Subject: [Git][ghc/ghc][wip/T17609] 2 commits: nativeGen: Deduplicate DWARF strings Message-ID: <5f9ef6174a59d_7853fb64024152c2766b4@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: 07ff759c by Ben Gamari at 2020-11-01T12:52:46-05:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - b48a56f1 by Ben Gamari at 2020-11-01T12:52:52-05:00 Add Note cross-reference for unique tag allocations - - - - - 5 changed files: - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Builtin/Uniques.hs ===================================== @@ -296,6 +296,9 @@ getTupleDataConName boxity n = * * ************************************************************************ +Note [Unique tag allocation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + Allocation of unique supply characters: v,t,u : for renumbering value-, type- and usage- vars. B: builtin ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -12,6 +12,7 @@ import GHC.Cmm.DebugBlock import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Platform +import GHC.Types.SrcLoc import GHC.Types.Unique import GHC.Types.Unique.Supply @@ -46,11 +47,12 @@ dwarfGen config modLoc us blocks = do compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + producer = dwarfStringFromString $ cProjectName ++ " " ++ cProjectVersion dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) - , dwName = fromMaybe "" (ml_hs_file modLoc) - , dwCompDir = addTrailingPathSeparator compPath - , dwProducer = cProjectName ++ " " ++ cProjectVersion + , dwName = dwarfStringFromString $ fromMaybe "" (ml_hs_file modLoc) + , dwCompDir = dwarfStringFromString $ addTrailingPathSeparator compPath + , dwProducer = producer , dwLowLabel = lowLabel , dwHighLabel = highLabel , dwLineLabel = dwarfLineLabel @@ -76,6 +78,9 @@ dwarfGen config modLoc us blocks = do , compileUnitFooter platform unitU ] + -- .debug_str section: Strings + let stringsSct = dwarfStringsSection (dwarfInfoStrings dwarfUnit) + -- .debug_line section: Generated mainly by the assembler, but we -- need to label it let lineSct = dwarfLineSection platform $$ @@ -92,7 +97,7 @@ dwarfGen config modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection platform $$ pprDwarfARanges platform aranges' unitU - return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') + return (infoSct $$ stringsSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. -- With split sections, each proc needs its own entry, since they may get @@ -177,7 +182,7 @@ parent, B. procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) - , dwName = case dblSourceTick prc of + , dwName = dwarfStringFromString $ case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) , dwLabel = dblCLabel prc @@ -208,7 +213,13 @@ blockToDwarf blk | otherwise = Nothing -- block was optimized out tickToDwarf :: Tickish () -> [DwarfInfo] -tickToDwarf (SourceNote ss _) = [DwarfSrcNote ss] +tickToDwarf (SourceNote ss _) = + [DwarfSrcNote { dwSpanFile = dwarfStringFromFastString (srcSpanFile ss) + , dwSpanStartLine = srcSpanStartLine ss + , dwSpanStartCol = srcSpanStartCol ss + , dwSpanEndLine = srcSpanEndLine ss + , dwSpanEndCol = srcSpanEndCol ss + }] tickToDwarf _ = [] -- | Generates the data for the debug frame section, which encodes the ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -86,12 +86,14 @@ dW_CHILDREN_no, dW_CHILDREN_yes :: Word8 dW_CHILDREN_no = 0 dW_CHILDREN_yes = 1 -dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, dW_FORM_string, dW_FORM_flag, +dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, + dW_FORM_strp,dW_FORM_string, dW_FORM_flag, dW_FORM_block1, dW_FORM_ref4, dW_FORM_ref_addr, dW_FORM_flag_present :: Word dW_FORM_addr = 0x01 dW_FORM_data2 = 0x05 dW_FORM_data4 = 0x06 dW_FORM_string = 0x08 +dW_FORM_strp = 0x0e dW_FORM_flag = 0x0c dW_FORM_block1 = 0x0a dW_FORM_ref_addr = 0x10 ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -2,12 +2,19 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RecordWildCards #-} module GHC.CmmToAsm.Dwarf.Types ( -- * Dwarf information DwarfInfo(..) , pprDwarfInfo , pprAbbrevDecls + , dwarfInfoStrings + -- * Dwarf Strings section + , DwarfString + , dwarfStringsSection + , dwarfStringFromString + , dwarfStringFromFastString -- * Dwarf address range table , DwarfARange(..) , pprDwarfARanges @@ -32,18 +39,15 @@ import GHC.Prelude import GHC.Cmm.DebugBlock import GHC.Cmm.CLabel import GHC.Cmm.Expr ( GlobalReg(..) ) -import GHC.Utils.Encoding import GHC.Data.FastString import GHC.Utils.Outputable import GHC.Platform import GHC.Types.Unique +import GHC.Types.Unique.Set import GHC.Platform.Reg -import GHC.Types.SrcLoc -import GHC.Utils.Misc import GHC.CmmToAsm.Dwarf.Constants -import qualified Data.ByteString as BS import qualified Control.Monad.Trans.State.Strict as S import Control.Monad (zipWithM, join) import Data.Bits @@ -53,18 +57,49 @@ import Data.Char import GHC.Platform.Regs +-- | A string in the DWARF @.debug_str@ section. +newtype DwarfString = DwarfString FastString + +instance Uniquable DwarfString where + getUnique (DwarfString fs) = getUnique fs + +dwarfStringFromString :: String -> DwarfString +dwarfStringFromString = dwarfStringFromFastString . fsLit + +dwarfStringFromFastString :: FastString -> DwarfString +dwarfStringFromFastString = DwarfString + +dwarfStringSymbol :: DwarfString -> SDoc +dwarfStringSymbol (DwarfString fs) = + text "_dbgfs_" <> ppr (getKey $ getUnique fs) + +debugStrSection :: SDoc +debugStrSection = text ".debug_str" + +pprDwarfString :: Platform -> DwarfString -> SDoc +pprDwarfString plat s = + sectionOffset plat (dwarfStringSymbol s) debugStrSection + +dwarfStringsSection :: UniqSet DwarfString -> SDoc +dwarfStringsSection xs = + text ".section" <+> debugStrSection $$ vcat (map string $ nonDetEltsUniqSet xs) + where + string :: DwarfString -> SDoc + string dstr@(DwarfString fstr) = + dwarfStringSymbol dstr <> colon $$ pprFastString fstr + -- | Individual dwarf records. Each one will be encoded as an entry in -- the @.debug_info@ section. data DwarfInfo = DwarfCompileUnit { dwChildren :: [DwarfInfo] - , dwName :: String - , dwProducer :: String - , dwCompDir :: String + , dwName :: DwarfString + , dwProducer :: DwarfString + , dwCompDir :: DwarfString , dwLowLabel :: CLabel , dwHighLabel :: CLabel , dwLineLabel :: PtrString } | DwarfSubprogram { dwChildren :: [DwarfInfo] - , dwName :: String + , dwName :: DwarfString , dwLabel :: CLabel , dwParent :: Maybe CLabel -- ^ label of DIE belonging to the parent tick @@ -73,9 +108,23 @@ data DwarfInfo , dwLabel :: CLabel , dwMarker :: Maybe CLabel } - | DwarfSrcNote { dwSrcSpan :: RealSrcSpan + | DwarfSrcNote { dwSpanFile :: !DwarfString + , dwSpanStartLine :: !Int + , dwSpanStartCol :: !Int + , dwSpanEndLine :: !Int + , dwSpanEndCol :: !Int } +-- | 'DwarfStrings' mentioned by the given 'DwarfInfo'. +dwarfInfoStrings :: DwarfInfo -> UniqSet DwarfString +dwarfInfoStrings dwinfo = + case dwinfo of + DwarfCompileUnit {..} -> mkUniqSet [dwName, dwProducer, dwCompDir] `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfSubprogram {..} -> unitUniqSet dwName `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfBlock {..} -> foldMap dwarfInfoStrings dwChildren + DwarfSrcNote {..} -> unitUniqSet dwSpanFile + + -- | Abbreviation codes used for encoding above records in the -- @.debug_info@ section. data DwarfAbbrev @@ -138,7 +187,7 @@ pprAbbrevDecls platform haveDebugLine = , (dW_AT_high_pc, dW_FORM_addr) ] $$ mkAbbrev DwAbbrGhcSrcNote dW_TAG_ghc_src_note dW_CHILDREN_no - [ (dW_AT_ghc_span_file, dW_FORM_string) + [ (dW_AT_ghc_span_file, dW_FORM_strp) , (dW_AT_ghc_span_start_line, dW_FORM_data4) , (dW_AT_ghc_span_start_col, dW_FORM_data2) , (dW_AT_ghc_span_end_line, dW_FORM_data4) @@ -174,10 +223,10 @@ pprDwarfInfoOpen :: Platform -> Bool -> DwarfInfo -> SDoc pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowLabel highLabel lineLbl) = pprAbbrev DwAbbrCompileUnit - $$ pprString name - $$ pprString producer + $$ pprDwarfString platform name + $$ pprDwarfString platform producer $$ pprData4 dW_LANG_Haskell - $$ pprString compDir + $$ pprDwarfString platform compDir $$ pprWord platform (pdoc platform lowLabel) $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc @@ -186,7 +235,7 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = pdoc platform (mkAsmTempDieLabel label) <> colon $$ pprAbbrev abbrev - $$ pprString name + $$ pprDwarfString platform name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) @@ -209,13 +258,13 @@ pprDwarfInfoOpen platform _ (DwarfBlock _ label (Just marker)) = $$ pprLabelString platform label $$ pprWord platform (pdoc platform marker) $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel marker) -pprDwarfInfoOpen _ _ (DwarfSrcNote ss) = +pprDwarfInfoOpen platform _ (DwarfSrcNote {..}) = pprAbbrev DwAbbrGhcSrcNote - $$ pprString' (ftext $ srcSpanFile ss) - $$ pprData4 (fromIntegral $ srcSpanStartLine ss) - $$ pprHalf (fromIntegral $ srcSpanStartCol ss) - $$ pprData4 (fromIntegral $ srcSpanEndLine ss) - $$ pprHalf (fromIntegral $ srcSpanEndCol ss) + $$ pprDwarfString platform dwSpanFile + $$ pprData4 (fromIntegral dwSpanStartLine) + $$ pprHalf (fromIntegral dwSpanStartCol) + $$ pprData4 (fromIntegral dwSpanEndLine) + $$ pprHalf (fromIntegral dwSpanEndCol) -- | Close a DWARF info record with children pprDwarfInfoClose :: SDoc @@ -584,12 +633,8 @@ pprString' :: SDoc -> SDoc pprString' str = text "\t.asciz \"" <> str <> char '"' -- | Generate a string constant. We take care to escape the string. -pprString :: String -> SDoc -pprString str - = pprString' $ hcat $ map escapeChar $ - if str `lengthIs` utf8EncodedLength str - then str - else map (chr . fromIntegral) $ BS.unpack $ bytesFS $ mkFastString str +pprFastString :: FastString -> SDoc +pprFastString = pprString' . hcat . map escapeChar . unpackFS -- | Escape a single non-unicode character escapeChar :: Char -> SDoc ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -68,8 +68,11 @@ import Data.Bits * * ************************************************************************ -The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . -Fast comparison is everything on @Uniques@: +The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . The +allocation of these is documented in Note [Unique tag allocation] in +GHC.Builtin.Uniques. + +Fast comparison is everything on @Uniques at . -} -- | Unique identifier. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebf4de37f4bd55a592f7477c1d76263ec0c26399...b48a56f16068bd1d574e8042fe7581a192f357d2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebf4de37f4bd55a592f7477c1d76263ec0c26399...b48a56f16068bd1d574e8042fe7581a192f357d2 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 Sun Nov 1 17:59:00 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 12:59:00 -0500 Subject: [Git][ghc/ghc][wip/tsan/stats] 2 commits: rts/Stats: Protect with mutex Message-ID: <5f9ef7648be1f_7853fb5dd3f5e302821a8@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tsan/stats at Glasgow Haskell Compiler / GHC Commits: b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - 4 changed files: - rts/RtsStartup.c - rts/Stats.c - rts/Stats.h - rts/sm/Storage.c Changes: ===================================== rts/RtsStartup.c ===================================== @@ -575,6 +575,10 @@ hs_exit_(bool wait_foreign) if (is_io_mng_native_p()) hs_restoreConsoleCP(); #endif + + /* tear down statistics subsystem */ + stat_exit(); + /* free hash table storage */ exitHashTable(); ===================================== rts/Stats.c ===================================== @@ -26,6 +26,11 @@ #include // for memset +#if defined(THREADED_RTS) +// Protects all statistics below +Mutex stats_mutex; +#endif + static Time start_init_cpu, start_init_elapsed, end_init_cpu, end_init_elapsed, @@ -101,6 +106,10 @@ mut_user_time_during_RP( void ) void initStats0(void) { +#if defined(THREADED_RTS) + initMutex(&stats_mutex); +#endif + start_init_cpu = 0; start_init_elapsed = 0; end_init_cpu = 0; @@ -262,9 +271,11 @@ stat_endInit(void) void stat_startExit(void) { + ACQUIRE_LOCK(&stats_mutex); getProcessTimes(&start_exit_cpu, &start_exit_elapsed); start_exit_gc_elapsed = stats.gc_elapsed_ns; start_exit_gc_cpu = stats.gc_cpu_ns; + RELEASE_LOCK(&stats_mutex); } /* ----------------------------------------------------------------------------- @@ -275,7 +286,9 @@ stat_startExit(void) void stat_endExit(void) { + ACQUIRE_LOCK(&stats_mutex); getProcessTimes(&end_exit_cpu, &end_exit_elapsed); + RELEASE_LOCK(&stats_mutex); } void @@ -287,8 +300,10 @@ stat_startGCSync (gc_thread *gct) void stat_startNonmovingGc () { + ACQUIRE_LOCK(&stats_mutex); start_nonmoving_gc_cpu = getCurrentThreadCPUTime(); start_nonmoving_gc_elapsed = getProcessCPUTime(); + RELEASE_LOCK(&stats_mutex); } void @@ -296,6 +311,8 @@ stat_endNonmovingGc () { Time cpu = getCurrentThreadCPUTime(); Time elapsed = getProcessCPUTime(); + + ACQUIRE_LOCK(&stats_mutex); stats.gc.nonmoving_gc_elapsed_ns = elapsed - start_nonmoving_gc_elapsed; stats.nonmoving_gc_elapsed_ns += stats.gc.nonmoving_gc_elapsed_ns; @@ -305,12 +322,15 @@ stat_endNonmovingGc () stats.nonmoving_gc_max_elapsed_ns = stg_max(stats.gc.nonmoving_gc_elapsed_ns, stats.nonmoving_gc_max_elapsed_ns); + RELEASE_LOCK(&stats_mutex); } void stat_startNonmovingGcSync () { + ACQUIRE_LOCK(&stats_mutex); start_nonmoving_gc_sync_elapsed = getProcessElapsedTime(); + RELEASE_LOCK(&stats_mutex); traceConcSyncBegin(); } @@ -318,13 +338,17 @@ void stat_endNonmovingGcSync () { Time end_elapsed = getProcessElapsedTime(); + ACQUIRE_LOCK(&stats_mutex); stats.gc.nonmoving_gc_sync_elapsed_ns = end_elapsed - start_nonmoving_gc_sync_elapsed; stats.nonmoving_gc_sync_elapsed_ns += stats.gc.nonmoving_gc_sync_elapsed_ns; stats.nonmoving_gc_sync_max_elapsed_ns = stg_max(stats.gc.nonmoving_gc_sync_elapsed_ns, stats.nonmoving_gc_sync_max_elapsed_ns); + Time sync_elapsed = stats.gc.nonmoving_gc_sync_elapsed_ns; + RELEASE_LOCK(&stats_mutex); + if (RtsFlags.GcFlags.giveStats == VERBOSE_GC_STATS) { - statsPrintf("# sync %6.3f\n", TimeToSecondsDbl(stats.gc.nonmoving_gc_sync_elapsed_ns)); + statsPrintf("# sync %6.3f\n", TimeToSecondsDbl(sync_elapsed)); } traceConcSyncEnd(); } @@ -440,6 +464,8 @@ stat_endGC (Capability *cap, gc_thread *initiating_gct, W_ live, W_ copied, W_ s W_ mut_spin_spin, W_ mut_spin_yield, W_ any_work, W_ no_work, W_ scav_find_work) { + ACQUIRE_LOCK(&stats_mutex); + // ------------------------------------------------- // Collect all the stats about this GC in stats.gc. We always do this since // it's relatively cheap and we need allocated_bytes to catch heap @@ -609,6 +635,7 @@ stat_endGC (Capability *cap, gc_thread *initiating_gct, W_ live, W_ copied, W_ s CAPSET_HEAP_DEFAULT, mblocks_allocated * MBLOCK_SIZE); } + RELEASE_LOCK(&stats_mutex); } /* ----------------------------------------------------------------------------- @@ -621,8 +648,10 @@ stat_startRP(void) Time user, elapsed; getProcessTimes( &user, &elapsed ); + ACQUIRE_LOCK(&stats_mutex); RP_start_time = user; RPe_start_time = elapsed; + RELEASE_LOCK(&stats_mutex); } #endif /* PROFILING */ @@ -640,11 +669,14 @@ stat_endRP( Time user, elapsed; getProcessTimes( &user, &elapsed ); + ACQUIRE_LOCK(&stats_mutex); RP_tot_time += user - RP_start_time; RPe_tot_time += elapsed - RPe_start_time; + double mut_time_during_RP = mut_user_time_during_RP(); + RELEASE_LOCK(&stats_mutex); fprintf(prof_file, "Retainer Profiling: %d, at %f seconds\n", - retainerGeneration, mut_user_time_during_RP()); + retainerGeneration, mut_time_during_RP); fprintf(prof_file, "\tMax auxiliary stack size = %u\n", maxStackSize); fprintf(prof_file, "\tAverage number of visits per object = %f\n", averageNumVisit); @@ -661,8 +693,10 @@ stat_startHeapCensus(void) Time user, elapsed; getProcessTimes( &user, &elapsed ); + ACQUIRE_LOCK(&stats_mutex); HC_start_time = user; HCe_start_time = elapsed; + RELEASE_LOCK(&stats_mutex); } #endif /* PROFILING */ @@ -676,8 +710,10 @@ stat_endHeapCensus(void) Time user, elapsed; getProcessTimes( &user, &elapsed ); + ACQUIRE_LOCK(&stats_mutex); HC_tot_time += user - HC_start_time; HCe_tot_time += elapsed - HCe_start_time; + RELEASE_LOCK(&stats_mutex); } #endif /* PROFILING */ @@ -774,6 +810,7 @@ static void free_RTSSummaryStats(RTSSummaryStats * sum) sum->gc_summary_stats = NULL; } +// Must hold stats_mutex. static void report_summary(const RTSSummaryStats* sum) { // We should do no calculation, other than unit changes and formatting, and @@ -1176,6 +1213,7 @@ static void report_machine_readable (const RTSSummaryStats * sum) statsPrintf(" ]\n"); } +// Must hold stats_mutex. static void report_one_line(const RTSSummaryStats * sum) { // We should do no calculation, other than unit changes and formatting, and @@ -1207,10 +1245,12 @@ static void report_one_line(const RTSSummaryStats * sum) } void -stat_exit (void) +stat_exitReport (void) { RTSSummaryStats sum; init_RTSSummaryStats(&sum); + // We'll need to refer to task counters later + ACQUIRE_LOCK(&all_tasks_mutex); if (RtsFlags.GcFlags.giveStats != NO_GC_STATS) { // First we tidy the times in stats, and populate the times in sum. @@ -1220,6 +1260,7 @@ stat_exit (void) Time now_cpu_ns, now_elapsed_ns; getProcessTimes(&now_cpu_ns, &now_elapsed_ns); + ACQUIRE_LOCK(&stats_mutex); stats.cpu_ns = now_cpu_ns - start_init_cpu; stats.elapsed_ns = now_elapsed_ns - start_init_elapsed; /* avoid divide by zero if stats.total_cpu_ns is measured as 0.00 @@ -1408,6 +1449,7 @@ stat_exit (void) report_one_line(&sum); } } + RELEASE_LOCK(&stats_mutex); statsFlush(); statsClose(); @@ -1427,6 +1469,15 @@ stat_exit (void) stgFree(GC_coll_max_pause); GC_coll_max_pause = NULL; } + + RELEASE_LOCK(&all_tasks_mutex); +} + +void stat_exit() +{ +#if defined(THREADED_RTS) + closeMutex(&stats_mutex); +#endif } /* Note [Work Balance] @@ -1646,7 +1697,10 @@ statDescribeGens(void) uint64_t getAllocations( void ) { - return stats.allocated_bytes; + ACQUIRE_LOCK(&stats_mutex); + StgWord64 n = stats.allocated_bytes; + RELEASE_LOCK(&stats_mutex); + return n; } int getRTSStatsEnabled( void ) @@ -1659,7 +1713,9 @@ void getRTSStats( RTSStats *s ) Time current_elapsed = 0; Time current_cpu = 0; + ACQUIRE_LOCK(&stats_mutex); *s = stats; + RELEASE_LOCK(&stats_mutex); getProcessTimes(¤t_cpu, ¤t_elapsed); s->cpu_ns = current_cpu - end_init_cpu; ===================================== rts/Stats.h ===================================== @@ -58,6 +58,7 @@ void stat_endHeapCensus(void); void stat_startExit(void); void stat_endExit(void); +void stat_exitReport(void); void stat_exit(void); void stat_workerStop(void); ===================================== rts/sm/Storage.c ===================================== @@ -302,7 +302,7 @@ exitStorage (void) { nonmovingExit(); updateNurseriesStats(); - stat_exit(); + stat_exitReport(); } void View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bacdbe5168644547954803879c5f15ca9698253e...5c2e6bced838b7d7617af2bfb272889a9af16a76 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bacdbe5168644547954803879c5f15ca9698253e...5c2e6bced838b7d7617af2bfb272889a9af16a76 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 Sun Nov 1 18:11:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 13:11:26 -0500 Subject: [Git][ghc/ghc][wip/tsan/all] 13 commits: rts/Stats: Protect with mutex Message-ID: <5f9efa4e96214_7853fb5f5d4cebc282755@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tsan/all at Glasgow Haskell Compiler / GHC Commits: b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 30 changed files: - .gitlab-ci.yml - hadrian/src/Flavour.hs - includes/rts/TSANUtils.h - includes/rts/storage/Closures.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Schedule.h - rts/Sparks.c - rts/Stats.c - rts/Stats.h - rts/Task.c - rts/ThreadPaused.c - rts/Threads.c - rts/Timer.c - rts/WSDeque.c - rts/WSDeque.h - rts/posix/GetTime.c - rts/posix/Signals.c - rts/posix/itimer/Pthread.c - rts/sm/BlockAlloc.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3a7e8bd76a817d0a5cab10f5b098153624b7585...07e82ba52228580cfbd90ff031e657acbecc715b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3a7e8bd76a817d0a5cab10f5b098153624b7585...07e82ba52228580cfbd90ff031e657acbecc715b 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 Sun Nov 1 18:16:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 13:16:25 -0500 Subject: [Git][ghc/ghc][wip/T18043] rts: Flush eventlog buffers from flushEventLog Message-ID: <5f9efb79e1da6_785d5bfc5428357f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18043 at Glasgow Haskell Compiler / GHC Commits: 47508fa9 by Ben Gamari at 2020-11-01T13:16:10-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 11 changed files: - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -17,7 +17,6 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" -#include "rts/EventLogWriter.h" /* * Running the scheduler @@ -47,6 +46,9 @@ typedef struct CapabilityPublic_ { StgRegTable r; } CapabilityPublic; +/* N.B. this needs the Capability declaration above. */ +#include "rts/EventLogWriter.h" + /* ---------------------------------------------------------------------------- RTS configuration settings, for passing to hs_init_ghc() ------------------------------------------------------------------------- */ ===================================== includes/rts/EventLogWriter.h ===================================== @@ -68,3 +68,8 @@ bool startEventLogging(const EventLogWriter *writer); * Stop event logging and destroy the current EventLogWriter. */ void endEventLogging(void); + +/* + * Flush the eventlog. cap can be NULL if one is not held. + */ +void flushEventLog(Capability **cap); ===================================== libraries/base/Debug/Trace.hs ===================================== @@ -37,6 +37,7 @@ module Debug.Trace ( -- $eventlog_tracing traceEvent, traceEventIO, + flushEventLog, -- * Execution phase markers -- $markers @@ -319,3 +320,11 @@ traceMarkerIO :: String -> IO () traceMarkerIO msg = GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> case traceMarker# p s of s' -> (# s', () #) + +-- | Immediately flush the event log, if enabled. +-- +-- @since 4.15.0.0 +flushEventLog :: IO () +flushEventLog = c_flushEventLog nullPtr + +foreign import ccall "flushEventLog" c_flushEventLog :: Ptr () -> IO () ===================================== rts/Capability.c ===================================== @@ -23,6 +23,7 @@ #include "Schedule.h" #include "Sparks.h" #include "Trace.h" +#include "eventlog/EventLog.h" // for flushLocalEventsBuf #include "sm/GC.h" // for gcWorkerThread() #include "STM.h" #include "RtsUtils.h" @@ -885,6 +886,10 @@ yieldCapability (Capability** pCap, Task *task, bool gcAllowed) debugTrace(DEBUG_nonmoving_gc, "Flushing update remembered set blocks..."); break; + case SYNC_FLUSH_EVENT_LOG: + flushLocalEventsBuf(cap); + break; + default: break; } ===================================== rts/Capability.h ===================================== @@ -263,7 +263,8 @@ typedef enum { SYNC_OTHER, SYNC_GC_SEQ, SYNC_GC_PAR, - SYNC_FLUSH_UPD_REM_SET + SYNC_FLUSH_UPD_REM_SET, + SYNC_FLUSH_EVENT_LOG } SyncType; // ===================================== rts/RtsSymbols.c ===================================== @@ -594,6 +594,7 @@ SymI_HasProto(__word_encodeFloat) \ SymI_HasProto(stg_atomicallyzh) \ SymI_HasProto(barf) \ + SymI_HasProto(flushEventLog) \ SymI_HasProto(deRefStablePtr) \ SymI_HasProto(debugBelch) \ SymI_HasProto(errorBelch) \ ===================================== rts/Schedule.c ===================================== @@ -2040,7 +2040,7 @@ forkProcess(HsStablePtr *entry stopTimer(); // See #4074 #if defined(TRACING) - flushEventLog(); // so that child won't inherit dirty file buffers + flushAllCapsEventsBufs(); // so that child won't inherit dirty file buffers #endif pid = fork(); ===================================== rts/Trace.c ===================================== @@ -118,10 +118,10 @@ void resetTracing (void) restartEventLogging(); } -void flushTrace (void) +void flushTrace () { if (eventlog_enabled) { - flushEventLog(); + flushEventLog(NULL); } } ===================================== rts/Trace.h ===================================== @@ -319,7 +319,6 @@ void traceConcSweepEnd(void); void traceConcUpdRemSetFlush(Capability *cap); void traceNonmovingHeapCensus(uint32_t log_blk_size, const struct NonmovingAllocCensus *census); - void flushTrace(void); #else /* !TRACING */ ===================================== rts/eventlog/EventLog.c ===================================== @@ -16,6 +16,7 @@ #include "RtsUtils.h" #include "Stats.h" #include "EventLog.h" +#include "Schedule.h" #include #include @@ -270,8 +271,8 @@ stopEventLogWriter(void) } } -void -flushEventLog(void) +static void +flushEventLogWriter(void) { if (event_log_writer != NULL && event_log_writer->flushEventLog != NULL) { @@ -1484,7 +1485,7 @@ void printAndClearEventBuf (EventsBuf *ebuf) "printAndClearEventLog: could not flush event log\n" ); resetEventsBuf(ebuf); - flushEventLog(); + flushEventLogWriter(); return; } @@ -1566,6 +1567,40 @@ void postEventType(EventsBuf *eb, EventType *et) postInt32(eb, EVENT_ET_END); } +void flushLocalEventsBuf(Capability *cap) +{ + EventsBuf *eb = &capEventBuf[cap->no]; + printAndClearEventBuf(eb); +} + +// Flush all capabilities' event buffers when we already hold all capabilities. +// Used during forkProcess. +void flushAllCapsEventsBufs() +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + + for (unsigned int i=0; i < n_capabilities; i++) { + flushLocalEventsBuf(capabilities[i]); + } + flushEventLogWriter(); +} + +void flushEventLog(Capability **cap USED_IF_THREADS) +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + +#if defined(THREADED_RTS) + Task *task = getTask(); + stopAllCapabilitiesWith(cap, task, SYNC_FLUSH_EVENT_LOG); + releaseAllCapabilities(n_capabilities, cap ? *cap : NULL, task); +#endif + flushEventLogWriter(); +} + #else enum EventLogStatus eventLogStatus(void) @@ -1579,4 +1614,6 @@ bool startEventLogging(const EventLogWriter *writer STG_UNUSED) { void endEventLogging(void) {} +void flushEventLog(Capability **cap STG_UNUSED) {} + #endif /* TRACING */ ===================================== rts/eventlog/EventLog.h ===================================== @@ -28,8 +28,10 @@ void initEventLogging(void); void restartEventLogging(void); void freeEventLogging(void); void abortEventLogging(void); // #4512 - after fork child needs to abort -void flushEventLog(void); // event log inherited from parent void moreCapEventBufs (uint32_t from, uint32_t to); +void flushLocalEventsBuf(Capability *cap); +void flushAllCapsEventsBufs(void); +void flushAllEventsBufs(Capability *cap); /* * Post a scheduler event to the capability's event buffer (an event @@ -175,6 +177,9 @@ void postNonmovingHeapCensus(int log_blk_size, #else /* !TRACING */ +INLINE_HEADER void flushLocalEventsBuf(Capability *cap STG_UNUSED) +{ /* nothing */ } + INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, EventTypeNum tag STG_UNUSED, StgThreadID id STG_UNUSED, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/47508fa96aa5175d6ceab00d3fb73af91840a104 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/47508fa96aa5175d6ceab00d3fb73af91840a104 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 Sun Nov 1 18:57:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 13:57:30 -0500 Subject: [Git][ghc/ghc][wip/perform-blocking-gc] 910 commits: rts: Teach getNumProcessors to return available processors Message-ID: <5f9f051a350bd_7853fb5f57628e42868fe@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/perform-blocking-gc at Glasgow Haskell Compiler / GHC Commits: 4413828b by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Teach getNumProcessors to return available processors Previously we would report the number of physical processors, which can be quite wrong in a containerized setting. Now we rather return how many processors are in our affinity mask when possible. I also refactored the code to prefer platform-specific since this will report logical CPUs instead of physical (using `machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD). Fixes #14781. - - - - - 1449435c by Ben Gamari at 2020-05-30T06:07:31-04:00 users-guide: Note change in getNumProcessors in users guide - - - - - 3d960169 by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Drop compatibility shims for Windows Vista We can now assume that the thread and processor group interfaces are available. - - - - - 7f8f948c by Peter Trommler at 2020-05-30T06:08:07-04:00 PPC NCG: Fix .size directive on powerpc64 ELF v1 Thanks to Sergei Trofimovich for pointing out the issue. Fixes #18237 - - - - - 7c555b05 by Andreas Klebinger at 2020-05-30T06:08:43-04:00 Optimize GHC.Utils.Monad. Many functions in this module are recursive and as such are marked loop breakers. Which means they are unlikely to get an unfolding. This is *bad*. We always want to specialize them to specific Monads. Which requires a visible unfolding at the use site. I rewrote the recursive ones from: foo f x = ... foo x' ... to foo f x = go x where go x = ... As well as giving some pragmas to make all of them available for specialization. The end result is a reduction of allocations of about -1.4% for nofib/spectral/simple/Main.hs when compiled with `-O`. ------------------------- Metric Decrease: T12425 T14683 T5631 T9233 T9675 T9961 WWRec ------------------------- - - - - - 8b1cb5df by Ben Gamari at 2020-05-30T06:09:20-04:00 Windows: Bump Windows toolchain to 0.2 - - - - - 6947231a by Zubin Duggal at 2020-05-30T06:10:02-04:00 Simplify contexts in GHC.Iface.Ext.Ast - - - - - 2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00 Cleanup OVERWRITING_CLOSURE logic The code is just more confusing than it needs to be. We don't need to mix the threaded check with the ldv profiling check since ldv's init already checks for this. Hence they can be two separate checks. Taking the sanity checking into account is also cleaner via DebugFlags.sanity. No need for checking the DEBUG define. The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the old code had also make things a lot more opaque IMO so I removed those. - - - - - 6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00 Fix OVERWRITING_CLOSURE assuming closures are not inherently used The new ASSERT in LDV_recordDead() was being tripped up by MVars when removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via OVERWRITE_INFO(). - - - - - 38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00 Always zero shrunk mutable array slop when profiling When shrinking arrays in the profiling way we currently don't always zero the leftover slop. This means we can't traverse such closures in the heap profiler. The old Note [zeroing slop] and #8402 have some rationale for why this is so but I belive the reasoning doesn't apply to mutable closures. There users already have to ensure multiple threads don't step on each other's toes so zeroing should be safe. - - - - - b0c1f2a6 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for #18151 - - - - - 9a99a178 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for desugaring of PostfixOperators - - - - - 2b89ca5b by Ben Gamari at 2020-06-01T06:33:37-04:00 HsToCore: Eta expand left sections Strangely, the comment next to this code already alluded to the fact that even simply eta-expanding will sacrifice laziness. It's quite unclear how we regressed so far. See #18151. - - - - - d412d7a3 by Kirill Elagin at 2020-06-01T06:34:21-04:00 Winferred-safe-imports: Do not exit with error Currently, when -Winferred-safe-imports is enabled, even when it is not turned into an error, the compiler will still exit with exit code 1 if this warning was emitted. Make sure it is really treated as a warning. - - - - - f945eea5 by Ben Gamari at 2020-06-01T06:34:58-04:00 nonmoving: Optimise log2_ceil - - - - - aab606e4 by Bodigrim at 2020-06-01T06:35:36-04:00 Clarify description of fromListN - - - - - 7e5220e2 by Bodigrim at 2020-06-01T06:35:36-04:00 Apply suggestion to libraries/base/GHC/Exts.hs - - - - - f3fb1ce9 by fendor at 2020-06-01T06:36:18-04:00 Add `isInScope` check to `lintCoercion` Mirrors the behaviour of `lintType`. - - - - - 5ac4d946 by fendor at 2020-06-01T06:36:18-04:00 Lint rhs of IfaceRule - - - - - 1cef6126 by Jeremy Schlatter at 2020-06-01T06:37:00-04:00 Fix wording in documentation The duplicate "orphan instance" phrase here doesn't make sense, and was probably an accident. - - - - - 5aaf08f2 by Takenobu Tani at 2020-06-01T06:37:43-04:00 configure: Modify aclocal.m4 according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * Rename: * compiler/GHC/Parser.hs <= compiler/parser/Parser.hs * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs * Add: * compiler/GHC/Cmm/Lexer.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular - - - - - 15857ad8 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Don't fail if we can't unlink __symlink_test Afterall, it's possible we were unable to create it due to lack of symlink permission. - - - - - 4a7229ef by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Refactor ghostscript detection Tamar reported that he saw crashes due to unhandled exceptions. - - - - - 2ab37eaf by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/perf_notes: Fix ill-typed assignments - - - - - e45d5b66 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/testutil: Fix bytes/str mismatch - - - - - 7002d0cb by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Work around spurious mypy failure - - - - - 11390e3a by Takenobu Tani at 2020-06-01T06:39:05-04:00 Clean up file paths for new module hierarchy This updates comments only. This patch replaces file references according to new module hierarchy. See also: * https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular * https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 8f2e5732 by Takenobu Tani at 2020-06-01T06:39:05-04:00 Modify file paths to module paths for new module hierarchy This updates comments only. This patch replaces module references according to new module hierarchy [1][2]. For files under the `compiler/` directory, I replace them as module paths instead of file paths. For instance, `GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3]. For current and future haddock's markup, this patch encloses the module name with "" [4]. [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 [3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613 [4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules - - - - - 68b71c4a by Tom Ellis at 2020-06-01T06:39:55-04:00 Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo - - - - - 95da76c2 by Sylvain Henry at 2020-06-01T06:40:41-04:00 Hadrian: fix binary-dist target for cross-compilation - - - - - 730fcd54 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for the @-operator Since GHC diverges from the Haskell Report by allowing the user to define (@) as an infix operator, we better give a good error message when the user does so unintentionally. In general, this is rather hard to do, as some failures will be discovered only in the renamer or the type checker: x :: (Integer, Integer) x @ (a, b) = (1, 2) This patch does *not* address this general case. However, it gives much better error messages when the binding is not syntactically valid: pairs xs @ (_:xs') = zip xs xs' Before this patch, the error message was rather puzzling: <interactive>:1:1: error: Parse error in pattern: pairs After this patch, the error message includes a hint: <interactive>:1:1: error: Parse error in pattern: pairs In a function binding for the ‘@’ operator. Perhaps you meant an as-pattern, which must not be surrounded by whitespace - - - - - 0fde5377 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TypeApplications With this patch, we always parse f @t as a type application, thereby producing better error messages. This steals two syntactic forms: * Prefix form of the @-operator in expressions. Since the @-operator is a divergence from the Haskell Report anyway, this is not a major loss. * Prefix form of @-patterns. Since we are stealing loose infix form anyway, might as well sacrifice the prefix form for the sake of much better error messages. - - - - - c68e7e1e by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TemplateHaskellQuotes While [e| |], [t| |], [d| |], and so on, steal syntax from list comprehensions, [| |] and [|| ||] do not steal any syntax. Thus we can improve error messages by always accepting them in the lexer. Turns out the renamer already performs necessary validation. - - - - - 120aedbd by Ben Gamari at 2020-06-01T16:07:02-04:00 gitlab-ci: Disable use of ld.lld on ARMv7 It turns out that lld non-deterministically fails on ARMv7. I suspect this may be due to the a kernel regression as this only started happening when we upgraded to 5.4. Nevertheless, easily avoided by simply sticking with gold. Works around #18280. - - - - - d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00 gitlab-ci: Ensure that workaround for #18280 applies to bindisttest We need to ensure that the `configure` flags working around #18280 are propagated to the bindisttest `configure` as well. - - - - - cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00 gitlab-ci: Allow ARMv7 job to fail Due to #18298. - - - - - 32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00 Clean up boot vs non-boot disambiguating types We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule. - - - - - c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00 docs: Add more details on InterruptibleFFI. Details from https://gitlab.haskell.org/ghc/ghc/issues/8684 and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430 - - - - - 1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00 Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr. MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd. This regression did not make it into a release of GHC. Here, the original behavior is restored, and FinalPtr is given the same treatment as PlainPtr. - - - - - 2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00 Fix documentation on type families not being extracted It looks like the location of the Names used for CoAxioms on type families are now located at their type constructors. Previously, Docs.hs thought the Names were located in the RHS, so the RealSrcSpan in the instanceMap and getInstLoc didn't match up. Fixes #18241 - - - - - 6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00 GHC.Hs.Instances: Compile with -O0 This module contains exclusively Data instances, which are going to be slow no matter what we do. Furthermore, they are incredibly slow to compile with optimisation (see #9557). Consequently we compile this with -O0. See #18254. - - - - - c330331a by nineonine at 2020-06-04T04:37:59-04:00 Add test for #17669 - - - - - cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00 rts: Add Windows-specific implementation of rtsSleep Previously we would use the POSIX path, which uses `nanosleep`. However, it turns out that `nanosleep` is provided by `libpthread` on Windows. In general we don't want to incur such a dependency. Avoid this by simply using `Sleep` on Windows. Fixes #18272. - - - - - ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00 compiler: Disable use of process jobs with process < 1.6.9 Due to #17926. - - - - - 6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00 [linker] Adds void printLoadedObjects(void); This allows us to dump in-memory object code locations for debugging. Fixup printLoadedObjects prototype - - - - - af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00 base: fix sign confusion in log1mexp implementation (fix #17125) author: claude (https://gitlab.haskell.org/trac-claude) The correct threshold for log1mexp is -(log 2) with the current specification of log1mexp. This change improves accuracy for large negative inputs. To avoid code duplication, a small helper function is added; it isn't the default implementation in Floating because it needs Ord. This patch does nothing to address that the Haskell specification is different from that in common use in other languages. - - - - - 2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00 Simple subsumption This patch simplifies GHC to use simple subsumption. Ticket #17775 Implements GHC proposal #287 https://github.com/ghc-proposals/ghc-proposals/blob/master/ proposals/0287-simplify-subsumption.rst All the motivation is described there; I will not repeat it here. The implementation payload: * tcSubType and friends become noticably simpler, because it no longer uses eta-expansion when checking subsumption. * No deeplyInstantiate or deeplySkolemise That in turn means that some tests fail, by design; they can all be fixed by eta expansion. There is a list of such changes below. Implementing the patch led me into a variety of sticky corners, so the patch includes several othe changes, some quite significant: * I made String wired-in, so that "foo" :: String rather than "foo" :: [Char] This improves error messages, and fixes #15679 * The pattern match checker relies on knowing about in-scope equality constraints, andd adds them to the desugarer's environment using addTyCsDs. But the co_fn in a FunBind was missed, and for some reason simple-subsumption ends up with dictionaries there. So I added a call to addTyCsDs. This is really part of #18049. * I moved the ic_telescope field out of Implication and into ForAllSkol instead. This is a nice win; just expresses the code much better. * There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader. We called checkDataKindSig inside tc_kind_sig, /before/ solveEqualities and zonking. Obviously wrong, easily fixed. * solveLocalEqualitiesX: there was a whole mess in here, around failing fast enough. I discovered a bad latent bug where we could successfully kind-check a type signature, and use it, but have unsolved constraints that could fill in coercion holes in that signature -- aargh. It's all explained in Note [Failure in local type signatures] in GHC.Tc.Solver. Much better now. * I fixed a serious bug in anonymous type holes. IN f :: Int -> (forall a. a -> _) -> Int that "_" should be a unification variable at the /outer/ level; it cannot be instantiated to 'a'. This was plain wrong. New fields mode_lvl and mode_holes in TcTyMode, and auxiliary data type GHC.Tc.Gen.HsType.HoleMode. This fixes #16292, but makes no progress towards the more ambitious #16082 * I got sucked into an enormous refactoring of the reporting of equality errors in GHC.Tc.Errors, especially in mkEqErr1 mkTyVarEqErr misMatchMsg misMatchMsgOrCND In particular, the very tricky mkExpectedActualMsg function is gone. It took me a full day. But the result is far easier to understand. (Still not easy!) This led to various minor improvements in error output, and an enormous number of test-case error wibbles. One particular point: for occurs-check errors I now just say Can't match 'a' against '[a]' rather than using the intimidating language of "occurs check". * Pretty-printing AbsBinds Tests review * Eta expansions T11305: one eta expansion T12082: one eta expansion (undefined) T13585a: one eta expansion T3102: one eta expansion T3692: two eta expansions (tricky) T2239: two eta expansions T16473: one eta determ004: two eta expansions (undefined) annfail06: two eta (undefined) T17923: four eta expansions (a strange program indeed!) tcrun035: one eta expansion * Ambiguity check at higher rank. Now that we have simple subsumption, a type like f :: (forall a. Eq a => Int) -> Int is no longer ambiguous, because we could write g :: (forall a. Eq a => Int) -> Int g = f and it'd typecheck just fine. But f's type is a bit suspicious, and we might want to consider making the ambiguity check do a check on each sub-term. Meanwhile, these tests are accepted, whereas they were previously rejected as ambiguous: T7220a T15438 T10503 T9222 * Some more interesting error message wibbles T13381: Fine: one error (Int ~ Exp Int) rather than two (Int ~ Exp Int, Exp Int ~ Int) T9834: Small change in error (improvement) T10619: Improved T2414: Small change, due to order of unification, fine T2534: A very simple case in which a change of unification order means we get tow unsolved constraints instead of one tc211: bizarre impredicative tests; just accept this for now Updates Cabal and haddock submodules. Metric Increase: T12150 T12234 T5837 haddock.base Metric Decrease: haddock.compiler haddock.Cabal haddock.base Merge note: This appears to break the `UnliftedNewtypesDifficultUnification` test. It has been marked as broken in the interest of merging. (cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5) - - - - - 2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00 Simplify bindLHsTyVarBndrs and bindHsQTyVars Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate `Maybe` arguments, which I find terribly confusing. Thankfully, it's possible to remove one `Maybe` argument from each of these functions, which this patch accomplishes: * `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if GHC should warn about any of the quantified type variables going unused. However, every call site uses `Nothing` in practice. This makes sense, since it doesn't really make sense to warn about unused type variables bound by an `LHsQTyVars`. For instance, you wouldn't warn about the `a` in `data Proxy a = Proxy` going unused. As a result, I simply remove this `Maybe SDoc` argument altogether. * `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same reasons that `bindHsQTyVars` took one. To make things more confusing, however, `bindLHsTyVarBndrs` also takes a separate `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in warnings and error messages. In practice, the `Maybe SDoc` and the `HsDocContext` often contain the same text. See the call sites for `bindLHsTyVarBndrs` in `rnFamInstEqn` and `rnConDecl`, for instance. There are only a handful of call sites where the text differs between the `Maybe SDoc` and `HsDocContext` arguments: * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`" and the `HsDocContext` says "`In the transformation rule`". * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says "`In the type`" but the `HsDocContext` is inhereted from the surrounding context (e.g., if `rnHsTyKi` were called on a top-level type signature, the `HsDocContext` would be "`In the type signature`" instead) In both cases, warnings/error messages arguably _improve_ by unifying making the `Maybe SDoc`'s text match that of the `HsDocContext`. As a result, I decided to remove the `Maybe SDoc` argument to `bindLHsTyVarBndrs` entirely and simply reuse the text from the `HsDocContext`. (I decided to change the phrase "transformation rule" to "rewrite rule" while I was in the area.) The `Maybe SDoc` argument has one other purpose: signaling when to emit "`Unused quantified type variable`" warnings. To recover this functionality, I replaced the `Maybe SDoc` argument with a boolean-like `WarnUnusedForalls` argument. The only `bindLHsTyVarBndrs` call site that chooses _not_ to emit these warnings in `bindHsQTyVars`. - - - - - e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00 hadrian: Add missing deriveConstants dependency on ghcplatform.h deriveConstants wants to compile C sources which #include PosixSource.h, which itself #includes ghcplatform.h. Make sure that Hadrian knows about this dependency. Fixes #18290. - - - - - b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00 ghc-prim needs to depend on libc and libm libm is just an empty shell on musl, and all the math functions are contained in libc. - - - - - 6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00 Disable DLL loading if without system linker Some platforms (musl, aarch64) do not have a working dynamic linker implemented in the libc, even though we might see dlopen. It will ultimately just return that this is not supported. Hence we'll add a flag to the compiler to flat our disable loading dlls. This is needed as we will otherwise try to load the shared library even if this will subsequently fail. At that point we have given up looking for static options though. - - - - - 4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00 Range is actually +/-2^32, not +/-2^31 See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf - - - - - f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00 OccurAnal: Avoid exponential behavior due to where clauses Previously the `Var` case of `occAnalApp` could in some cases (namely in the case of `runRW#` applications) call `occAnalRhs` two. In the case of nested `runRW#`s this results in exponential complexity. In some cases the compilation time that resulted would be very long indeed (see #18296). Fixes #18296. Metric Decrease: T9961 T12150 T12234 - - - - - 9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00 Add link to GHC's wiki in the GHC API header This adds a URL to point to GHC's wiki in the GHC API header. Newcomers could easily find more information from the GHC API's web like [1]. [1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html [skip ci] - - - - - 72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00 Make GADT constructors adhere to the forall-or-nothing rule properly Issue #18191 revealed that the types of GADT constructors don't quite adhere to the `forall`-or-nothing rule. This patch serves to clean up this sad state of affairs somewhat. The main change is not in the code itself, but in the documentation, as this patch introduces two sections to the GHC User's Guide: * A "Formal syntax for GADTs" section that presents a BNF-style grammar for what is and isn't allowed in GADT constructor types. This mostly exists to codify GHC's existing behavior, but it also imposes a new restriction that addresses #18191: the outermost `forall` and/or context in a GADT constructor is not allowed to be surrounded by parentheses. Doing so would make these `forall`s/contexts nested, and GADTs do not support nested `forall`s/contexts at present. * A "`forall`-or-nothing rule" section that describes exactly what the `forall`-or-nothing rule is all about. Surprisingly, there was no mention of this anywhere in the User's Guide up until now! To adhere the new specification in the "Formal syntax for GADTs" section of the User's Guide, the following code changes were made: * A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced. This is very much like `splitLHsSigmaTy`, except that it avoids splitting apart any parentheses, which can be syntactically significant for GADT types. See `Note [No nested foralls or contexts in GADT constructors]` in `GHC.Hs.Type`. * `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return it when given a prefix GADT constructor. Unlike `ConDeclGADT`, `ConDeclGADTPrefixPs` does not split the GADT type into its argument and result types, as this cannot be done until after the type is renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why this is the case). * `GHC.Renamer.Module.rnConDecl` now has an additional case for `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into its `forall`s, context, argument types, and result type, and (2) checks for nested `forall`s/contexts. Step (2) used to be performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather than the renamer, but now the relevant code from the typechecker can simply be deleted. One nice side effect of this change is that we are able to give a more accurate error message for GADT constructors that use visible dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`), which improves the stderr in the `T16326_Fail6` test case. Fixes #18191. Bumps the Haddock submodule. - - - - - a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00 Always use rnImplicitBndrs to bring implicit tyvars into scope This implements a first step towards #16762 by changing the renamer to always use `rnImplicitBndrs` to bring implicitly bound type variables into scope. The main change is in `rnFamInstEqn` and `bindHsQTyVars`, which previously used _ad hoc_ methods of binding their implicit tyvars. There are a number of knock-on consequences: * One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding mechanism was to give more precise source locations in `-Wunused-type-patterns` warnings. (See https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an example of this.) However, these warnings are actually a little _too_ precise, since implicitly bound type variables don't have exact binding sites like explicitly bound type variables do. A similar problem existed for "`Different names for the same type variable`" errors involving implicit tyvars bound by `bindHsQTyVars`. Therefore, we simply accept the less precise (but more accurate) source locations from `rnImplicitBndrs` in `rnFamInstEqn` and `bindHsQTyVars`. See `Note [Source locations for implicitly bound type variables]` in `GHC.Rename.HsType` for the full story. * In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs to be able to look up names from the parent class (in the event that we are renaming an associated type family instance). As a result, `rnImplicitBndrs` now takes an argument of type `Maybe assoc`, which is `Just` in the event that a type family instance is associated with a class. * Previously, GHC kept track of three type synonyms for free type variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups` (which are allowed to contain duplicates), and `FreeKiTyVarsNoDups` (which contain no duplicates). However, making is a distinction between `-Dups` and `-NoDups` is now pointless, as all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually end up being passed to `rnImplicitBndrs`, which removes duplicates. As a result, I decided to just get rid of `FreeKiTyVarsDups` and `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`. * The `bindLRdrNames` and `deleteBys` functions are now dead code, so I took the liberty of removing them. - - - - - 24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00 Clarify leaf module names for new module hierarchy This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00 rts: Remove unused GET_ENTRY closure macro This macro is not used and got broken in the meantime, as ENTRY_CODE was deleted. - - - - - 87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00 Fix -fkeep-cafs flag name in users guide - - - - - ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00 Expose impliedGFlags, impledOffGFlags, impliedXFlags - - - - - 7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00 Cross-module LambdaFormInfo passing - Store LambdaFormInfos of exported Ids in interface files - Use them in importing modules This is for optimization purposes: if we know LambdaFormInfo of imported Ids we can generate more efficient calling code, see `getCallMethod`. Exporting (putting them in interface files or in ModDetails) and importing (reading them from interface files) are both optional. We don't assume known LambdaFormInfos anywhere and do not change how we call Ids with unknown LambdaFormInfos. Runtime, allocation, and residency numbers when building Cabal-the-library (commit 0d4ee7ba3): (Log and .hp files are in the MR: !2842) | | GHC HEAD | This patch | Diff | |-----|----------|------------|----------------| | -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% | | -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% | | -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% | | | GHC HEAD | This patch | Diff | |-----|-----------------|-----------------|----------------------------| | -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% | | -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% | | -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% | NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively turn all GCs into major GCs, and do GC more often. | | GHC HEAD | This patch | Diff | |-----|----------------------------|------------------------------|----------------------------| | -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% | | -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% | | -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% | NoFib results: -------------------------------------------------------------------------------- Program Size Allocs Instrs Reads Writes -------------------------------------------------------------------------------- CS 0.0% 0.0% +0.0% +0.0% +0.0% CSD 0.0% 0.0% 0.0% +0.0% +0.0% FS 0.0% 0.0% +0.0% +0.0% +0.0% S 0.0% 0.0% +0.0% +0.0% +0.0% VS 0.0% 0.0% +0.0% +0.0% +0.0% VSD 0.0% 0.0% +0.0% +0.0% +0.1% VSM 0.0% 0.0% +0.0% +0.0% +0.0% anna 0.0% 0.0% -0.3% -0.8% -0.0% ansi 0.0% 0.0% -0.0% -0.0% 0.0% atom 0.0% 0.0% -0.0% -0.0% 0.0% awards 0.0% 0.0% -0.1% -0.3% 0.0% banner 0.0% 0.0% -0.0% -0.0% -0.0% bernouilli 0.0% 0.0% -0.0% -0.0% -0.0% binary-trees 0.0% 0.0% -0.0% -0.0% +0.0% boyer 0.0% 0.0% -0.0% -0.0% 0.0% boyer2 0.0% 0.0% -0.0% -0.0% 0.0% bspt 0.0% 0.0% -0.0% -0.2% 0.0% cacheprof 0.0% 0.0% -0.1% -0.4% +0.0% calendar 0.0% 0.0% -0.0% -0.0% 0.0% cichelli 0.0% 0.0% -0.9% -2.4% 0.0% circsim 0.0% 0.0% -0.0% -0.0% 0.0% clausify 0.0% 0.0% -0.1% -0.3% 0.0% comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0% compress 0.0% 0.0% -0.0% -0.0% -0.0% compress2 0.0% 0.0% -0.0% -0.0% 0.0% constraints 0.0% 0.0% -0.1% -0.2% -0.0% cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0% cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0% cse 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0% dom-lt 0.0% 0.0% -0.1% -0.2% 0.0% eliza 0.0% 0.0% -0.5% -1.5% 0.0% event 0.0% 0.0% -0.0% -0.0% -0.0% exact-reals 0.0% 0.0% -0.1% -0.3% +0.0% exp3_8 0.0% 0.0% -0.0% -0.0% -0.0% expert 0.0% 0.0% -0.3% -1.0% -0.0% fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0% fasta 0.0% 0.0% -0.0% -0.0% +0.0% fem 0.0% 0.0% -0.0% -0.0% 0.0% fft 0.0% 0.0% -0.0% -0.0% 0.0% fft2 0.0% 0.0% -0.0% -0.0% 0.0% fibheaps 0.0% 0.0% -0.0% -0.0% +0.0% fish 0.0% 0.0% 0.0% -0.0% +0.0% fluid 0.0% 0.0% -0.4% -1.2% +0.0% fulsom 0.0% 0.0% -0.0% -0.0% 0.0% gamteb 0.0% 0.0% -0.1% -0.3% 0.0% gcd 0.0% 0.0% -0.0% -0.0% 0.0% gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0% genfft 0.0% 0.0% -0.0% -0.0% 0.0% gg 0.0% 0.0% -0.0% -0.0% +0.0% grep 0.0% 0.0% -0.0% -0.0% -0.0% hidden 0.0% 0.0% -0.1% -0.4% -0.0% hpg 0.0% 0.0% -0.2% -0.5% +0.0% ida 0.0% 0.0% -0.0% -0.0% +0.0% infer 0.0% 0.0% -0.3% -0.8% -0.0% integer 0.0% 0.0% -0.0% -0.0% +0.0% integrate 0.0% 0.0% -0.0% -0.0% 0.0% k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0% kahan 0.0% 0.0% -0.0% -0.0% +0.0% knights 0.0% 0.0% -2.2% -5.4% 0.0% lambda 0.0% 0.0% -0.6% -1.8% 0.0% last-piece 0.0% 0.0% -0.0% -0.0% 0.0% lcss 0.0% 0.0% -0.0% -0.1% 0.0% life 0.0% 0.0% -0.0% -0.1% 0.0% lift 0.0% 0.0% -0.2% -0.6% +0.0% linear 0.0% 0.0% -0.0% -0.0% -0.0% listcompr 0.0% 0.0% -0.0% -0.0% 0.0% listcopy 0.0% 0.0% -0.0% -0.0% 0.0% maillist 0.0% 0.0% -0.1% -0.3% +0.0% mandel 0.0% 0.0% -0.0% -0.0% 0.0% mandel2 0.0% 0.0% -0.0% -0.0% -0.0% mate +0.0% 0.0% -0.0% -0.0% -0.0% minimax 0.0% 0.0% -0.2% -1.0% 0.0% mkhprog 0.0% 0.0% -0.1% -0.2% -0.0% multiplier 0.0% 0.0% -0.0% -0.0% -0.0% n-body 0.0% 0.0% -0.0% -0.0% +0.0% nucleic2 0.0% 0.0% -0.1% -0.2% 0.0% para 0.0% 0.0% -0.0% -0.0% -0.0% paraffins 0.0% 0.0% -0.0% -0.0% 0.0% parser 0.0% 0.0% -0.2% -0.7% 0.0% parstof 0.0% 0.0% -0.0% -0.0% +0.0% pic 0.0% 0.0% -0.0% -0.0% 0.0% pidigits 0.0% 0.0% +0.0% +0.0% +0.0% power 0.0% 0.0% -0.2% -0.6% +0.0% pretty 0.0% 0.0% -0.0% -0.0% -0.0% primes 0.0% 0.0% -0.0% -0.0% 0.0% primetest 0.0% 0.0% -0.0% -0.0% -0.0% prolog 0.0% 0.0% -0.3% -1.1% 0.0% puzzle 0.0% 0.0% -0.0% -0.0% 0.0% queens 0.0% 0.0% -0.0% -0.0% +0.0% reptile 0.0% 0.0% -0.0% -0.0% 0.0% reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0% rewrite 0.0% 0.0% -0.7% -2.5% -0.0% rfib 0.0% 0.0% -0.0% -0.0% 0.0% rsa 0.0% 0.0% -0.0% -0.0% 0.0% scc 0.0% 0.0% -0.1% -0.2% -0.0% sched 0.0% 0.0% -0.0% -0.0% -0.0% scs 0.0% 0.0% -1.0% -2.6% +0.0% simple 0.0% 0.0% +0.0% -0.0% +0.0% solid 0.0% 0.0% -0.0% -0.0% 0.0% sorting 0.0% 0.0% -0.6% -1.6% 0.0% spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0% sphere 0.0% 0.0% -0.0% -0.0% -0.0% symalg 0.0% 0.0% -0.0% -0.0% +0.0% tak 0.0% 0.0% -0.0% -0.0% 0.0% transform 0.0% 0.0% -0.0% -0.0% 0.0% treejoin 0.0% 0.0% -0.0% -0.0% 0.0% typecheck 0.0% 0.0% -0.0% -0.0% +0.0% veritas +0.0% 0.0% -0.2% -0.4% +0.0% wang 0.0% 0.0% -0.0% -0.0% 0.0% wave4main 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0% x2n1 0.0% 0.0% -0.0% -0.0% -0.0% -------------------------------------------------------------------------------- Min 0.0% 0.0% -2.2% -5.4% -0.0% Max +0.0% 0.0% +0.0% +0.0% +0.1% Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0% Metric increases micro benchmarks tracked in #17686: Metric Increase: T12150 T12234 T12425 T13035 T5837 T6048 T9233 Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00 Give Language a Bounded instance - - - - - 9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Optimisation in Unique.Supply This patch switches on -fno-state-hack in GHC.Types.Unique.Supply. It turned out that my fixes for #18078 (coercion floating) changed the optimisation pathway for mkSplitUniqSupply in such a way that we had an extra allocation inside the inner loop. Adding -fno-state-hack fixed that -- and indeed the loop in mkSplitUniqSupply is a classic example of the way in which -fno-state-hack can be bad; see #18238. Moreover, the new code is better than the old. They allocate the same, but the old code ends up with a partial application. The net effect is that the test perf/should_run/UniqLoop runs 20% faster! From 2.5s down to 2.0s. The allocation numbers are the same -- but elapsed time falls. Good! The bad thing about this is that it's terribly delicate. But at least it's a good example of such delicacy in action. There is a long Note [Optimising the unique supply] which now explains all this. - - - - - 6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Implement cast worker/wrapper properly The cast worker/wrapper transformation transforms x = e |> co into y = e x = y |> co This is done by the simplifier, but we were being careless about transferring IdInfo from x to y, and about what to do if x is a NOINLNE function. This resulted in a series of bugs: #17673, #18093, #18078. This patch fixes all that: * Main change is in GHC.Core.Opt.Simplify, and the new prepareBinding function, which does this cast worker/wrapper transform. See Note [Cast worker/wrappers]. * There is quite a bit of refactoring around prepareRhs, makeTrivial etc. It's nicer now. * Some wrappers from strictness and cast w/w, notably those for a function with a NOINLINE, should inline very late. There wasn't really a mechanism for that, which was an existing bug really; so I invented a new finalPhase = Phase (-1). It's used for all simplifier runs after the user-visible phase 2,1,0 have run. (No new runs of the simplifier are introduced thereby.) See new Note [Compiler phases] in GHC.Types.Basic; the main changes are in GHC.Core.Opt.Driver * Doing this made me trip over two places where the AnonArgFlag on a FunTy was being lost so we could end up with (Num a -> ty) rather than (Num a => ty) - In coercionLKind/coercionRKind - In contHoleType in the Simplifier I fixed the former by defining mkFunctionType and using it in coercionLKind/RKind. I could have done the same for the latter, but the information is almost to hand. So I fixed the latter by - adding sc_hole_ty to ApplyToVal (like ApplyToTy), - adding as_hole_ty to ValArg (like TyArg) - adding sc_fun_ty to StrictArg Turned out I could then remove ai_type from ArgInfo. This is just moving the deck chairs around, but it worked out nicely. See the new Note [AnonArgFlag] in GHC.Types.Var * When looking at the 'arity decrease' thing (#18093) I discovered that stable unfoldings had a much lower arity than the actual optimised function. That's what led to the arity-decrease message. Simple solution: eta-expand. It's described in Note [Eta-expand stable unfoldings] in GHC.Core.Opt.Simplify * I also discovered that unsafeCoerce wasn't being inlined if the context was boring. So (\x. f (unsafeCoerce x)) would create a thunk -- yikes! I fixed that by making inlineBoringOK a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold. I also found that unsafeCoerceName was unused, so I removed it. I made a test case for #18078, and a very similar one for #17673. The net effect of all this on nofib is very modest, but positive: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.4% -0.1% -3.1% -3.1% 0.0% fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0% maillist -0.4% -0.1% -7.8% -1.0% -14.3% primetest -0.4% -15.6% -7.1% -6.6% 0.0% -------------------------------------------------------------------------------- Min -0.9% -15.6% -13.3% -14.2% -14.3% Max -0.3% 0.0% +12.1% +12.4% 0.0% Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1% All following metric decreases are compile-time allocation decreases between -1% and -3%: Metric Decrease: T5631 T13701 T14697 T15164 - - - - - 32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00 Fix lookupGlobalOccRn_maybe sometimes reporting an error In some cases it was possible for lookupGlobalOccRn_maybe to return an error, when it should be returning a Nothing. If it called lookupExactOcc_either when there were no matching GlobalRdrElts in the otherwise case, it would return an error message. This could be caused when lookupThName_maybe in Template Haskell was looking in different namespaces (thRdrNameGuesses), guessing different namespaces that the name wasn't guaranteed to be found in. However, by addressing this some more accurate errors were being lost in the conversion to Maybes. So some of the lookup* functions have been shuffled about so that errors should always be ignored in lookup*_maybes, and propagated otherwise. This fixes #18263 - - - - - 9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00 Initialize the allocation counter in GHCi to 0 (Fixes #16012) According to the documentation for the function `getAllocationCounter` in [System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html) initialize the allocationCounter also in GHCi to 0. - - - - - 8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00 test: fix conc038 We had spurious failures of conc038 test on CI with stdout: ``` newThread started -mainThread -Haskell: 2 newThread back again +mainThread 1 sec later shutting down +Haskell: 2 ``` - - - - - 4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00 Release Notes: Add news from the pattern-match checker [skip ci] - - - - - 3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00 Only test T16190 with the NCG T16190 is meant to test a NCG feature. It has already caused spurious failures in other MRs (e.g. !2165) when LLVM is used. - - - - - 2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00 DynFlags refactoring VIII (#17957) * Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.* * Add LlvmOpts datatype to store Llvm backend options * Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and Llvm.MetaExpr) which require LlvmOpts. * Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`) - - - - - 7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove unused code - - - - - 72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor homeUnit * rename thisPackage into homeUnit * document and refactor several Backpack things - - - - - 8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Rename unsafeGetUnitInfo into unsafeLookupUnit - - - - - f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Add allowVirtualUnits field in PackageState Instead of always querying DynFlags to know whether we are allowed to use virtual units (i.e. instantiated on-the-fly, cf Note [About units] in GHC.Unit), we store it once for all in `PackageState.allowVirtualUnits`. This avoids using DynFlags too much (cf #17957) and is preliminary work for #14335. - - - - - e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Enhance UnitId use * use UnitId instead of String to identify wired-in units * use UnitId instead of Unit in the backend (Unit are only use by Backpack to produce type-checked interfaces, not real code) * rename lookup functions for consistency * documentation - - - - - 9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove LinkerUnitId type alias - - - - - d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor WiredMap * Remove WiredInUnitId and WiredUnitId type aliases - - - - - 3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document and refactor `mkUnit` and `mkUnitInfoMap` - - - - - d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove PreloadUnitId type alias - - - - - f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename listUnitInfoMap into listUnitInfo There is no Map involved - - - - - ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc. - - - - - 202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Make ClosureUnitInfoMap uses UnitInfoMap - - - - - 55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove ClosureUnitInfoMap - - - - - 653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit (2) * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc. - - - - - ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move dump_mod_map into initUnits - - - - - 598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move wiring of homeUnitInstantiations outside of mkUnitState - - - - - 437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00 Avoid timing module map dump in initUnits - - - - - 9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove preload parameter of mkUnitState * Remove preload parameter (unused) * Don't explicitly return preloaded units: redundant because already returned as "preloadUnits" field of UnitState - - - - - 266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: refactor unwireUnit - - - - - 9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document getPreloadUnitsAnd - - - - - bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: remove useless add_package parameter - - - - - 36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: make listVisibleModuleNames take a UnitState - - - - - 5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document add_package - - - - - 4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document closeUnitDeps - - - - - 42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: findWiredInUnits - - - - - a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: reportCycles, reportUnusable - - - - - 8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: merge_databases - - - - - fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: add UnitConfig datatype Avoid directly querying flags from DynFlags to build the UnitState. Instead go via UnitConfig so that we could reuse this to make another UnitState for plugins. - - - - - 4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move distrustAll into mkUnitState - - - - - 28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Create helper upd_wired_in_home_instantiations - - - - - ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Put database cache in UnitConfig - - - - - bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00 Don't return preload units when we set DyNFlags Preload units can be retrieved in UnitState when needed (i.e. in GHCi) - - - - - 1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 NCGConfig: remove useless ncgUnitId field - - - - - c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Doc: fix some comments - - - - - 456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Bump haddock submodule and allow metric decrease Metric Decrease: T12150 T12234 T5837 Metric Increase: T16190 - - - - - 42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00 Trim the demand for recursive product types Ticket #18304 showed that we need to be very careful when exploring the demand (esp usage demand) on recursive product types. This patch solves the problem by trimming the demand on such types -- in effect, a form of "widening". See the Note [Trimming a demand to a type] in DmdAnal, which explains how I did this by piggy-backing on an existing mechansim for trimming demands becuase of GADTs. The significant payload of this patch is very small indeed: * Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to avoid looking through recursive types. But on the way * I found that ae_rec_tc was entirely inoperative and did nothing. So I removed it altogether from DmdAnal. * I moved some code around in DmdAnal and Demand. (There are no actual changes in dmdFix.) * I changed the API of DmsAnal.dmdAnalRhsLetDown to return a StrictSig rather than a decorated Id * I removed the dead function peelTsFuns from Demand Performance effects: Nofib: 0.0% changes. Not surprising, because they don't use recursive products Perf tests T12227: 1% increase in compiler allocation, becuase $cto gets w/w'd. It did not w/w before because it takes a deeply nested argument, so the worker gets too many args, so we abandon w/w altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough) With this patch we trim the demands. That is not strictly necessary (since these Generic type constructors are like tuples -- they can't cause a loop) but the net result is that we now w/w $cto which is fine. UniqLoop: 16% decrease in /runtime/ allocation. The UniqSupply is a recursive product, so currently we abandon all strictness on 'churn'. With this patch 'churn' gets useful strictness, and we w/w it. Hooray Metric Decrease: UniqLoop Metric Increase: T12227 - - - - - 87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00 Add introductory prose for Data.Traversable - - - - - 9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00 Fix #12073: Add MonadFix Q instance - - - - - 220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00 testsuite: Increase size of T12150 As noted in #18319, this test was previously very fragile. Increase its size to make it more likely that its fails with its newly-increased acceptance threshold. Metric Increase: T12150 - - - - - 8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00 gitlab-ci: Always push perf notes Previously we ci.sh would run with `set -e` implying that we wouldn't push perf notes if the testsuite were to fail, even if it *only* failed due to perf notes. This rendered the whole performance testing story quite fragile as a single regressing commit would cause every successive commit to fail since a new baseline would not be uploaded. Fix this by ensuring that we always push performance notes. - - - - - 7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00 gitlab-ci: Eliminate redundant push of CI metrics - - - - - a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00 Use HsForAllTelescope to avoid inferred, visible foralls Currently, `HsForAllTy` permits the combination of `ForallVis` and `Inferred`, but you can't actually typecheck code that uses it (e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a new `HsForAllTelescope` data type that makes a type-level distinction between visible and invisible `forall`s such that visible `forall`s do not track `Specificity`. That part of the patch is actually quite small; the rest is simply changing consumers of `HsType` to accommodate this new type. Fixes #18235. Bumps the `haddock` submodule. - - - - - c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00 winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges. The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00 codeGen: Don't discard live case binders in unsafeEqualityProof logic Previously CoreToStg would unconditionally discard cases of the form: case unsafeEqualityProof of wild { _ -> rhs } and rather replace the whole thing with `rhs`. However, in some cases (see #18227) the case binder is still live, resulting in unbound occurrences in `rhs`. Fix this by only discarding the case if the case binder is dead. Fixes #18227. - - - - - e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00 testsuite: Add tests for #18227 T18227A is the original issue which gave rise to the ticket and depends upon bytestring. T18227B is a minimized reproducer. - - - - - 8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Fix rts include and library paths Fixes two bugs: * (?) and (<>) associated in a surprising way * We neglected to include libdw paths in the rts configure flags - - - - - bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Drop redundant GHC arguments Cabal should already be passing this arguments to GHC. - - - - - 01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00 FFI: Fix pass small ints in foreign call wrappers The Haskell calling convention requires integer parameters smaller than wordsize to be promoted to wordsize (where the upper bits are don't care). To access such small integer parameter read a word from the parameter array and then cast that word to the small integer target type. Fixes #15933 - - - - - 502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00 Fix "ndecreasingIndentation" in manual (#18116) - - - - - 9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00 Use foldl' in unionManyUniqDSets - - - - - 761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00 Load .lo as well. Some archives contain so called linker objects, with the affectionate .lo suffic. For example the musl libc.a will come in that form. We still want to load those objects, hence we should not discard them and look for .lo as well. Ultimately we might want to fix this proerly by looking at the file magic. - - - - - cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00 User's Guide: KnownNat evidence is Natural This bit of documentation got outdated after commit 1fcede43d2b30f33b7505e25eb6b1f321be0407f - - - - - d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00 Fix typos and formatting in user guide - - - - - 56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00 Resolve TODO - - - - - 3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00 Rename TcHoleErrors to GHC.Tc.Errors.Hole - - - - - d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00 hadrian: Build with threaded runtime if available See #16873. - - - - - 0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00 T16190: only measure bytes_allocated Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics fluctuate by 13%. - - - - - 4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00 docs: fix formatting in users guide - - - - - eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00 Move CLabel assertions into smart constructors (#17957) It avoids using DynFlags in the Outputable instance of Clabel to check assertions at pretty-printing time. - - - - - 7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00 base: Bump to 4.15.0.0 - - - - - 20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00 configure: Use grep -q instead of --quiet The latter is apparently not supported by busybox. - - - - - 40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00 Linear types (#15981) This is the first step towards implementation of the linear types proposal (https://github.com/ghc-proposals/ghc-proposals/pull/111). It features * A language extension -XLinearTypes * Syntax for linear functions in the surface language * Linearity checking in Core Lint, enabled with -dlinear-core-lint * Core-to-core passes are mostly compatible with linearity * Fields in a data type can be linear or unrestricted; linear fields have multiplicity-polymorphic constructors. If -XLinearTypes is disabled, the GADT syntax defaults to linear fields The following items are not yet supported: * a # m -> b syntax (only prefix FUN is supported for now) * Full multiplicity inference (multiplicities are really only checked) * Decent linearity error messages * Linear let, where, and case expressions in the surface language (each of these currently introduce the unrestricted variant) * Multiplicity-parametric fields * Syntax for annotating lambda-bound or let-bound with a multiplicity * Syntax for non-linear/multiple-field-multiplicity records * Linear projections for records with a single linear field * Linear pattern synonyms * Multiplicity coercions (test LinearPolyType) A high-level description can be found at https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation Following the link above you will find a description of the changes made to Core. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Matthew Pickering * Arnaud Spiwack With contributions from: * Mark Barbone * Alexander Vershilov Updates haddock submodule. - - - - - 6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00 Various performance improvements This implements several general performance improvements to GHC, to offset the effect of the linear types change. General optimisations: - Add a `coreFullView` function which iterates `coreView` on the head. This avoids making function recursive solely because the iterate `coreView` themselves. As a consequence, this functions can be inlined, and trigger case-of-known constructor (_e.g._ `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`, `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`, `tyConAppTyCon_maybe`). The common pattern about all these functions is that they are almost always used as views, and immediately consumed by a case expression. This commit also mark them asx `INLINE`. - In `subst_ty` add a special case for nullary `TyConApp`, which avoid allocations altogether. - Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This required quite a bit of module shuffling. case. `myTyConApp` enforces crucial sharing, which was lost during substitution. See also !2952 . - Make `subst_ty` stricter. - In `eqType` (specifically, in `nonDetCmpType`), add a special case, tested first, for the very common case of nullary `TyConApp`. `nonDetCmpType` has been made `INLINE` otherwise it is actually a regression. This is similar to the optimisations in !2952. Linear-type specific optimisations: - Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in the definition of the pattern synonyms `One` and `Many`. - Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`: `Multiplicity` now import `Type` normally, rather than from the `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the `One` and `Many` pattern synonyms. - Make `updateIdTypeAndMult` strict in its type and multiplicity - The `scaleIdBy` gets a specialised definition rather than being an alias to `scaleVarBy` - `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type, Type)` instead of `Type -> Maybe (Scaled Type, Type)` - Remove the `MultMul` pattern synonym in favour of a view `isMultMul` because pattern synonyms appear not to inline well. - in `eqType`, in a `FunTy`, compare multiplicities last: they are almost always both `Many`, so it helps failing faster. - Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the instances of `TyConApp ManyDataConTy []` are physically the same. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Arnaud Spiwack Metric Decrease: haddock.base T12227 T12545 T12990 T1969 T3064 T5030 T9872b Metric Increase: haddock.base haddock.Cabal haddock.compiler T12150 T12234 T12425 T12707 T13035 T13056 T15164 T16190 T18304 T1969 T3064 T3294 T5631 T5642 T5837 T6048 T9020 T9233 T9675 T9872a T9961 WWRec - - - - - 57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Remove integer-simple integer-simple uses lists of words (`[Word]`) to represent big numbers instead of ByteArray#: * it is less efficient than the newer ghc-bignum native backend * it isn't compatible with the big number representation that is now shared by all the ghc-bignum backends (based on the one that was used only in integer-gmp before). As a consequence, we simply drop integer-simple - - - - - 9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00 ghc-bignum library ghc-bignum is a newer package that aims to replace the legacy integer-simple and integer-gmp packages. * it supports several backends. In particular GMP is still supported and most of the code from integer-gmp has been merged in the "gmp" backend. * the pure Haskell "native" backend is new and is much faster than the previous pure Haskell implementation provided by integer-simple * new backends are easier to write because they only have to provide a few well defined functions. All the other code is common to all backends. In particular they all share the efficient small/big number distinction previously used only in integer-gmp. * backends can all be tested against the "native" backend with a simple Cabal flag. Backends are only allowed to differ in performance, their results should be the same. * Add `integer-gmp` compat package: provide some pattern synonyms and function aliases for those in `ghc-bignum`. It is intended to avoid breaking packages that depend on `integer-gmp` internals. Update submodules: text, bytestring Metric Decrease: Conversions ManyAlternatives ManyConstructors Naperian T10359 T10547 T10678 T12150 T12227 T12234 T12425 T13035 T13719 T14936 T1969 T4801 T4830 T5237 T5549 T5837 T8766 T9020 parsing001 space_leak_001 T16190 haddock.base On ARM and i386, T17499 regresses (+6% > 5%). On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%). Metric Increase: T17499 T13701 - - - - - 96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update compiler Thanks to ghc-bignum, the compiler can be simplified: * Types and constructors of Integer and Natural can be wired-in. It means that we don't have to query them from interfaces. It also means that numeric literals don't have to carry their type with them. * The same code is used whatever ghc-bignum backend is enabled. In particular, conversion of bignum literals into final Core expressions is now much more straightforward. Bignum closure inspection too. * GHC itself doesn't depend on any integer-* package anymore * The `integerLibrary` setting is gone. - - - - - 0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `base` package * GHC.Natural isn't implemented in `base` anymore. It is provided by ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural primitives in `base` without fearing issues with built-in rewrite rules (cf #15286) * `base` doesn't conditionally depend on an integer-* package anymore, it depends on ghc-bignum * Some duplicated code in integer-* can now be factored in GHC.Float * ghc-bignum tries to use a uniform naming convention so most of the other changes are renaming - - - - - aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `make` based build system * replace integer-* package selection with ghc-bignum backend selection - - - - - f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update testsuite * support detection of slow ghc-bignum backend (to replace the detection of integer-simple use). There are still some test cases that the native backend doesn't handle efficiently enough. * remove tests for GMP only functions that have been removed from ghc-bignum * fix test results showing dependent packages (e.g. integer-gmp) or showing suggested instances * fix test using Integer/Natural API or showing internal names - - - - - dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update Hadrian * support ghc-bignum backend selection in flavours and command-line * support ghc-bignum "--check" flag (compare results of selected backend against results of the native one) in flavours and command-line (e.g. pass --bignum=check-gmp" to check the "gmp" backend) * remove the hack to workaround #15286 * build GMP only when the gmp backend is used * remove hacks to workaround `text` package flags about integer-*. We fix `text` to use ghc-bignum unconditionally in another patch - - - - - fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Bump bytestring and text submodules - - - - - 1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00 docs: mention -hiedir in docs for -outputdir [skip ci] - - - - - 729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00 Hadrian: fix build on Mac OS Catalina (#17798) - - - - - 95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00 Relax allocation threshold for T12150. This test performs little work, so the most minor allocation changes often cause the test to fail. Increasing the threshold to 2% should help with this. - - - - - 8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00 hadrian: Bump pinned cabal.project to an existent index-state - - - - - 08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00 Fix uninitialized field read in Linker.c Valgrind report of the bug when running the test `linker_unload`: ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522) ==29666== by 0x36C0600: loadArchive (LoadArchive.c:626) ==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload) ==29666== ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507) ==29666== by 0x369CA8D: loadObj_ (Linker.c:1536) ==29666== by 0x369CB17: loadObj (Linker.c:1557) ==29666== by 0x3866BC: main (linker_unload.c:33) The problem is `mkOc` allocates a new `ObjectCode` and calls `setOcInitialStatus` without initializing the `status` field. `setOcInitialStatus` reads the field as first thing: static void setOcInitialStatus(ObjectCode* oc) { if (oc->status == OBJECT_DONT_RESOLVE) return; if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; } } `setOcInitialStatus` is unsed in two places for two different purposes: in `mkOc` where we don't have the `status` field initialized yet (`mkOc` is supposed to initialize it), and `loadOc` where we do have `status` field initialized and we want to update it. Instead of splitting the function into two functions which are both called just once I inline the functions in the use sites and remove it. Fixes #18342 - - - - - da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00 fix windows bootstrap due to linker changes - - - - - 2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00 DynFlags: store default depth in SDocContext (#17957) It avoids having to use DynFlags to reach for pprUserLength. - - - - - d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00 Move tablesNextToCode field into Platform tablesNextToCode is a platform setting and doesn't belong into DynFlags (#17957). Doing this is also a prerequisite to fix #14335 where we deal with two platforms (target and host) that may have different platform settings. - - - - - 809caedf by John Ericson at 2020-06-23T22:47:37-04:00 Switch from HscSource to IsBootInterface for module lookup in GhcMake We look up modules by their name, and not their contents. There is no way to separately reference a signature vs regular module; you get what you get. Only boot files can be referenced indepenently with `import {-# SOURCE #-}`. - - - - - 7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Cmm: introduce SAVE_REGS/RESTORE_REGS We don't want to save both Fn and Dn register sets on x86-64 as they are aliased to the same arch register (XMMn). Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]` which makes a set of Cmm registers alive so that they cover all arch registers used to pass parameter, we could have Fn, Dn and XMMn alive at the same time. It made the LLVM code generator choke (see #17920). Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of registers. - - - - - 2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00 CmmToC: don't add extern decl to parsed Cmm data Previously, if a .cmm file *not in the RTS* contained something like: ```cmm section "rodata" { msg : bits8[] "Test\n"; } ``` It would get compiled by CmmToC into: ```c ERW_(msg); const char msg[] = "Test\012"; ``` and fail with: ``` /tmp/ghc32129_0/ghc_4.hc:5:12: error: error: conflicting types for \u2018msg\u2019 const char msg[] = "Test\012"; ^~~ In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error: /tmp/ghc32129_0/ghc_4.hc:4:6: error: note: previous declaration of \u2018msg\u2019 was here ERW_(msg); ^ /builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error: note: in definition of macro \u2018ERW_\u2019 #define ERW_(X) extern StgWordArray (X) ^ ``` See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes Now we don't generate these extern declarations (ERW_, etc.) for top-level data. It shouldn't change anything for the RTS (the only place we use .cmm files) as it is already special cased in `GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit extern declarations when needed. Note that it allows `cgrun069` test to pass with CmmToC (cf #15467). - - - - - 5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00 LLVM: refactor and comment register padding code (#17920) - - - - - cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Add tests for #17920 Metric Decrease: T12150 T12234 - - - - - a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00 Fix issue #18262 by zonking constraints after solving Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results. - - - - - 181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00 Fix a buglet in Simplify.simplCast This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal - - - - - 625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00 Two small tweaks to Coercion.simplifyArgsWorker These tweaks affect the inner loop of simplifyArgsWorker, which in turn is called from the flattener in Flatten.hs. This is a key perf bottleneck to T9872{a,b,c,d}. These two small changes have a modest but useful benefit. No change in functionality whatsoever. Relates to #18354 - - - - - b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00 Don't use timesInt2# with GHC < 8.11 (fix #18358) - - - - - 7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00 Fix invalid printf format - - - - - a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00 Add missing entry to freeNamesItem (#18369) - - - - - 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 1a184ceb by Ben Gamari at 2020-11-01T13:57:10-05:00 rts: Introduce performBlockingMajorGC - - - - - 17 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Builtin/RebindableNames.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da04a8647230fa97e84cfc4b319ce097e2b2d734...1a184ceb8d4c3093fe1a8a5085a747943274a8d9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da04a8647230fa97e84cfc4b319ce097e2b2d734...1a184ceb8d4c3093fe1a8a5085a747943274a8d9 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 Sun Nov 1 19:01:18 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 14:01:18 -0500 Subject: [Git][ghc/ghc][wip/ticky-eventlog] 71 commits: Remove Proxy# argument in Data.Typeable.Internal Message-ID: <5f9f05fe289aa_7853fb5f57628e4287532@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/ticky-eventlog at Glasgow Haskell Compiler / GHC Commits: 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 5517f893 by Ben Gamari at 2020-11-01T14:00:06-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/239a228917cd5d152d66fe21fd0c421dead042c6...5517f893601fce0887740d645e6147ef8d8f4868 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/239a228917cd5d152d66fe21fd0c421dead042c6...5517f893601fce0887740d645e6147ef8d8f4868 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 Sun Nov 1 22:53:55 2020 From: gitlab at gitlab.haskell.org (Alan Zimmerman) Date: Sun, 01 Nov 2020 17:53:55 -0500 Subject: [Git][ghc/ghc][wip/T18888] 22 commits: hadrian: Don't quote metric baseline argument Message-ID: <5f9f3c83bf5f8_785ed29c5029762@gitlab.haskell.org.mail> Alan Zimmerman pushed to branch wip/T18888 at Glasgow Haskell Compiler / GHC Commits: 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4490e45e by Alan Zimmerman at 2020-11-01T22:33:47+00:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a5fbe06d6b7138fa8dcdf70071e228d69c16c37...4490e45e4bdb2881c05c14f7e2505b3e98e61360 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a5fbe06d6b7138fa8dcdf70071e228d69c16c37...4490e45e4bdb2881c05c14f7e2505b3e98e61360 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 Sun Nov 1 23:27:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 18:27:44 -0500 Subject: [Git][ghc/ghc][wip/inlining-flags-docs] 750 commits: Enable large address space optimization on windows. Message-ID: <5f9f4470b9b54_7853fb64069f038302515@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/inlining-flags-docs at Glasgow Haskell Compiler / GHC Commits: 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 304c0409 by Matthew Pickering at 2020-11-01T18:27:41-05:00 Update inlining flags documentation - - - - - 23 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/test-metrics.sh - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Builtin/RebindableNames.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Uniques.hs-boot - compiler/GHC/Builtin/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2952d7fdfb64aab4e5e5c6958bd37c37eb115ba8...304c04095b7a5aa073a70559469aebe5b58d2c40 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2952d7fdfb64aab4e5e5c6958bd37c37eb115ba8...304c04095b7a5aa073a70559469aebe5b58d2c40 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 Sun Nov 1 23:45:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 18:45:26 -0500 Subject: [Git][ghc/ghc][wip/T18234] 6 commits: testsuite: Add performance test for #18698 Message-ID: <5f9f48963aba5_7853fb640fc80103047ad@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - a52540b3 by Ben Gamari at 2020-11-01T18:45:21-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 51b5386d by Ben Gamari at 2020-11-01T18:45:21-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/.hlint.yaml - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Data/FastString.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80105a93849b832c8223af3c23aa6fb505db4edf...51b5386d586fb2bfea8f4ee010019dde935eac82 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80105a93849b832c8223af3c23aa6fb505db4edf...51b5386d586fb2bfea8f4ee010019dde935eac82 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 Sun Nov 1 23:54:19 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 01 Nov 2020 18:54:19 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: testsuite: Add --top flag to driver Message-ID: <5f9f4aab191b6_7853fb5e221855431234c@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 5e9eec58 by GHC GitLab CI at 2020-11-01T18:54:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 078252c3 by Ben Gamari at 2020-11-01T18:54:06-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 58e81685 by Simon Peyton Jones at 2020-11-01T18:54:07-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - e015d282 by Ben Gamari at 2020-11-01T18:54:07-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 19 changed files: - compiler/GHC/Tc/Module.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/ffi.rst - hadrian/src/Builder.hs - hadrian/src/Settings/Builders/RunTest.hs - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - + testsuite/tests/ghci/scripts/T13795.script - + testsuite/tests/ghci/scripts/T13795.stdout - + testsuite/tests/ghci/scripts/T18828.hs - + testsuite/tests/ghci/scripts/T18828.script - + testsuite/tests/ghci/scripts/T18828.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/rts/T5423.hs - testsuite/tests/rts/T5423.stdout - testsuite/tests/rts/T5423_c.c - testsuite/tests/rts/T5423_cmm.cmm Changes: ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -2629,12 +2629,13 @@ tcRnType hsc_env flexi normalise rdr_type -- Do validity checking on type ; checkValidType (GhciCtxt True) ty - ; ty' <- if normalise - then do { fam_envs <- tcGetFamInstEnvs - ; let (_, ty') - = normaliseType fam_envs Nominal ty - ; return ty' } - else return ty ; + -- Optionally (:k vs :k!) normalise the type. Does two things: + -- normaliseType: expand type-family applications + -- expandTypeSynonyms: expand type synonyms (#18828) + ; fam_envs <- tcGetFamInstEnvs + ; let ty' | normalise = expandTypeSynonyms $ snd $ + normaliseType fam_envs Nominal ty + | otherwise = ty ; return (ty', mkInfForAllTys kvs (tcTypeKind ty')) } ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -37,6 +37,9 @@ Compiler - Type checker plugins which work with the natural numbers now should use ``naturalTy`` kind instead of ``typeNatKind``, which has been removed. +- GHCi's ``:kind!`` command now expands through type synonyms in addition to type + families. See :ghci-cmd:`:kind`. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -83,6 +83,21 @@ For more details on the implementation see the Paper: Last known to be accessible `here `_. +Varargs not supported by ``ccall`` calling convention +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Note that functions requiring varargs arguments are unsupported by the ``ccall`` +calling convention. Foreign imports needing to call such functions should rather +use the ``capi`` convention, giving an explicit signature for the needed +call-pattern. For instance, one could write: :: + + foreign import "capi" "printf" + my_printf :: Ptr CChar -> CInt -> IO () + + printInt :: CInt -> IO () + printInt n = my_printf "printed number %d" n + + .. _ffi-ghcexts: GHC extensions to the FFI Chapter ===================================== hadrian/src/Builder.hs ===================================== @@ -304,6 +304,11 @@ instance H.Builder Builder where Makeindex -> unit $ cmd' [Cwd output] [path] (buildArgs ++ [input]) Tar _ -> cmd' buildOptions echo [path] buildArgs + + -- RunTest produces a very large amount of (colorised) output; + -- Don't attempt to capture it. + RunTest -> cmd echo [path] buildArgs + _ -> cmd' echo [path] buildArgs -- TODO: Some builders are required only on certain platforms. For example, ===================================== hadrian/src/Settings/Builders/RunTest.hs ===================================== @@ -102,6 +102,7 @@ runTestBuilderArgs = builder RunTest ? do -- TODO: set CABAL_MINIMAL_BUILD/CABAL_PLUGIN_BUILD mconcat [ arg $ "testsuite/driver/runtests.py" , pure [ "--rootdir=" ++ testdir | testdir <- rootdirs ] + , arg "--top", arg (top -/- "testsuite") , arg "-e", arg $ "windows=" ++ show windowsHost , arg "-e", arg $ "darwin=" ++ show osxHost , arg "-e", arg $ "config.local=False" @@ -129,7 +130,6 @@ runTestBuilderArgs = builder RunTest ? do , arg "-e", arg $ "config.ghc_dynamic_by_default=" ++ show hasDynamicByDefault , arg "-e", arg $ "config.ghc_dynamic=" ++ show hasDynamic - , arg "-e", arg $ "config.top=" ++ show (top -/- "testsuite") , arg "-e", arg $ "config.wordsize=" ++ show wordsize , arg "-e", arg $ "config.os=" ++ show os , arg "-e", arg $ "config.arch=" ++ show arch ===================================== testsuite/driver/runtests.py ===================================== @@ -14,6 +14,7 @@ import tempfile import time import re import traceback +from pathlib import Path # We don't actually need subprocess in runtests.py, but: # * We do need it in testlibs.py @@ -56,6 +57,7 @@ parser = argparse.ArgumentParser(description="GHC's testsuite driver") perf_group = parser.add_mutually_exclusive_group() parser.add_argument("-e", action='append', help="A string to execute from the command line.") +parser.add_argument("--top", type=Path, help="path to top of testsuite/ tree") parser.add_argument("--config-file", action="append", help="config file") parser.add_argument("--config", action='append', help="config field") parser.add_argument("--rootdir", action='append', help="root of tree containing tests (default: .)") @@ -104,6 +106,9 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +if args.top: + config.top = args.top + if args.only: config.only = args.only config.run_only_some_tests = True @@ -277,7 +282,7 @@ testopts_local.x = TestOptions() # if timeout == -1 then we try to calculate a sensible value if config.timeout == -1: - config.timeout = int(read_no_crs(config.top + '/timeout/calibrate.out')) + config.timeout = int(read_no_crs(config.top / 'timeout' / 'calibrate.out')) print('Timeout is ' + str(config.timeout)) print('Known ways: ' + ', '.join(config.other_ways)) ===================================== testsuite/driver/testglobals.py ===================================== @@ -22,7 +22,7 @@ class TestConfig: def __init__(self): # Where the testsuite root is - self.top = '' + self.top = Path('.') # Directories below which to look for test description files (foo.T) self.rootdirs = [] ===================================== testsuite/driver/testlib.py ===================================== @@ -1110,7 +1110,7 @@ def do_test(name: TestName, dst_makefile = in_testdir('Makefile') if src_makefile.exists(): makefile = src_makefile.read_text(encoding='UTF-8') - makefile = re.sub('TOP=.*', 'TOP=' + config.top, makefile, 1) + makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1) dst_makefile.write_text(makefile, encoding='UTF-8') if opts.pre_cmd: ===================================== testsuite/mk/test.mk ===================================== @@ -256,13 +256,13 @@ endif RUNTEST_OPTS += \ --rootdir=. \ --config-file=$(CONFIG) \ + --top="$(TOP_ABS)" \ -e 'config.platform="$(TARGETPLATFORM)"' \ -e 'config.os="$(TargetOS_CPP)"' \ -e 'config.arch="$(TargetARCH_CPP)"' \ -e 'config.wordsize="$(WORDSIZE)"' \ -e 'config.timeout=int($(TIMEOUT)) or config.timeout' \ - -e 'config.exeext="$(exeext)"' \ - -e 'config.top="$(TOP_ABS)"' + -e 'config.exeext="$(exeext)"' # Wrap non-empty program paths in quotes, because they may contain spaces. Do # it here, so we don't have to (and don't forget to do it) in the .T test ===================================== testsuite/tests/ghci/scripts/T13795.script ===================================== @@ -0,0 +1,2 @@ +type A = () +:kind! A ===================================== testsuite/tests/ghci/scripts/T13795.stdout ===================================== @@ -0,0 +1,2 @@ +A :: * += () ===================================== testsuite/tests/ghci/scripts/T18828.hs ===================================== @@ -0,0 +1,31 @@ +{-# Language ConstraintKinds #-} +{-# Language DataKinds #-} +{-# Language GADTs #-} +{-# Language PolyKinds #-} +{-# Language RankNTypes #-} +{-# Language StandaloneKindSignatures #-} +{-# Language TypeFamilies #-} +{-# Language TypeOperators #-} +module T18828 where + +import Data.Kind + +type Cat :: Type -> Type +type Cat ob = ob -> ob -> Type + +type Dict :: Constraint -> Type +data Dict cls where + Dict :: cls => Dict cls + +type (:-) :: Cat Constraint +newtype cls1 :- cls2 where + Sub :: (cls1 => Dict cls2) -> (cls1 :- cls2) + +type ObjectSyn :: Cat ob -> Type +type ObjectSyn (cat :: ob -> ob -> Type) = ob + +type + ObjectFam :: Cat ob -> Type +type family + ObjectFam cat where + ObjectFam @ob cat = ob ===================================== testsuite/tests/ghci/scripts/T18828.script ===================================== @@ -0,0 +1,9 @@ +:load T18828 +:set -XDataKinds -XKindSignatures -XRankNTypes +import Data.Type.Equality +:k! ObjectSyn (->) +:k! forall ob. ObjectSyn ((:~:) :: Cat ob) +:k! ObjectSyn (:-) +:k! ObjectFam (->) +:k! forall ob. ObjectFam ((:~:) :: Cat ob) +:k! ObjectFam (:-) ===================================== testsuite/tests/ghci/scripts/T18828.stdout ===================================== @@ -0,0 +1,12 @@ +ObjectSyn (->) :: * += * +forall ob. ObjectSyn ((:~:) :: Cat ob) :: * += ob +ObjectSyn (:-) :: * += Constraint +ObjectFam (->) :: * += * +forall ob. ObjectFam ((:~:) :: Cat ob) :: * += ob +ObjectFam (:-) :: * += Constraint ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -279,6 +279,7 @@ test('T13591', expect_broken(13591), ghci_script, ['T13591.script']) test('T13699', normal, ghci_script, ['T13699.script']) test('T13988', normal, ghci_script, ['T13988.script']) test('T13407', normal, ghci_script, ['T13407.script']) +test('T13795', normal, ghci_script, ['T13795.script']) test('T13963', normal, ghci_script, ['T13963.script']) test('T14342', [extra_hc_opts("-XOverloadedStrings -XRebindableSyntax")], ghci_script, ['T14342.script']) @@ -322,3 +323,4 @@ test('T17669', [extra_run_opts('-fexternal-interpreter -fobject-code'), expect_b test('T18501', normal, ghci_script, ['T18501.script']) test('T18644', normal, ghci_script, ['T18644.script']) test('T18755', normal, ghci_script, ['T18755.script']) +test('T18828', normal, ghci_script, ['T18828.script']) ===================================== testsuite/tests/rts/T5423.hs ===================================== @@ -1,3 +1,5 @@ +-- | Verify that @foreign import prim@ calls with more than 10 arguments +-- are lowered correctly. {-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-} ===================================== testsuite/tests/rts/T5423.stdout ===================================== @@ -1,2 +1,2 @@ -111 112 113 114 115 116 117 118 119 120 +111 112 113 114 115 116 117 118 119 120 120 ===================================== testsuite/tests/rts/T5423_c.c ===================================== @@ -1,6 +1,34 @@ +#include #include void flush_stdout(void) { fflush(stdout); } + +void print_it( + StgWord r1, + StgWord r2, + StgWord r3, + StgWord r4, + StgWord r5, + StgWord r6, + StgWord r7, + StgWord r8, + StgWord r9, + StgWord r10 + ) +{ + printf("%" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word "\n", + r1, r2, r3, r4, r5, + r6, r7, r8, r9, r10); +} ===================================== testsuite/tests/rts/T5423_cmm.cmm ===================================== @@ -10,7 +10,6 @@ test (W_ r1, W_ r9, W_ r10) { - foreign "C" printf("%d %d %d %d %d %d %d %d %d %d\n", - r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); + foreign "C" print_it(r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); return (r10); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ba7415574a201a4db0f839ef0906982b751c92e4...e015d2824c5c17dd3be9fbb7f1467c800b219a75 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ba7415574a201a4db0f839ef0906982b751c92e4...e015d2824c5c17dd3be9fbb7f1467c800b219a75 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 Mon Nov 2 02:59:29 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 21:59:29 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/backports Message-ID: <5f9f7611871c2_7853fb5ea6a09343242eb@gitlab.haskell.org.mail> Ben Gamari deleted branch wip/backports at Glasgow Haskell Compiler / GHC -- 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 Mon Nov 2 02:59:31 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 21:59:31 -0500 Subject: [Git][ghc/ghc][ghc-9.0] Api Annotations: Introduce AnnPercent for HsExplicitMult Message-ID: <5f9f761360126_7853fb642b38264324412@gitlab.haskell.org.mail> Ben Gamari pushed to branch ghc-9.0 at Glasgow Haskell Compiler / GHC Commits: 3d7f5ec8 by Alan Zimmerman at 2020-11-01T11:45:02-05:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' (cherry picked from commit c15b5f25ad54164c951e797ecbd10d0df1cf4ba6) - - - - - 3 changed files: - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs Changes: ===================================== compiler/GHC/Parser.y ===================================== @@ -1961,17 +1961,18 @@ type :: { LHsType GhcPs } [mu AnnRarrow $2] } | btype mult '->' ctype {% hintLinear (getLoc $2) - >> ams $1 [mj AnnMult $2,mu AnnRarrow $3] -- See Note [GADT decl discards annotations] - >> ams (sLL $1 $> $ HsFunTy noExtField ((unLoc $2) (toUnicode $3)) $1 $4) - [mj AnnMult $2,mu AnnRarrow $3] } + >> let (arr, ann) = (unLoc $2) (toUnicode $3) + in (ams $1 [ann,mu AnnRarrow $3] -- See Note [GADT decl discards annotations] + >> ams (sLL $1 $> $ HsFunTy noExtField arr $1 $4) + [ann,mu AnnRarrow $3]) } | btype '->.' ctype {% hintLinear (getLoc $2) >> ams $1 [mu AnnLollyU $2] -- See Note [GADT decl discards annotations] >> ams (sLL $1 $> $ HsFunTy noExtField (HsLinearArrow UnicodeSyntax) $1 $3) [mu AnnLollyU $2] } -mult :: { Located (IsUnicodeSyntax -> HsArrow GhcPs) } - : PREFIX_PERCENT atype { sLL $1 $> (\u -> mkMultTy u $2) } +mult :: { Located (IsUnicodeSyntax -> (HsArrow GhcPs, AddAnn)) } + : PREFIX_PERCENT atype { sLL $1 $> (\u -> mkMultTy u $1 $2) } btype :: { LHsType GhcPs } : tyapps {% mergeOps (unLoc $1) } ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -302,7 +302,7 @@ data AnnKeywordId | AnnMdo | AnnMinus -- ^ '-' | AnnModule - | AnnMult -- ^ '%1' + | AnnPercentOne -- ^ '%1' -- for HsLinearArrow | AnnNewtype | AnnName -- ^ where a name loses its location in the AST, this carries it | AnnOf @@ -319,6 +319,7 @@ data AnnKeywordId | AnnDollarDollar -- ^ prefix '$$' -- TemplateHaskell | AnnPackageName | AnnPattern + | AnnPercent -- ^ '%' -- for HsExplicitMult | AnnProc | AnnQualified | AnnRarrow -- ^ '->' ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -3069,9 +3069,10 @@ mkLHsOpTy x op y = let loc = getLoc x `combineSrcSpans` getLoc op `combineSrcSpans` getLoc y in L loc (mkHsOpTy x op y) -mkMultTy :: IsUnicodeSyntax -> LHsType GhcPs -> HsArrow GhcPs -mkMultTy u (L _ (HsTyLit _ (HsNumTy _ 1))) = HsLinearArrow u -mkMultTy u t = HsExplicitMult u t +mkMultTy :: IsUnicodeSyntax -> Located Token -> LHsType GhcPs -> (HsArrow GhcPs, AddAnn) +mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy _ 1))) + = (HsLinearArrow u, AddAnn AnnPercentOne (combineLocs tok t)) +mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok)) ----------------------------------------------------------------------------- -- Token symbols View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3d7f5ec8232d9053b192cb94b19c5d5e85bc46f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3d7f5ec8232d9053b192cb94b19c5d5e85bc46f4 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 Mon Nov 2 03:37:57 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 22:37:57 -0500 Subject: [Git][ghc/ghc][wip/T17609] 6 commits: testsuite: Add performance test for #18698 Message-ID: <5f9f7f154b04c_7853fb61d86f78c327260@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 1313c000 by Ben Gamari at 2020-11-01T22:37:52-05:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - a8792d49 by Ben Gamari at 2020-11-01T22:37:52-05:00 Add Note cross-reference for unique tag allocations - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b48a56f16068bd1d574e8042fe7581a192f357d2...a8792d493d30978d83a91456692dca34fbafd474 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b48a56f16068bd1d574e8042fe7581a192f357d2...a8792d493d30978d83a91456692dca34fbafd474 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 Mon Nov 2 04:04:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 01 Nov 2020 23:04:40 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] 9 commits: testsuite: Add performance test for #18698 Message-ID: <5f9f8558d818b_7853fb61cbc322c33256f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC Commits: bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 169c7bcc by Sven Tennie at 2020-11-01T23:02:21-05:00 deriveConstants: Add hie.yaml - - - - - 1f3235e5 by Sven Tennie at 2020-11-01T23:02:21-05:00 base: Generalize newStablePtrPrimMVar Make it polymorphic in the type of the MVar's value. - - - - - 44c1fff9 by Sven Tennie at 2020-11-01T23:03:18-05:00 Introduce snapshotting of thread's own stack Introduce `StackSnapshot#` type and the `cloneMyStack#` primop, allowing the user to reify the state of the calling thread's stack for later inspection. The stack snapshot is offline/cold, i.e. it isn't evaluated any further. For technical details, please see note [Stack Cloning]. - - - - - bcc93393 by Sven Tennie at 2020-11-01T23:03:18-05:00 Introduce cloning of other threads' stacks Introduce `cloneThreadStack` function, allowing threads to request snapshots of other threads' stacks. For technical details, please see note [Stack Cloning]. - - - - - 4e2fac38 by Sven Tennie at 2020-11-01T23:03:18-05:00 Introduce printing support for StackSnapshot#'s This refactors the RTS's existing Printer module to allow printing of StackSnapshot#'s. - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7223c48466d501a077f0331ae4f390269310d984...4e2fac38419a9f76ba1aadd081c58009e8a7ca9a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7223c48466d501a077f0331ae4f390269310d984...4e2fac38419a9f76ba1aadd081c58009e8a7ca9a 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 Mon Nov 2 05:56:22 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 00:56:22 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-ncg] 5 commits: [CmmSized Word] Constant Fold Message-ID: <5f9f9f8699af8_7853fb660b54c98338898@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC Commits: fe9a0293 by Moritz Angermann at 2020-11-02T10:02:15+08:00 [CmmSized Word] Constant Fold - - - - - a0903f8e by Moritz Angermann at 2020-11-02T10:03:44+08:00 [CmmSized Word] Fix testsuite - - - - - 4d64b5af by Moritz Angermann at 2020-11-02T11:25:08+08:00 fix bytestring bump - - - - - 13a7028b by Moritz Angermann at 2020-11-02T13:50:47+08:00 [CmmSized Word] More constant folds - - - - - e98e3d12 by Moritz Angermann at 2020-11-02T13:55:57+08:00 [SizedCmm Word] Trying to fix TH Quotes - - - - - 27 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/HsToCore/Quote.hs - libraries/bytestring - testsuite/tests/array/should_run/arr020.hs - testsuite/tests/backpack/should_compile/bkp16.stderr - testsuite/tests/codeGen/should_run/cgrun070.hs - testsuite/tests/codeGen/should_run/cgrun072.hs - testsuite/tests/codeGen/should_run/cgrun075.hs - testsuite/tests/codeGen/should_run/cgrun076.hs - testsuite/tests/codeGen/should_run/compareByteArrays.hs - testsuite/tests/dependent/should_compile/T14729.stderr - testsuite/tests/dependent/should_compile/T15743.stderr - testsuite/tests/dependent/should_compile/T15743e.stderr - testsuite/tests/ffi/should_run/T16650a.hs - testsuite/tests/ffi/should_run/T16650b.hs - testsuite/tests/ffi/should_run/UnliftedNewtypesByteArrayOffset.hs - testsuite/tests/indexed-types/should_compile/T15711.stderr - testsuite/tests/indexed-types/should_compile/T15852.stderr - testsuite/tests/lib/integer/integerImportExport.hs - testsuite/tests/polykinds/T15592.stderr - testsuite/tests/polykinds/T15592b.stderr - testsuite/tests/printer/T18052a.stderr - testsuite/tests/profiling/should_run/T3001-2.hs - testsuite/tests/simplCore/should_compile/T5359a.hs - testsuite/tests/typecheck/should_compile/T12763.stderr Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -54,6 +54,9 @@ module GHC.Builtin.Types ( -- * Word wordTyCon, wordDataCon, wordTyConName, wordTy, + -- * Word8 + word8TyCon, word8DataCon, word8Ty, + -- * List listTyCon, listTyCon_RDR, listTyConName, listTyConKey, nilDataCon, nilDataConName, nilDataConKey, @@ -348,9 +351,10 @@ nothingDataConName = mkWiredInDataConName UserSyntax gHC_MAYBE (fsLit "Nothing") justDataConName = mkWiredInDataConName UserSyntax gHC_MAYBE (fsLit "Just") justDataConKey justDataCon -wordTyConName, wordDataConName :: Name +wordTyConName, wordDataConName, word8DataConName :: Name wordTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "Word") wordTyConKey wordTyCon wordDataConName = mkWiredInDataConName UserSyntax gHC_TYPES (fsLit "W#") wordDataConKey wordDataCon +word8DataConName = mkWiredInDataConName UserSyntax gHC_WORD (fsLit "W8#") word8DataConKey word8DataCon floatTyConName, floatDataConName, doubleTyConName, doubleDataConName :: Name floatTyConName = mkWiredInTyConName UserSyntax gHC_TYPES (fsLit "Float") floatTyConKey floatTyCon @@ -1537,6 +1541,17 @@ wordTyCon = pcTyCon wordTyConName wordDataCon :: DataCon wordDataCon = pcDataCon wordDataConName [] [wordPrimTy] wordTyCon +word8Ty :: Type +word8Ty = mkTyConTy word8TyCon + +word8TyCon :: TyCon +word8TyCon = pcTyCon word8TyConName + (Just (CType NoSourceText Nothing + (NoSourceText, fsLit "HsWord8"))) [] + [word8DataCon] +word8DataCon :: DataCon +word8DataCon = pcDataCon word8DataConName [] [word8PrimTy] word8TyCon + floatTy :: Type floatTy = mkTyConTy floatTyCon ===================================== compiler/GHC/Core.hs ===================================== @@ -29,6 +29,7 @@ module GHC.Core ( mkIntLit, mkIntLitInt, mkWordLit, mkWordLitWord, + mkWord8Lit, mkWord8LitWord, mkWord64LitWord64, mkInt64LitInt64, mkCharLit, mkStringLit, mkFloatLit, mkFloatLitFloat, @@ -1995,6 +1996,12 @@ mkWordLitWord :: Platform -> Word -> Expr b mkWordLit platform w = Lit (mkLitWord platform w) mkWordLitWord platform w = Lit (mkLitWord platform (toInteger w)) +mkWord8Lit :: Platform -> Integer -> Expr b +mkWord8Lit _platform w = Lit (mkLitWord8 w) + +mkWord8LitWord :: Platform -> Integer -> Expr b +mkWord8LitWord _platform w = Lit (mkLitWord8 (toInteger w)) + mkWord64LitWord64 :: Word64 -> Expr b mkWord64LitWord64 w = Lit (mkLitWord64 (toInteger w)) ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -212,6 +212,26 @@ primOpRules nm = \case , subsumedByPrimOp Int16NarrowOp , subsumedByPrimOp Int32NarrowOp , narrowSubsumesAnd AndIOp Int32NarrowOp 32 ] + + Word8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs + matchPrimOpId Word8NarrowOp primop_id + return (Var (mkPrimOpId Narrow8WordOp) `App` e) ] + Word16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs + matchPrimOpId Word16NarrowOp primop_id + return (Var (mkPrimOpId Narrow16WordOp) `App` e) ] + Word32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs + matchPrimOpId Word32NarrowOp primop_id + return (Var (mkPrimOpId Narrow32WordOp) `App` e) ] + Word8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + , narrowSubsumesAnd AndOp Word8NarrowOp 8 ] + Word16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + , subsumedByPrimOp Word16NarrowOp + , narrowSubsumesAnd AndOp Word16NarrowOp 16 ] + Word32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + , subsumedByPrimOp Word16NarrowOp + , subsumedByPrimOp Word32NarrowOp + , narrowSubsumesAnd AndOp Word32NarrowOp 32 ] + -- Int64NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndIOp Int64NarrowOp 64 ] -- Word8NarrowOp -> mkPrimOpRule nm 1 [ narrowSubsumesAnd AndOp Word8NarrowOp 8 ] ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -2750,14 +2750,13 @@ repTyVarSig (MkC bndr) = rep2 tyVarSigName [bndr] -- Literals repLiteral :: HsLit GhcRn -> MetaM (Core TH.Lit) --- XXX this needs fixing. --- repLiteral (HsStringPrim _ bs) --- = do platform <- getPlatform --- word8_ty <- lookupType word8TyConName --- let w8s = unpack bs --- w8s_expr = map (\w8 -> mkCoreConApps word8DataCon --- [mkWordLit platform (toInteger w8)]) w8s --- rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr] +repLiteral (HsStringPrim _ bs) + = do platform <- getPlatform + word8_ty <- lookupType word8TyConName + let w8s = unpack bs + w8s_expr = map (\w8 -> mkCoreConApps word8DataCon + [mkWord8Lit platform (toInteger w8)]) w8s + rep2_nw stringPrimLName [mkListExpr word8_ty w8s_expr] repLiteral lit = do lit' <- case lit of HsIntPrim _ i -> mk_integer i ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit 9e542456b9b5514de7574774e47932c0bedd5b43 +Subproject commit 01754193492044e446f57442e0c9473972e5951e ===================================== testsuite/tests/array/should_run/arr020.hs ===================================== @@ -20,12 +20,12 @@ newByteArray (I# n#) writeByteArray :: MutableByteArray s -> Int -> Word32 -> ST s () writeByteArray (MutableByteArray mba#) (I# i#) (W32# w#) - = ST $ \s# -> case writeWord32Array# mba# i# w# s# of + = ST $ \s# -> case writeWord32Array# mba# i# (extendWord32# w#) s# of s'# -> (# s'#, () #) indexArray :: ByteArray Word32 -> Int -> Word32 indexArray (ByteArray arr#) (I# i#) - = W32# (indexWord32Array# arr# i#) + = W32# (narrowWord32# (indexWord32Array# arr# i#)) unsafeFreezeByteArray :: MutableByteArray s -> ST s (ByteArray e) unsafeFreezeByteArray (MutableByteArray mba#) @@ -68,7 +68,7 @@ unsafeFreezeArrayArray (MutableArrayArray marrs#) (# s'#, arrs# #) -> (# s'#, ArrayArray arrs# #) unsafeDeepFreezeArrayArray :: forall s e - . MutableArrayArray s (MutableByteArray s) + . MutableArrayArray s (MutableByteArray s) -> ST s (ArrayArray (ByteArray e)) unsafeDeepFreezeArrayArray marrs@(MutableArrayArray marrs#) = do { let n = I# (sizeofMutableArrayArray# marrs#) @@ -112,7 +112,7 @@ newUnboxedArray2D values } unboxedArray2D :: UnboxedArray2D Word32 -unboxedArray2D +unboxedArray2D = newUnboxedArray2D [ [1..10] , [11..200] @@ -125,7 +125,7 @@ indexUnboxedArray2D :: UnboxedArray2D Word32 -> (Int, Int) -> Word32 indexUnboxedArray2D arr (i, j) = indexArrayArray arr i `indexArray` j -main +main = do { print $ unboxedArray2D `indexUnboxedArray2D` (3, 1000) ; performGC ; print $ unboxedArray2D `indexUnboxedArray2D` (3, 1000) ===================================== testsuite/tests/backpack/should_compile/bkp16.stderr ===================================== @@ -4,5 +4,5 @@ Instantiating q [1 of 1] Including p[Int=base-4.13.0.0:GHC.Exts] Instantiating p[Int=base-4.13.0.0:GHC.Exts] - [1 of 1] Including ghc-prim-0.7.0 + [1 of 1] Including ghc-prim-0.8.0 [1 of 1] Compiling Int[sig] ( p/Int.hsig, bkp16.out/p/p-97PZnzqiJmd2hTwUNGdjod/Int.o ) ===================================== testsuite/tests/codeGen/should_run/cgrun070.hs ===================================== @@ -196,11 +196,11 @@ touch a = unsafeIOToST $ IO $ \s# -> indexWord8Array :: ByteArray -> Int -> Word8 indexWord8Array arr (I# i#) = case indexWord8Array# (unBA arr) i# of - a -> W8# a + a -> W8# (narrowWord8# a) writeWord8Array :: MByteArray s -> Int -> Word8 -> ST s () writeWord8Array marr (I# i#) (W8# a) = ST $ \ s# -> - case writeWord8Array# (unMBA marr) i# a s# of + case writeWord8Array# (unMBA marr) i# (extendWord8# a) s# of s2# -> (# s2#, () #) unsafeFreezeByteArray :: MByteArray s -> ST s (ByteArray) ===================================== testsuite/tests/codeGen/should_run/cgrun072.hs ===================================== @@ -31,10 +31,10 @@ main = do putStrLn test_primop_bSwap16 putStrLn test'_base_bSwap64 bswap16 :: Word16 -> Word16 -bswap16 (W16# w#) = W16# (narrow16Word# (byteSwap16# w#)) +bswap16 (W16# w#) = W16# (narrowWord16# (byteSwap16# (extendWord16# w#))) bswap32 :: Word32 -> Word32 -bswap32 (W32# w#) = W32# (narrow32Word# (byteSwap32# w#)) +bswap32 (W32# w#) = W32# (narrowWord32# (byteSwap32# (extendWord32# w#))) bswap64 :: Word64 -> Word64 bswap64 (W64# w#) = W64# (byteSwap64# w#) ===================================== testsuite/tests/codeGen/should_run/cgrun075.hs ===================================== @@ -27,13 +27,13 @@ instance Pdep Word where pdep (W# src#) (W# mask#) = W# (pdep# src# mask#) instance Pdep Word8 where - pdep (W8# src#) (W8# mask#) = W8# (pdep8# src# mask#) + pdep (W8# src#) (W8# mask#) = W8# (narrowWord8# (pdep8# (extendWord8# src#) (extendWord8# mask#))) instance Pdep Word16 where - pdep (W16# src#) (W16# mask#) = W16# (pdep16# src# mask#) + pdep (W16# src#) (W16# mask#) = W16# (narrowWord16# (pdep16# (extendWord16# src#) (extendWord16# mask#))) instance Pdep Word32 where - pdep (W32# src#) (W32# mask#) = W32# (pdep32# src# mask#) + pdep (W32# src#) (W32# mask#) = W32# (narrowWord32# (pdep32# (extendWord32# src#) (extendWord32# mask#))) instance Pdep Word64 where pdep (W64# src#) (W64# mask#) = W64# (pdep64# src# mask#) ===================================== testsuite/tests/codeGen/should_run/cgrun076.hs ===================================== @@ -27,13 +27,13 @@ instance Pext Word where pext (W# src#) (W# mask#) = W# (pext# src# mask#) instance Pext Word8 where - pext (W8# src#) (W8# mask#) = W8# (pext8# src# mask#) + pext (W8# src#) (W8# mask#) = W8# (narrowWord8# (pext8# (extendWord8# src#) (extendWord8# mask#))) instance Pext Word16 where - pext (W16# src#) (W16# mask#) = W16# (pext16# src# mask#) + pext (W16# src#) (W16# mask#) = W16# (narrowWord16# (pext16# (extendWord16# src#) (extendWord16# mask#))) instance Pext Word32 where - pext (W32# src#) (W32# mask#) = W32# (pext32# src# mask#) + pext (W32# src#) (W32# mask#) = W32# (narrowWord32# (pext32# (extendWord32# src#) (extendWord32# mask#))) instance Pext Word64 where pext (W64# src#) (W64# mask#) = W64# (pext64# src# mask#) ===================================== testsuite/tests/codeGen/should_run/compareByteArrays.hs ===================================== @@ -39,7 +39,7 @@ copyByteArray (BA# src#) (I# srcOfs#) (MBA# dest#) (I# destOfs#) (I# n#) indexWord8Array :: BA -> Int -> Word8 indexWord8Array (BA# ba#) (I# i#) - = W8# (indexWord8Array# ba# i#) + = W8# (narrowWord8# (indexWord8Array# ba# i#)) sizeofByteArray :: BA -> Int sizeofByteArray (BA# ba#) = I# (sizeofByteArray# ba#) @@ -54,7 +54,7 @@ newByteArray (I# n#) writeWord8Array :: MBA s -> Int -> Word8 -> ST s () writeWord8Array (MBA# mba#) (I# i#) (W8# j#) - = ST $ \s -> case writeWord8Array# mba# i# j# s of + = ST $ \s -> case writeWord8Array# mba# i# (extendWord8# j#) s of s' -> (# s', () #) unsafeFreezeByteArray :: MBA s -> ST s BA ===================================== testsuite/tests/dependent/should_compile/T14729.stderr ===================================== @@ -11,4 +11,4 @@ COERCION AXIOMS FAMILY INSTANCES type instance F Int = Bool -- Defined at T14729.hs:10:15 Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/dependent/should_compile/T15743.stderr ===================================== @@ -3,4 +3,4 @@ TYPE CONSTRUCTORS forall {k1} k2 (k3 :: k2). Proxy k3 -> k1 -> k2 -> * roles nominal nominal nominal phantom phantom phantom Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/dependent/should_compile/T15743e.stderr ===================================== @@ -52,4 +52,4 @@ DATA CONSTRUCTORS (d :: Proxy k5) (e :: Proxy k7). f c -> T k8 a b f c d e Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/ffi/should_run/T16650a.hs ===================================== @@ -44,4 +44,4 @@ luckySingleton = IO $ \s0 -> case newByteArray# 1# s0 of readByteArray :: MutableByteArray -> Int -> IO Word8 readByteArray (MutableByteArray b#) (I# i#) = IO $ \s0 -> case readWord8Array# b# i# s0 of - (# s1, w #) -> (# s1, W8# w #) + (# s1, w #) -> (# s1, W8# (narrowWord8# w) #) ===================================== testsuite/tests/ffi/should_run/T16650b.hs ===================================== @@ -53,7 +53,7 @@ luckySingleton = IO $ \s0 -> case newByteArray# 1# s0 of readByteArray :: MutableByteArray -> Int -> IO Word8 readByteArray (MutableByteArray b#) (I# i#) = IO $ \s0 -> case readWord8Array# b# i# s0 of - (# s1, w #) -> (# s1, W8# w #) + (# s1, w #) -> (# s1, W8# (narrowWord8# w) #) -- Write a mutable byte array to the array of mutable byte arrays -- at the given index. ===================================== testsuite/tests/ffi/should_run/UnliftedNewtypesByteArrayOffset.hs ===================================== @@ -35,7 +35,7 @@ main = do readByteArray :: MutableByteArray -> Int -> IO Word8 readByteArray (MutableByteArray b#) (I# i#) = IO $ \s0 -> case readWord8Array# b# i# s0 of - (# s1, w #) -> (# s1, W8# w #) + (# s1, w #) -> (# s1, W8# (narrowWord8# w) #) -- Create a new mutable byte array of length 1 with the sole byte -- set to the 105. @@ -43,5 +43,3 @@ luckySingleton :: IO MutableByteArray luckySingleton = IO $ \s0 -> case newByteArray# 1# s0 of (# s1, marr# #) -> case writeWord8Array# marr# 0# 105## s1 of s2 -> (# s2, MutableByteArray marr# #) - - ===================================== testsuite/tests/indexed-types/should_compile/T15711.stderr ===================================== @@ -3,4 +3,4 @@ TYPE CONSTRUCTORS associated type family F{2} :: forall a. Maybe a -> * roles nominal nominal Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/indexed-types/should_compile/T15852.stderr ===================================== @@ -9,4 +9,4 @@ FAMILY INSTANCES data instance forall {k1} {k2} {j :: k1} {c :: k2}. DF (Proxy c) -- Defined at T15852.hs:10:15 Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/lib/integer/integerImportExport.hs ===================================== @@ -33,13 +33,13 @@ newByteArray :: Word# -> IO MBA newByteArray sz = IO $ \s -> case newPinnedByteArray# (word2Int# sz) s of (# s, arr #) -> (# s, MBA arr #) indexByteArray :: ByteArray# -> Word# -> Word8 -indexByteArray a# n# = W8# (indexWord8Array# a# (word2Int# n#)) +indexByteArray a# n# = W8# (narrowWord8# (indexWord8Array# a# (word2Int# n#))) -- indexMutableByteArray :: MutableByteArray# RealWorld -> Word# -> IO Word8 -- indexMutableByteArray a# n# = IO $ \s -> case readWord8Array# a# (word2Int# n#) s of (# s', v #) -> (# s', W# v #) writeByteArray :: MutableByteArray# RealWorld -> Int# -> Word8 -> IO () -writeByteArray arr i (W8# w) = IO $ \s -> case writeWord8Array# arr i w s of s -> (# s, () #) +writeByteArray arr i (W8# w) = IO $ \s -> case writeWord8Array# arr i (extendWord8# w) s of s -> (# s, () #) lengthByteArray :: ByteArray# -> Word lengthByteArray ba = W# (int2Word# (sizeofByteArray# ba)) ===================================== testsuite/tests/polykinds/T15592.stderr ===================================== @@ -5,4 +5,4 @@ DATA CONSTRUCTORS MkT :: forall {k} k1 (f :: k1 -> k -> *) (a :: k1) (b :: k). f a b -> T f a b -> T f a b Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/polykinds/T15592b.stderr ===================================== @@ -4,4 +4,4 @@ TYPE CONSTRUCTORS forall k (f :: k -> *) (a :: k). f a -> * roles nominal nominal nominal nominal Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ===================================== testsuite/tests/printer/T18052a.stderr ===================================== @@ -6,7 +6,7 @@ TYPE CONSTRUCTORS PATTERN SYNONYMS (:||:) :: forall {a} {b}. a -> b -> (a, b) Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] ==================== Tidy Core ==================== Result size of Tidy Core @@ -36,6 +36,3 @@ T18052a.$m:||: (cont :: a -> b -> r) _ [Occ=Dead] -> case scrut of { (x, y) -> cont x y } - - - ===================================== testsuite/tests/profiling/should_run/T3001-2.hs ===================================== @@ -153,7 +153,7 @@ readN :: Int -> (S.ByteString -> a) -> Get a readN n f = fmap f $ getBytes n shiftl_w32 :: Word32 -> Int -> Word32 -shiftl_w32 (W32# w) (I# i) = W32# (w `uncheckedShiftL#` i) +shiftl_w32 (W32# w) (I# i) = W32# (narrowWord32# ((extendWord32# w) `uncheckedShiftL#` i)) getPtr :: Storable a => Int -> Get a getPtr n = do @@ -274,7 +274,7 @@ putWord32beB w = writeN 4 $ \p -> do poke (p `plusPtr` 3) (fromIntegral (w) :: Word8) shiftr_w32 :: Word32 -> Int -> Word32 -shiftr_w32 (W32# w) (I# i) = W32# (w `uncheckedShiftRL#` i) +shiftr_w32 (W32# w) (I# i) = W32# (narrowWord32# ((extendWord32# w) `uncheckedShiftRL#` i)) flush :: Builder flush = Builder $ \ k buf@(Buffer p o u l) -> @@ -291,4 +291,3 @@ instance Semigroup Builder where instance Monoid Builder where mempty = emptyBuilder mappend = (<>) - ===================================== testsuite/tests/simplCore/should_compile/T5359a.hs ===================================== @@ -61,7 +61,7 @@ textP arr off len | len == 0 = emptyT {-# INLINE textP #-} unsafeChrT :: Word16 -> Char -unsafeChrT (W16# w#) = C# (chr# (word2Int# w#)) +unsafeChrT (W16# w#) = C# (chr# (word2Int# (extendWord16# w#))) {-# INLINE unsafeChrT #-} data Array = Array ByteArray# @@ -82,7 +82,7 @@ unsafeFreeze (MArray maBA) = ST $ \s# -> (# s#, Array (unsafeCoerce# maBA) #) unsafeIndex :: Array -> Int -> Word16 unsafeIndex (Array aBA) (I# i#) = - case indexWord16Array# aBA i# of r# -> (W16# r#) + case indexWord16Array# aBA i# of r# -> (W16# (narrowWord16# r#)) {-# INLINE unsafeIndex #-} empty :: Array ===================================== testsuite/tests/typecheck/should_compile/T12763.stderr ===================================== @@ -8,4 +8,4 @@ COERCION AXIOMS CLASS INSTANCES instance C Int -- Defined at T12763.hs:9:10 Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.8.0] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80115ada7822e3c3006a2290a60492f6dbc6f205...e98e3d124a92cdf48108d918e501a132eaaee53a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80115ada7822e3c3006a2290a60492f6dbc6f205...e98e3d124a92cdf48108d918e501a132eaaee53a 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 Mon Nov 2 06:06:23 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 01:06:23 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/angerman/sized Message-ID: <5f9fa1df46ad2_7853fb640b910dc34125d@gitlab.haskell.org.mail> Moritz Angermann pushed new branch wip/angerman/sized at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/angerman/sized 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 Mon Nov 2 06:08:16 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 02 Nov 2020 01:08:16 -0500 Subject: [Git][ghc/ghc][wip/T17609] 2 commits: nativeGen: Deduplicate DWARF strings Message-ID: <5f9fa250599d8_7853fb582e3868c343292@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: e2760490 by Ben Gamari at 2020-11-02T01:08:08-05:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - b037879d by Ben Gamari at 2020-11-02T01:08:08-05:00 Add Note cross-reference for unique tag allocations - - - - - 5 changed files: - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Builtin/Uniques.hs ===================================== @@ -296,6 +296,9 @@ getTupleDataConName boxity n = * * ************************************************************************ +Note [Unique tag allocation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + Allocation of unique supply characters: v,t,u : for renumbering value-, type- and usage- vars. B: builtin ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -12,6 +12,7 @@ import GHC.Cmm.DebugBlock import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Platform +import GHC.Types.SrcLoc import GHC.Types.Unique import GHC.Types.Unique.Supply @@ -46,11 +47,12 @@ dwarfGen config modLoc us blocks = do compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + producer = dwarfStringFromString $ cProjectName ++ " " ++ cProjectVersion dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) - , dwName = fromMaybe "" (ml_hs_file modLoc) - , dwCompDir = addTrailingPathSeparator compPath - , dwProducer = cProjectName ++ " " ++ cProjectVersion + , dwName = dwarfStringFromString $ fromMaybe "" (ml_hs_file modLoc) + , dwCompDir = dwarfStringFromString $ addTrailingPathSeparator compPath + , dwProducer = producer , dwLowLabel = lowLabel , dwHighLabel = highLabel , dwLineLabel = dwarfLineLabel @@ -76,6 +78,9 @@ dwarfGen config modLoc us blocks = do , compileUnitFooter platform unitU ] + -- .debug_str section: Strings + let stringsSct = dwarfStringsSection platform (dwarfInfoStrings dwarfUnit) + -- .debug_line section: Generated mainly by the assembler, but we -- need to label it let lineSct = dwarfLineSection platform $$ @@ -92,7 +97,7 @@ dwarfGen config modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection platform $$ pprDwarfARanges platform aranges' unitU - return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') + return (infoSct $$ stringsSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. -- With split sections, each proc needs its own entry, since they may get @@ -177,7 +182,7 @@ parent, B. procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) - , dwName = case dblSourceTick prc of + , dwName = dwarfStringFromString $ case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) , dwLabel = dblCLabel prc @@ -208,7 +213,13 @@ blockToDwarf blk | otherwise = Nothing -- block was optimized out tickToDwarf :: Tickish () -> [DwarfInfo] -tickToDwarf (SourceNote ss _) = [DwarfSrcNote ss] +tickToDwarf (SourceNote ss _) = + [DwarfSrcNote { dwSpanFile = dwarfStringFromFastString (srcSpanFile ss) + , dwSpanStartLine = srcSpanStartLine ss + , dwSpanStartCol = srcSpanStartCol ss + , dwSpanEndLine = srcSpanEndLine ss + , dwSpanEndCol = srcSpanEndCol ss + }] tickToDwarf _ = [] -- | Generates the data for the debug frame section, which encodes the ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -86,12 +86,14 @@ dW_CHILDREN_no, dW_CHILDREN_yes :: Word8 dW_CHILDREN_no = 0 dW_CHILDREN_yes = 1 -dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, dW_FORM_string, dW_FORM_flag, +dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, + dW_FORM_strp,dW_FORM_string, dW_FORM_flag, dW_FORM_block1, dW_FORM_ref4, dW_FORM_ref_addr, dW_FORM_flag_present :: Word dW_FORM_addr = 0x01 dW_FORM_data2 = 0x05 dW_FORM_data4 = 0x06 dW_FORM_string = 0x08 +dW_FORM_strp = 0x0e dW_FORM_flag = 0x0c dW_FORM_block1 = 0x0a dW_FORM_ref_addr = 0x10 @@ -145,11 +147,13 @@ dW_OP_call_frame_cfa = 0x9c -- * Dwarf section declarations dwarfInfoSection, dwarfAbbrevSection, dwarfLineSection, - dwarfFrameSection, dwarfGhcSection, dwarfARangesSection :: Platform -> SDoc + dwarfFrameSection, dwarfStringSection, + dwarfGhcSection, dwarfARangesSection :: Platform -> SDoc dwarfInfoSection platform = dwarfSection platform "info" dwarfAbbrevSection platform = dwarfSection platform "abbrev" dwarfLineSection platform = dwarfSection platform "line" dwarfFrameSection platform = dwarfSection platform "frame" +dwarfStringSection platform = dwarfSection platform "str" dwarfGhcSection platform = dwarfSection platform "ghc" dwarfARangesSection platform = dwarfSection platform "aranges" @@ -165,11 +169,13 @@ dwarfSection platform name = -> text "\t.section .debug_" <> text name <> text ",\"dr\"" -- * Dwarf section labels -dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel :: PtrString +dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel, + dwarfStringLabel :: PtrString dwarfInfoLabel = sLit ".Lsection_info" dwarfAbbrevLabel = sLit ".Lsection_abbrev" dwarfLineLabel = sLit ".Lsection_line" dwarfFrameLabel = sLit ".Lsection_frame" +dwarfStringLabel = sLit ".Lsection_str" -- | Mapping of registers to DWARF register numbers dwarfRegNo :: Platform -> Reg -> Word8 ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -2,12 +2,19 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RecordWildCards #-} module GHC.CmmToAsm.Dwarf.Types ( -- * Dwarf information DwarfInfo(..) , pprDwarfInfo , pprAbbrevDecls + , dwarfInfoStrings + -- * Dwarf Strings section + , DwarfString + , dwarfStringsSection + , dwarfStringFromString + , dwarfStringFromFastString -- * Dwarf address range table , DwarfARange(..) , pprDwarfARanges @@ -32,18 +39,15 @@ import GHC.Prelude import GHC.Cmm.DebugBlock import GHC.Cmm.CLabel import GHC.Cmm.Expr ( GlobalReg(..) ) -import GHC.Utils.Encoding import GHC.Data.FastString import GHC.Utils.Outputable import GHC.Platform import GHC.Types.Unique +import GHC.Types.Unique.Set import GHC.Platform.Reg -import GHC.Types.SrcLoc -import GHC.Utils.Misc import GHC.CmmToAsm.Dwarf.Constants -import qualified Data.ByteString as BS import qualified Control.Monad.Trans.State.Strict as S import Control.Monad (zipWithM, join) import Data.Bits @@ -53,18 +57,49 @@ import Data.Char import GHC.Platform.Regs +-- | A string in the DWARF @.debug_str@ section. +newtype DwarfString = DwarfString FastString + +instance Uniquable DwarfString where + getUnique (DwarfString fs) = getUnique fs + +dwarfStringFromString :: String -> DwarfString +dwarfStringFromString = dwarfStringFromFastString . fsLit + +dwarfStringFromFastString :: FastString -> DwarfString +dwarfStringFromFastString = DwarfString + +dwarfStringSymbol :: DwarfString -> SDoc +dwarfStringSymbol (DwarfString fs) = + text "_dbgfs_" <> ppr (getKey $ getUnique fs) + +pprDwarfString :: Platform -> DwarfString -> SDoc +pprDwarfString plat s = + sectionOffset plat (dwarfStringSymbol s) (ptext dwarfStringLabel) + +dwarfStringsSection :: Platform -> UniqSet DwarfString -> SDoc +dwarfStringsSection platform xs = vcat + [ ptext dwarfStringLabel <> colon + , dwarfStringSection platform + , vcat (map string $ nonDetEltsUniqSet xs) + ] + where + string :: DwarfString -> SDoc + string dstr@(DwarfString fstr) = + dwarfStringSymbol dstr <> colon $$ pprFastString fstr + -- | Individual dwarf records. Each one will be encoded as an entry in -- the @.debug_info@ section. data DwarfInfo = DwarfCompileUnit { dwChildren :: [DwarfInfo] - , dwName :: String - , dwProducer :: String - , dwCompDir :: String + , dwName :: DwarfString + , dwProducer :: DwarfString + , dwCompDir :: DwarfString , dwLowLabel :: CLabel , dwHighLabel :: CLabel , dwLineLabel :: PtrString } | DwarfSubprogram { dwChildren :: [DwarfInfo] - , dwName :: String + , dwName :: DwarfString , dwLabel :: CLabel , dwParent :: Maybe CLabel -- ^ label of DIE belonging to the parent tick @@ -73,9 +108,23 @@ data DwarfInfo , dwLabel :: CLabel , dwMarker :: Maybe CLabel } - | DwarfSrcNote { dwSrcSpan :: RealSrcSpan + | DwarfSrcNote { dwSpanFile :: !DwarfString + , dwSpanStartLine :: !Int + , dwSpanStartCol :: !Int + , dwSpanEndLine :: !Int + , dwSpanEndCol :: !Int } +-- | 'DwarfStrings' mentioned by the given 'DwarfInfo'. +dwarfInfoStrings :: DwarfInfo -> UniqSet DwarfString +dwarfInfoStrings dwinfo = + case dwinfo of + DwarfCompileUnit {..} -> mkUniqSet [dwName, dwProducer, dwCompDir] `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfSubprogram {..} -> unitUniqSet dwName `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfBlock {..} -> foldMap dwarfInfoStrings dwChildren + DwarfSrcNote {..} -> unitUniqSet dwSpanFile + + -- | Abbreviation codes used for encoding above records in the -- @.debug_info@ section. data DwarfAbbrev @@ -138,7 +187,7 @@ pprAbbrevDecls platform haveDebugLine = , (dW_AT_high_pc, dW_FORM_addr) ] $$ mkAbbrev DwAbbrGhcSrcNote dW_TAG_ghc_src_note dW_CHILDREN_no - [ (dW_AT_ghc_span_file, dW_FORM_string) + [ (dW_AT_ghc_span_file, dW_FORM_strp) , (dW_AT_ghc_span_start_line, dW_FORM_data4) , (dW_AT_ghc_span_start_col, dW_FORM_data2) , (dW_AT_ghc_span_end_line, dW_FORM_data4) @@ -174,10 +223,10 @@ pprDwarfInfoOpen :: Platform -> Bool -> DwarfInfo -> SDoc pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowLabel highLabel lineLbl) = pprAbbrev DwAbbrCompileUnit - $$ pprString name - $$ pprString producer + $$ pprDwarfString platform name + $$ pprDwarfString platform producer $$ pprData4 dW_LANG_Haskell - $$ pprString compDir + $$ pprDwarfString platform compDir $$ pprWord platform (pdoc platform lowLabel) $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc @@ -186,7 +235,7 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = pdoc platform (mkAsmTempDieLabel label) <> colon $$ pprAbbrev abbrev - $$ pprString name + $$ pprDwarfString platform name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) @@ -209,13 +258,13 @@ pprDwarfInfoOpen platform _ (DwarfBlock _ label (Just marker)) = $$ pprLabelString platform label $$ pprWord platform (pdoc platform marker) $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel marker) -pprDwarfInfoOpen _ _ (DwarfSrcNote ss) = +pprDwarfInfoOpen platform _ (DwarfSrcNote {..}) = pprAbbrev DwAbbrGhcSrcNote - $$ pprString' (ftext $ srcSpanFile ss) - $$ pprData4 (fromIntegral $ srcSpanStartLine ss) - $$ pprHalf (fromIntegral $ srcSpanStartCol ss) - $$ pprData4 (fromIntegral $ srcSpanEndLine ss) - $$ pprHalf (fromIntegral $ srcSpanEndCol ss) + $$ pprDwarfString platform dwSpanFile + $$ pprData4 (fromIntegral dwSpanStartLine) + $$ pprHalf (fromIntegral dwSpanStartCol) + $$ pprData4 (fromIntegral dwSpanEndLine) + $$ pprHalf (fromIntegral dwSpanEndCol) -- | Close a DWARF info record with children pprDwarfInfoClose :: SDoc @@ -584,12 +633,8 @@ pprString' :: SDoc -> SDoc pprString' str = text "\t.asciz \"" <> str <> char '"' -- | Generate a string constant. We take care to escape the string. -pprString :: String -> SDoc -pprString str - = pprString' $ hcat $ map escapeChar $ - if str `lengthIs` utf8EncodedLength str - then str - else map (chr . fromIntegral) $ BS.unpack $ bytesFS $ mkFastString str +pprFastString :: FastString -> SDoc +pprFastString = pprString' . hcat . map escapeChar . unpackFS -- | Escape a single non-unicode character escapeChar :: Char -> SDoc ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -68,8 +68,11 @@ import Data.Bits * * ************************************************************************ -The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . -Fast comparison is everything on @Uniques@: +The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . The +allocation of these is documented in Note [Unique tag allocation] in +GHC.Builtin.Uniques. + +Fast comparison is everything on @Uniques at . -} -- | Unique identifier. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a8792d493d30978d83a91456692dca34fbafd474...b037879d83f6751e5b4a48ec14952217626385af -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a8792d493d30978d83a91456692dca34fbafd474...b037879d83f6751e5b4a48ec14952217626385af 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 Mon Nov 2 06:10:11 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 01:10:11 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/angerman/aarch64-always-pic Message-ID: <5f9fa2c31ff55_7853fb627eca4b03439ee@gitlab.haskell.org.mail> Moritz Angermann pushed new branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/angerman/aarch64-always-pic 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 Mon Nov 2 06:29:38 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 01:29:38 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] Fix superfluous import Message-ID: <5f9fa7523234f_7853fb61cb2be7c34637b@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 263852cd by Moritz Angermann at 2020-11-02T14:29:18+08:00 Fix superfluous import - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/Ppr.hs ===================================== @@ -44,7 +44,6 @@ import GHC.Word #if MIN_VERSION_ghc_prim(0,8,0) import GHC.Base (extendWord8#) #else -import GHC.Prim (Word#) extendWord8# :: Word# -> Word# extendWord8# w = w #endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/263852cd831f283b3409d3b18962c6dfd8c50e62 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/263852cd831f283b3409d3b18962c6dfd8c50e62 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 Mon Nov 2 07:17:44 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 02:17:44 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-always-pic] Meh, AArch64 is ARM64 in master. Message-ID: <5f9fb298db3f4_7853fb643129d58350114@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC Commits: 7d441e18 by Moritz Angermann at 2020-11-02T15:17:23+08:00 Meh, AArch64 is ARM64 in master. - - - - - 1 changed file: - compiler/GHC/Driver/Session.hs Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3797,8 +3797,8 @@ default_PIC :: Platform -> [GeneralFlag] default_PIC platform = case (platformOS platform, platformArch platform) of (OSDarwin, ArchX86_64) -> [Opt_PIC] - (OSDarwin, ArchAArch64) -> [Opt_PIC] - (OSLinux, ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs] + (OSDarwin, ArchARM64) -> [Opt_PIC] + (OSLinux, ArchARM64) -> [Opt_PIC, Opt_ExternalDynamicRefs] (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release -- (1 May 2013) we need to View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7d441e1849a3be17265cbd1a1db5a4085e4c63ef -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7d441e1849a3be17265cbd1a1db5a4085e4c63ef 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 Mon Nov 2 07:37:50 2020 From: gitlab at gitlab.haskell.org (Sven Tennie) Date: Mon, 02 Nov 2020 02:37:50 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] Deleted 1 commit: Introduce printing support for StackSnapshot#'s Message-ID: <5f9fb74e11736_7853fb5dc9221fc3573e9@gitlab.haskell.org.mail> Sven Tennie pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below. Deleted commits: 4e2fac38 by Sven Tennie at 2020-11-01T23:03:18-05:00 Introduce printing support for StackSnapshot#'s This refactors the RTS's existing Printer module to allow printing of StackSnapshot#'s. - - - - - 7 changed files: - + includes/rts/PrinterAPI.h - libraries/base/GHC/Stack/CloneStack.hs - rts/Disassembler.c - rts/Disassembler.h - rts/Printer.c - rts/Printer.h - rts/RtsSymbols.c Changes: ===================================== includes/rts/PrinterAPI.h ===================================== @@ -0,0 +1,3 @@ +#pragma once + +extern void printStack (StgStack* stack); ===================================== libraries/base/GHC/Stack/CloneStack.hs ===================================== @@ -12,7 +12,8 @@ module GHC.Stack.CloneStack ( StackSnapshot(..), cloneMyStack, - cloneThreadStack + cloneThreadStack, + printStack ) where import GHC.Prim (StackSnapshot#, cloneMyStack#, ThreadId#) @@ -68,3 +69,8 @@ cloneThreadStack (ThreadId tid#) = do freeStablePtr ptr takeMVar resultVar +foreign import ccall "PrinterAPI.h printStack" printStack_c :: StackSnapshot# -> IO () + +-- | Print the stack +printStack :: StackSnapshot -> IO () +printStack (StackSnapshot stack) = printStack_c stack ===================================== rts/Disassembler.c ===================================== @@ -8,8 +8,6 @@ * $Date: 2004/09/03 15:28:19 $ * ---------------------------------------------------------------------------*/ -#if defined(DEBUG) - #include "PosixSource.h" #include "Rts.h" #include "RtsAPI.h" @@ -358,5 +356,3 @@ void disassemble( StgBCO *bco ) debugBelch("\n"); } - -#endif /* DEBUG */ ===================================== rts/Disassembler.h ===================================== @@ -8,9 +8,5 @@ #pragma once -#if defined(DEBUG) - RTS_PRIVATE int disInstr ( StgBCO *bco, int pc ); RTS_PRIVATE void disassemble( StgBCO *bco ); - -#endif ===================================== rts/Printer.c ===================================== @@ -17,6 +17,7 @@ #include "sm/GCThread.h" #include "Hash.h" #include "Printer.h" +#include "rts/PrinterAPI.h" #include "RtsUtils.h" #if defined(PROFILING) @@ -25,9 +26,10 @@ #include +#include "Disassembler.h" + #if defined(DEBUG) -#include "Disassembler.h" #include "Apply.h" /* -------------------------------------------------------------------------- @@ -58,402 +60,337 @@ void printObj( StgClosure *obj ) printClosure(obj); } -STATIC_INLINE void -printStdObjHdr( const StgClosure *obj, char* tag ) +void +printMutableList(bdescr *bd) { - debugBelch("%s(",tag); - printPtr((StgPtr)obj->header.info); -#if defined(PROFILING) - debugBelch(", %s", obj->header.prof.ccs->cc->label); -#endif -} + StgPtr p; -static void -printStdObjPayload( const StgClosure *obj ) -{ - StgWord i, j; - const StgInfoTable* info; + debugBelch("mutable list %p: ", bd); - info = get_itbl(obj); - for (i = 0; i < info->layout.payload.ptrs; ++i) { - debugBelch(", "); - printPtr((StgPtr)obj->payload[i]); - } - for (j = 0; j < info->layout.payload.nptrs; ++j) { - debugBelch(", %pd#",obj->payload[i+j]); + for (; bd != NULL; bd = bd->link) { + for (p = bd->start; p < bd->free; p++) { + debugBelch("%p (%s), ", (void *)*p, info_type((StgClosure *)*p)); + } } - debugBelch(")\n"); + debugBelch("\n"); } -static void -printThunkPayload( StgThunk *obj ) +void printTSO( StgTSO *tso ) { - StgWord i, j; - const StgInfoTable* info; - - info = get_itbl((StgClosure *)obj); - for (i = 0; i < info->layout.payload.ptrs; ++i) { - debugBelch(", "); - printPtr((StgPtr)obj->payload[i]); - } - for (j = 0; j < info->layout.payload.nptrs; ++j) { - debugBelch(", %pd#",obj->payload[i+j]); - } - debugBelch(")\n"); + printStack( tso->stackobj ); } -static void -printThunkObject( StgThunk *obj, char* tag ) +void printStaticObjects( StgClosure *p ) { - printStdObjHdr( (StgClosure *)obj, tag ); - printThunkPayload( obj ); + while (p != END_OF_STATIC_OBJECT_LIST) { + p = UNTAG_STATIC_LIST_PTR(p); + printClosure(p); + + const StgInfoTable *info = get_itbl(p); + p = *STATIC_LINK(info, p); + } } -void -printClosure( const StgClosure *obj ) +void printWeakLists() { - debugBelch("%p: ", obj); - obj = UNTAG_CONST_CLOSURE(obj); - const StgInfoTable* info = get_itbl(obj); + debugBelch("======= WEAK LISTS =======\n"); - while (IS_FORWARDING_PTR(info)) { - obj = (StgClosure*)UN_FORWARDING_PTR(info); - debugBelch("(forwarding to %p) ", (void*)obj); - info = get_itbl(obj); + for (uint32_t cap_idx = 0; cap_idx < n_capabilities; ++cap_idx) { + debugBelch("Capability %d:\n", cap_idx); + Capability *cap = capabilities[cap_idx]; + for (StgWeak *weak = cap->weak_ptr_list_hd; weak; weak = weak->link) { + printClosure((StgClosure*)weak); + } } - switch ( info->type ) { - case INVALID_OBJECT: - barf("Invalid object"); - - case CONSTR: - case CONSTR_1_0: case CONSTR_0_1: - case CONSTR_1_1: case CONSTR_0_2: case CONSTR_2_0: - case CONSTR_NOCAF: - { - StgWord i, j; - const StgConInfoTable *con_info = get_con_itbl (obj); - - debugBelch("%s(", GET_CON_DESC(con_info)); - for (i = 0; i < info->layout.payload.ptrs; ++i) { - if (i != 0) debugBelch(", "); - printPtr((StgPtr)obj->payload[i]); - } - for (j = 0; j < info->layout.payload.nptrs; ++j) { - if (i != 0 || j != 0) debugBelch(", "); - debugBelch("%p#", obj->payload[i+j]); - } - debugBelch(")\n"); - break; + for (uint32_t gen_idx = 0; gen_idx <= oldest_gen->no; ++gen_idx) { + generation *gen = &generations[gen_idx]; + debugBelch("Generation %d current weaks:\n", gen_idx); + for (StgWeak *weak = gen->weak_ptr_list; weak; weak = weak->link) { + printClosure((StgClosure*)weak); } + debugBelch("Generation %d old weaks:\n", gen_idx); + for (StgWeak *weak = gen->old_weak_ptr_list; weak; weak = weak->link) { + printClosure((StgClosure*)weak); + } + } - case FUN: - case FUN_1_0: case FUN_0_1: - case FUN_1_1: case FUN_0_2: case FUN_2_0: - case FUN_STATIC: - debugBelch("FUN/%d(",(int)itbl_to_fun_itbl(info)->f.arity); - printPtr((StgPtr)obj->header.info); -#if defined(PROFILING) - debugBelch(", %s", obj->header.prof.ccs->cc->label); -#endif - printStdObjPayload(obj); - break; - - case PRIM: - debugBelch("PRIM("); - printPtr((StgPtr)obj->header.info); - printStdObjPayload(obj); - break; - - case MUT_PRIM: - debugBelch("MUT_PRIM("); - printPtr((StgPtr)obj->header.info); - printStdObjPayload(obj); - break; - - case THUNK: - case THUNK_1_0: case THUNK_0_1: - case THUNK_1_1: case THUNK_0_2: case THUNK_2_0: - case THUNK_STATIC: - /* ToDo: will this work for THUNK_STATIC too? */ -#if defined(PROFILING) - printThunkObject((StgThunk *)obj,GET_PROF_DESC(info)); -#else - printThunkObject((StgThunk *)obj,"THUNK"); -#endif - break; + debugBelch("=========================\n"); +} - case THUNK_SELECTOR: - printStdObjHdr(obj, "THUNK_SELECTOR"); - debugBelch(", %p)\n", ((StgSelector *)obj)->selectee); - break; +void printLargeAndPinnedObjects() +{ + debugBelch("====== PINNED OBJECTS ======\n"); - case BCO: - disassemble( (StgBCO*)obj ); - break; + for (uint32_t cap_idx = 0; cap_idx < n_capabilities; ++cap_idx) { + Capability *cap = capabilities[cap_idx]; - case AP: - { - StgAP* ap = (StgAP*)obj; - StgWord i; - debugBelch("AP("); printPtr((StgPtr)ap->fun); - for (i = 0; i < ap->n_args; ++i) { - debugBelch(", "); - printPtr((P_)ap->payload[i]); - } - debugBelch(")\n"); - break; + debugBelch("Capability %d: Current pinned object block: %p\n", + cap_idx, (void*)cap->pinned_object_block); + for (bdescr *bd = cap->pinned_object_blocks; bd; bd = bd->link) { + debugBelch("%p\n", (void*)bd); } + } - case PAP: - { - StgPAP* pap = (StgPAP*)obj; - StgWord i; - debugBelch("PAP/%d(",(int)pap->arity); - printPtr((StgPtr)pap->fun); - for (i = 0; i < pap->n_args; ++i) { - debugBelch(", "); - printPtr((StgPtr)pap->payload[i]); - } - debugBelch(")\n"); - break; + debugBelch("====== LARGE OBJECTS =======\n"); + for (uint32_t gen_idx = 0; gen_idx <= oldest_gen->no; ++gen_idx) { + generation *gen = &generations[gen_idx]; + debugBelch("Generation %d current large objects:\n", gen_idx); + for (bdescr *bd = gen->large_objects; bd; bd = bd->link) { + debugBelch("%p: ", (void*)bd); + printClosure((StgClosure*)bd->start); } - case AP_STACK: - { - StgAP_STACK* ap = (StgAP_STACK*)obj; - StgWord i; - debugBelch("AP_STACK("); printPtr((StgPtr)ap->fun); - for (i = 0; i < ap->size; ++i) { - debugBelch(", "); - printPtr((P_)ap->payload[i]); - } - debugBelch(")\n"); - break; + debugBelch("Generation %d scavenged large objects:\n", gen_idx); + for (bdescr *bd = gen->scavenged_large_objects; bd; bd = bd->link) { + debugBelch("%p: ", (void*)bd); + printClosure((StgClosure*)bd->start); } + } - case IND: - debugBelch("IND("); - printPtr((StgPtr)((StgInd*)obj)->indirectee); - debugBelch(")\n"); - break; - - case IND_STATIC: - debugBelch("IND_STATIC("); - printPtr((StgPtr)((StgInd*)obj)->indirectee); - debugBelch(")\n"); - break; + debugBelch("============================\n"); +} - case BLACKHOLE: - debugBelch("BLACKHOLE("); - printPtr((StgPtr)((StgInd*)obj)->indirectee); - debugBelch(")\n"); - break; +/* -------------------------------------------------------------------------- + * Address printing code + * + * Uses symbol table in (unstripped executable) + * ------------------------------------------------------------------------*/ - /* Cannot happen -- use default case. - case RET_BCO: - case RET_SMALL: - case RET_BIG: - case RET_FUN: - */ +/* -------------------------------------------------------------------------- + * Simple lookup table + * address -> function name + * ------------------------------------------------------------------------*/ - case UPDATE_FRAME: - { - StgUpdateFrame* u = (StgUpdateFrame*)obj; - debugBelch("%s(", info_update_frame(obj)); - printPtr((StgPtr)GET_INFO((StgClosure *)u)); - debugBelch(","); - printPtr((StgPtr)u->updatee); - debugBelch(")\n"); - break; - } +static HashTable * add_to_fname_table = NULL; - case CATCH_FRAME: - { - StgCatchFrame* u = (StgCatchFrame*)obj; - debugBelch("CATCH_FRAME("); - printPtr((StgPtr)GET_INFO((StgClosure *)u)); - debugBelch(","); - printPtr((StgPtr)u->handler); - debugBelch(")\n"); - break; - } - - case UNDERFLOW_FRAME: - { - StgUnderflowFrame* u = (StgUnderflowFrame*)obj; - debugBelch("UNDERFLOW_FRAME("); - printPtr((StgPtr)u->next_chunk); - debugBelch(")\n"); - break; - } - - case STOP_FRAME: - { - StgStopFrame* u = (StgStopFrame*)obj; - debugBelch("STOP_FRAME("); - printPtr((StgPtr)GET_INFO((StgClosure *)u)); - debugBelch(")\n"); - break; - } - - case ARR_WORDS: - { - StgWord i; - debugBelch("ARR_WORDS(\""); - for (i=0; ipayload[i]); - debugBelch("\")\n"); - break; - } - - case MUT_ARR_PTRS_CLEAN: - debugBelch("MUT_ARR_PTRS_CLEAN(size=%" FMT_Word ")\n", (W_)((StgMutArrPtrs *)obj)->ptrs); - break; - - case MUT_ARR_PTRS_DIRTY: - debugBelch("MUT_ARR_PTRS_DIRTY(size=%" FMT_Word ")\n", (W_)((StgMutArrPtrs *)obj)->ptrs); - break; +const char *lookupGHCName( void *addr ) +{ + if (add_to_fname_table == NULL) + return NULL; - case MUT_ARR_PTRS_FROZEN_CLEAN: - debugBelch("MUT_ARR_PTRS_FROZEN_CLEAN(size=%" FMT_Word ")\n", (W_)((StgMutArrPtrs *)obj)->ptrs); - break; + return lookupHashTable(add_to_fname_table, (StgWord)addr); +} - case SMALL_MUT_ARR_PTRS_CLEAN: - debugBelch("SMALL_MUT_ARR_PTRS_CLEAN(size=%" FMT_Word ")\n", - (W_)((StgSmallMutArrPtrs *)obj)->ptrs); - break; +/* -------------------------------------------------------------------------- + * Symbol table loading + * ------------------------------------------------------------------------*/ - case SMALL_MUT_ARR_PTRS_DIRTY: - debugBelch("SMALL_MUT_ARR_PTRS_DIRTY(size=%" FMT_Word ")\n", - (W_)((StgSmallMutArrPtrs *)obj)->ptrs); - break; +/* Causing linking trouble on Win32 plats, so I'm + disabling this for now. +*/ +#if defined(USING_LIBBFD) +# define PACKAGE 1 +# define PACKAGE_VERSION 1 +/* Those PACKAGE_* defines are workarounds for bfd: + * https://sourceware.org/bugzilla/show_bug.cgi?id=14243 + * ghc's build system filter PACKAGE_* values out specifically to avoid clashes + * with user's autoconf-based Cabal packages. + * It's a shame checks for unrelated fields instead of actually used + * macros. + */ +# include - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - debugBelch("SMALL_MUT_ARR_PTRS_FROZEN_CLEAN(size=%" FMT_Word ")\n", - (W_)((StgSmallMutArrPtrs *)obj)->ptrs); - break; +/* Fairly ad-hoc piece of code that seems to filter out a lot of + * rubbish like the obj-splitting symbols + */ - case MVAR_CLEAN: - case MVAR_DIRTY: - { - StgMVar* mv = (StgMVar*)obj; +static bool isReal( flagword flags STG_UNUSED, const char *name ) +{ +#if 0 + /* ToDo: make this work on BFD */ + int tp = type & N_TYPE; + if (tp == N_TEXT || tp == N_DATA) { + return (name[0] == '_' && name[1] != '_'); + } else { + return false; + } +#else + if (*name == '\0' || + (name[0] == 'g' && name[1] == 'c' && name[2] == 'c') || + (name[0] == 'c' && name[1] == 'c' && name[2] == '.')) { + return false; + } + return true; +#endif +} - debugBelch("MVAR(head="); - if ((StgClosure*)mv->head == &stg_END_TSO_QUEUE_closure) { - debugBelch("END_TSO_QUEUE"); - } else { - debugBelch("%p", mv->head); - } +extern void DEBUG_LoadSymbols( const char *name ) +{ + bfd* abfd; + char **matching; - debugBelch(", tail="); - if ((StgClosure*)mv->tail == &stg_END_TSO_QUEUE_closure) { - debugBelch("END_TSO_QUEUE"); - } else { - debugBelch("%p", mv->tail); - } + bfd_init(); + abfd = bfd_openr(name, "default"); + if (abfd == NULL) { + barf("can't open executable %s to get symbol table", name); + } + if (!bfd_check_format_matches (abfd, bfd_object, &matching)) { + barf("mismatch"); + } - debugBelch(", value="); - if ((StgClosure*)mv->value == &stg_END_TSO_QUEUE_closure) { - debugBelch("END_TSO_QUEUE"); - } else { - debugBelch("%p", mv->value); - } - debugBelch(")\n"); + { + long storage_needed; + asymbol **symbol_table; + long number_of_symbols; + long num_real_syms = 0; + long i; - break; - } + storage_needed = bfd_get_symtab_upper_bound (abfd); - case TVAR: - { - StgTVar* tv = (StgTVar*)obj; - debugBelch("TVAR(value=%p, wq=%p, num_updates=%" FMT_Word ")\n", tv->current_value, tv->first_watch_queue_entry, tv->num_updates); - break; + if (storage_needed < 0) { + barf("can't read symbol table"); } + symbol_table = (asymbol **) stgMallocBytes(storage_needed,"DEBUG_LoadSymbols"); - case MUT_VAR_CLEAN: - { - StgMutVar* mv = (StgMutVar*)obj; - debugBelch("MUT_VAR_CLEAN(var=%p)\n", mv->var); - break; - } + number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table); - case MUT_VAR_DIRTY: - { - StgMutVar* mv = (StgMutVar*)obj; - debugBelch("MUT_VAR_DIRTY(var=%p)\n", mv->var); - break; + if (number_of_symbols < 0) { + barf("can't canonicalise symbol table"); } - case WEAK: - debugBelch("WEAK("); - debugBelch("key=%p value=%p finalizer=%p", - (StgPtr)(((StgWeak*)obj)->key), - (StgPtr)(((StgWeak*)obj)->value), - (StgPtr)(((StgWeak*)obj)->finalizer)); - debugBelch(")\n"); - /* ToDo: chase 'link' ? */ - break; - - case TSO: - debugBelch("TSO("); - debugBelch("%lu (%p)",(unsigned long)(((StgTSO*)obj)->id), (StgTSO*)obj); - debugBelch(")\n"); - break; - - case STACK: - debugBelch("STACK\n"); - break; - -#if 0 - /* Symptomatic of a problem elsewhere, have it fall-through & fail */ - case EVACUATED: - debugBelch("EVACUATED("); - printClosure((StgEvacuated*)obj->evacuee); - debugBelch(")\n"); - break; -#endif + if (add_to_fname_table == NULL) + add_to_fname_table = allocHashTable(); - case COMPACT_NFDATA: - debugBelch("COMPACT_NFDATA(size=%" FMT_Word ")\n", - (W_)((StgCompactNFData *)obj)->totalW * (W_)sizeof(W_)); - break; + for( i = 0; i != number_of_symbols; ++i ) { + symbol_info info; + bfd_get_symbol_info(abfd,symbol_table[i],&info); + if (isReal(info.type, info.name)) { + insertHashTable(add_to_fname_table, + info.value, (void*)info.name); + num_real_syms += 1; + } + } - case TREC_CHUNK: - debugBelch("TREC_CHUNK\n"); - break; + IF_DEBUG(interpreter, + debugBelch("Loaded %ld symbols. Of which %ld are real symbols\n", + number_of_symbols, num_real_syms) + ); - default: - //barf("printClosure %d",get_itbl(obj)->type); - debugBelch("*** printClosure: unknown type %d ****\n", - (int)get_itbl(obj)->type ); - barf("printClosure %d",get_itbl(obj)->type); - return; + stgFree(symbol_table); } } -void -printMutableList(bdescr *bd) +#else /* USING_LIBBFD */ + +extern void DEBUG_LoadSymbols( const char *name STG_UNUSED ) { - StgPtr p; + /* nothing, yet */ +} - debugBelch("mutable list %p: ", bd); +#endif /* USING_LIBBFD */ - for (; bd != NULL; bd = bd->link) { - for (p = bd->start; p < bd->free; p++) { - debugBelch("%p (%s), ", (void *)*p, info_type((StgClosure *)*p)); - } - } - debugBelch("\n"); -} +void findPtr(P_ p, int); /* keep gcc -Wall happy */ -// If you know you have an UPDATE_FRAME, but want to know exactly which. -const char *info_update_frame(const StgClosure *closure) +int searched = 0; + +static int +findPtrBlocks (StgPtr p, bdescr *bd, StgPtr arr[], int arr_size, int i) { - // Note: We intentionally don't take the info table pointer as - // an argument. As it will be confusing whether one should pass - // it pointing to the code or struct members when compiling with - // TABLES_NEXT_TO_CODE. + StgPtr q, r, end; + for (; bd; bd = bd->link) { + searched++; + for (q = bd->start; q < bd->free; q++) { + if (UNTAG_CONST_CLOSURE((StgClosure*)*q) == (const StgClosure *)p) { + if (i < arr_size) { + for (r = bd->start; r < bd->free; r = end) { + // skip over zeroed-out slop + while (*r == 0) r++; + if (!LOOKS_LIKE_CLOSURE_PTR(r)) { + debugBelch("%p found at %p, no closure at %p\n", + p, q, r); + break; + } + end = r + closure_sizeW((StgClosure*)r); + if (q < end) { + debugBelch("%p = ", r); + printClosure((StgClosure *)r); + arr[i++] = r; + break; + } + } + if (r >= bd->free) { + debugBelch("%p found at %p, closure?", p, q); + } + } else { + return i; + } + } + } + } + return i; +} + +void +findPtr(P_ p, int follow) +{ + uint32_t g, n; + bdescr *bd; + const int arr_size = 1024; + StgPtr arr[arr_size]; + int i = 0; + searched = 0; + +#if 0 + // We can't search the nursery, because we don't know which blocks contain + // valid data, because the bd->free pointers in the nursery are only reset + // just before a block is used. + for (n = 0; n < n_capabilities; n++) { + bd = nurseries[i].blocks; + i = findPtrBlocks(p,bd,arr,arr_size,i); + if (i >= arr_size) return; + } +#endif + + for (g = 0; g < RtsFlags.GcFlags.generations; g++) { + bd = generations[g].blocks; + i = findPtrBlocks(p,bd,arr,arr_size,i); + bd = generations[g].large_objects; + i = findPtrBlocks(p,bd,arr,arr_size,i); + if (i >= arr_size) return; + for (n = 0; n < n_capabilities; n++) { + i = findPtrBlocks(p, gc_threads[n]->gens[g].part_list, + arr, arr_size, i); + i = findPtrBlocks(p, gc_threads[n]->gens[g].todo_bd, + arr, arr_size, i); + } + if (i >= arr_size) return; + } + if (follow && i == 1) { + debugBelch("-->\n"); + findPtr(arr[0], 1); + } +} + +const char *what_next_strs[] = { + [0] = "(unknown)", + [ThreadRunGHC] = "ThreadRunGHC", + [ThreadInterpret] = "ThreadInterpret", + [ThreadKilled] = "ThreadKilled", + [ThreadComplete] = "ThreadComplete" +}; + +#else /* DEBUG */ +void printPtr( StgPtr p ) +{ + debugBelch("ptr 0x%p (enable -DDEBUG for more info) " , p ); +} + +void printObj( StgClosure *obj ) +{ + debugBelch("obj 0x%p (enable -DDEBUG for more info) " , obj ); +} + + +#endif /* DEBUG */ + +// If you know you have an UPDATE_FRAME, but want to know exactly which. +const char *info_update_frame(const StgClosure *closure) +{ + // Note: We intentionally don't take the info table pointer as + // an argument. As it will be confusing whether one should pass + // it pointing to the code or struct members when compiling with + // TABLES_NEXT_TO_CODE. const StgInfoTable *info = closure->header.info; if (info == &stg_upd_frame_info) { return "NORMAL_UPDATE_FRAME"; @@ -467,501 +404,567 @@ const char *info_update_frame(const StgClosure *closure) } static void -printSmallBitmap( StgPtr spBottom, StgPtr payload, StgWord bitmap, - uint32_t size ) +printThunkPayload( StgThunk *obj ) { - uint32_t i; + StgWord i, j; + const StgInfoTable* info; - for(i = 0; i < size; i++, bitmap >>= 1 ) { - debugBelch(" stk[%ld] (%p) = ", (long)(spBottom-(payload+i)), payload+i); - if ((bitmap & 1) == 0) { - printPtr((P_)payload[i]); - debugBelch(" -- "); - printObj((StgClosure*) payload[i]); - } else { - debugBelch("Word# %" FMT_Word "\n", (W_)payload[i]); - } + info = get_itbl((StgClosure *)obj); + for (i = 0; i < info->layout.payload.ptrs; ++i) { + debugBelch(", "); + printPtr((StgPtr)obj->payload[i]); + } + for (j = 0; j < info->layout.payload.nptrs; ++j) { + debugBelch(", %pd#",obj->payload[i+j]); } + debugBelch(")\n"); +} + +STATIC_INLINE void +printStdObjHdr( const StgClosure *obj, char* tag ) +{ + debugBelch("%s(",tag); + printPtr((StgPtr)obj->header.info); +#if defined(PROFILING) + debugBelch(", %s", obj->header.prof.ccs->cc->label); +#endif } static void -printLargeBitmap( StgPtr spBottom, StgPtr payload, StgLargeBitmap* large_bitmap, - uint32_t size ) +printThunkObject( StgThunk *obj, char* tag ) { - StgWord bmp; - uint32_t i, j; + printStdObjHdr( (StgClosure *)obj, tag ); + printThunkPayload( obj ); +} - i = 0; - for (bmp=0; i < size; bmp++) { - StgWord bitmap = large_bitmap->bitmap[bmp]; - j = 0; - for(; i < size && j < BITS_IN(W_); j++, i++, bitmap >>= 1 ) { - debugBelch(" stk[%" FMT_Word "] (%p) = ", (W_)(spBottom-(payload+i)), payload+i); - if ((bitmap & 1) == 0) { - printPtr((P_)payload[i]); - debugBelch(" -- "); - printObj((StgClosure*) payload[i]); - } else { - debugBelch("Word# %" FMT_Word "\n", (W_)payload[i]); - } - } +static void +printStdObjPayload( const StgClosure *obj ) +{ + StgWord i, j; + const StgInfoTable* info; + + info = get_itbl(obj); + for (i = 0; i < info->layout.payload.ptrs; ++i) { + debugBelch(", "); + printPtr((StgPtr)obj->payload[i]); + } + for (j = 0; j < info->layout.payload.nptrs; ++j) { + debugBelch(", %pd#",obj->payload[i+j]); } + debugBelch(")\n"); } void -printStackChunk( StgPtr sp, StgPtr spBottom ) +printClosure( const StgClosure *obj ) { - const StgInfoTable *info; + debugBelch("%p: ", obj); + obj = UNTAG_CONST_CLOSURE(obj); + const StgInfoTable* info = get_itbl(obj); - ASSERT(sp <= spBottom); - for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) { + while (IS_FORWARDING_PTR(info)) { + obj = (StgClosure*)UN_FORWARDING_PTR(info); + debugBelch("(forwarding to %p) ", (void*)obj); + info = get_itbl(obj); + } - info = get_itbl((StgClosure *)sp); + switch ( info->type ) { + case INVALID_OBJECT: + barf("Invalid object"); - switch (info->type) { + case CONSTR: + case CONSTR_1_0: case CONSTR_0_1: + case CONSTR_1_1: case CONSTR_0_2: case CONSTR_2_0: + case CONSTR_NOCAF: + { + StgWord i, j; + const StgConInfoTable *con_info = get_con_itbl (obj); - case UPDATE_FRAME: - case CATCH_FRAME: - case UNDERFLOW_FRAME: - case STOP_FRAME: - printClosure((StgClosure*)sp); - continue; + debugBelch("%s(", GET_CON_DESC(con_info)); + for (i = 0; i < info->layout.payload.ptrs; ++i) { + if (i != 0) debugBelch(", "); + printPtr((StgPtr)obj->payload[i]); + } + for (j = 0; j < info->layout.payload.nptrs; ++j) { + if (i != 0 || j != 0) debugBelch(", "); + debugBelch("%p#", obj->payload[i+j]); + } + debugBelch(")\n"); + break; + } - case RET_SMALL: { - StgWord c = *sp; - if (c == (StgWord)&stg_ctoi_R1p_info) { - debugBelch("tstg_ctoi_ret_R1p_info\n" ); - } else if (c == (StgWord)&stg_ctoi_R1n_info) { - debugBelch("stg_ctoi_ret_R1n_info\n" ); - } else if (c == (StgWord)&stg_ctoi_F1_info) { - debugBelch("stg_ctoi_ret_F1_info\n" ); - } else if (c == (StgWord)&stg_ctoi_D1_info) { - debugBelch("stg_ctoi_ret_D1_info\n" ); - } else if (c == (StgWord)&stg_ctoi_V_info) { - debugBelch("stg_ctoi_ret_V_info\n" ); - } else if (c == (StgWord)&stg_ap_v_info) { - debugBelch("stg_ap_v_info\n" ); - } else if (c == (StgWord)&stg_ap_f_info) { - debugBelch("stg_ap_f_info\n" ); - } else if (c == (StgWord)&stg_ap_d_info) { - debugBelch("stg_ap_d_info\n" ); - } else if (c == (StgWord)&stg_ap_l_info) { - debugBelch("stg_ap_l_info\n" ); - } else if (c == (StgWord)&stg_ap_n_info) { - debugBelch("stg_ap_n_info\n" ); - } else if (c == (StgWord)&stg_ap_p_info) { - debugBelch("stg_ap_p_info\n" ); - } else if (c == (StgWord)&stg_ap_pp_info) { - debugBelch("stg_ap_pp_info\n" ); - } else if (c == (StgWord)&stg_ap_ppp_info) { - debugBelch("stg_ap_ppp_info\n" ); - } else if (c == (StgWord)&stg_ap_pppp_info) { - debugBelch("stg_ap_pppp_info\n" ); - } else if (c == (StgWord)&stg_ap_ppppp_info) { - debugBelch("stg_ap_ppppp_info\n" ); - } else if (c == (StgWord)&stg_ap_pppppp_info) { - debugBelch("stg_ap_pppppp_info\n" ); - } else if (c == (StgWord)&stg_ret_v_info) { - debugBelch("stg_ret_v_info\n" ); - } else if (c == (StgWord)&stg_ret_p_info) { - debugBelch("stg_ret_p_info\n" ); - } else if (c == (StgWord)&stg_ret_n_info) { - debugBelch("stg_ret_n_info\n" ); - } else if (c == (StgWord)&stg_ret_f_info) { - debugBelch("stg_ret_f_info\n" ); - } else if (c == (StgWord)&stg_ret_d_info) { - debugBelch("stg_ret_d_info\n" ); - } else if (c == (StgWord)&stg_ret_l_info) { - debugBelch("stg_ret_l_info\n" ); + case FUN: + case FUN_1_0: case FUN_0_1: + case FUN_1_1: case FUN_0_2: case FUN_2_0: + case FUN_STATIC: + debugBelch("FUN/%d(",(int)itbl_to_fun_itbl(info)->f.arity); + printPtr((StgPtr)obj->header.info); #if defined(PROFILING) - } else if (c == (StgWord)&stg_restore_cccs_info) { - debugBelch("stg_restore_cccs_info\n" ); - fprintCCS(stderr, (CostCentreStack*)sp[1]); - debugBelch("\n" ); - continue; - } else if (c == (StgWord)&stg_restore_cccs_eval_info) { - debugBelch("stg_restore_cccs_eval_info\n" ); - fprintCCS(stderr, (CostCentreStack*)sp[1]); - debugBelch("\n" ); - continue; + debugBelch(", %s", obj->header.prof.ccs->cc->label); #endif - } else { - debugBelch("RET_SMALL (%p)\n", info); - } - StgWord bitmap = info->layout.bitmap; - printSmallBitmap(spBottom, sp+1, - BITMAP_BITS(bitmap), BITMAP_SIZE(bitmap)); - continue; - } + printStdObjPayload(obj); + break; - case RET_BCO: { - StgBCO *bco; + case PRIM: + debugBelch("PRIM("); + printPtr((StgPtr)obj->header.info); + printStdObjPayload(obj); + break; - bco = ((StgBCO *)sp[1]); + case MUT_PRIM: + debugBelch("MUT_PRIM("); + printPtr((StgPtr)obj->header.info); + printStdObjPayload(obj); + break; - debugBelch("RET_BCO (%p)\n", sp); - printLargeBitmap(spBottom, sp+2, - BCO_BITMAP(bco), BCO_BITMAP_SIZE(bco)); - continue; - } + case THUNK: + case THUNK_1_0: case THUNK_0_1: + case THUNK_1_1: case THUNK_0_2: case THUNK_2_0: + case THUNK_STATIC: + /* ToDo: will this work for THUNK_STATIC too? */ +#if defined(PROFILING) + printThunkObject((StgThunk *)obj,GET_PROF_DESC(info)); +#else + printThunkObject((StgThunk *)obj,"THUNK"); +#endif + break; - case RET_BIG: - debugBelch("RET_BIG (%p)\n", sp); - StgLargeBitmap* bitmap = GET_LARGE_BITMAP(info); - printLargeBitmap(spBottom, - (StgPtr)((StgClosure *) sp)->payload, - bitmap, - bitmap->size); - continue; - case RET_FUN: + case THUNK_SELECTOR: + printStdObjHdr(obj, "THUNK_SELECTOR"); + debugBelch(", %p)\n", ((StgSelector *)obj)->selectee); + break; + + case BCO: + disassemble( (StgBCO*)obj ); + break; + + case AP: { - const StgFunInfoTable *fun_info; - StgRetFun *ret_fun; + StgAP* ap = (StgAP*)obj; + StgWord i; + debugBelch("AP("); printPtr((StgPtr)ap->fun); + for (i = 0; i < ap->n_args; ++i) { + debugBelch(", "); + printPtr((P_)ap->payload[i]); + } + debugBelch(")\n"); + break; + } - ret_fun = (StgRetFun *)sp; - fun_info = get_fun_itbl(UNTAG_CLOSURE(ret_fun->fun)); - debugBelch("RET_FUN (%p) (type=%d)\n", ret_fun->fun, (int)fun_info->f.fun_type); - switch (fun_info->f.fun_type) { - case ARG_GEN: - printSmallBitmap(spBottom, sp+2, - BITMAP_BITS(fun_info->f.b.bitmap), - BITMAP_SIZE(fun_info->f.b.bitmap)); - break; - case ARG_GEN_BIG: - printLargeBitmap(spBottom, sp+2, - GET_FUN_LARGE_BITMAP(fun_info), - GET_FUN_LARGE_BITMAP(fun_info)->size); - break; - default: - printSmallBitmap(spBottom, sp+2, - BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]), - BITMAP_SIZE(stg_arg_bitmaps[fun_info->f.fun_type])); - break; + case PAP: + { + StgPAP* pap = (StgPAP*)obj; + StgWord i; + debugBelch("PAP/%d(",(int)pap->arity); + printPtr((StgPtr)pap->fun); + for (i = 0; i < pap->n_args; ++i) { + debugBelch(", "); + printPtr((StgPtr)pap->payload[i]); } - continue; + debugBelch(")\n"); + break; } - default: - debugBelch("unknown object %d\n", (int)info->type); - barf("printStackChunk"); + case AP_STACK: + { + StgAP_STACK* ap = (StgAP_STACK*)obj; + StgWord i; + debugBelch("AP_STACK("); printPtr((StgPtr)ap->fun); + for (i = 0; i < ap->size; ++i) { + debugBelch(", "); + printPtr((P_)ap->payload[i]); + } + debugBelch(")\n"); + break; } - } -} -static void printStack( StgStack *stack ) -{ - printStackChunk( stack->sp, stack->stack + stack->stack_size ); -} + case IND: + debugBelch("IND("); + printPtr((StgPtr)((StgInd*)obj)->indirectee); + debugBelch(")\n"); + break; -void printTSO( StgTSO *tso ) -{ - printStack( tso->stackobj ); -} + case IND_STATIC: + debugBelch("IND_STATIC("); + printPtr((StgPtr)((StgInd*)obj)->indirectee); + debugBelch(")\n"); + break; -void printStaticObjects( StgClosure *p ) -{ - while (p != END_OF_STATIC_OBJECT_LIST) { - p = UNTAG_STATIC_LIST_PTR(p); - printClosure(p); + case BLACKHOLE: + debugBelch("BLACKHOLE("); + printPtr((StgPtr)((StgInd*)obj)->indirectee); + debugBelch(")\n"); + break; - const StgInfoTable *info = get_itbl(p); - p = *STATIC_LINK(info, p); - } -} + /* Cannot happen -- use default case. + case RET_BCO: + case RET_SMALL: + case RET_BIG: + case RET_FUN: + */ -void printWeakLists() -{ - debugBelch("======= WEAK LISTS =======\n"); + case UPDATE_FRAME: + { + StgUpdateFrame* u = (StgUpdateFrame*)obj; + debugBelch("%s(", info_update_frame(obj)); + printPtr((StgPtr)GET_INFO((StgClosure *)u)); + debugBelch(","); + printPtr((StgPtr)u->updatee); + debugBelch(")\n"); + break; + } - for (uint32_t cap_idx = 0; cap_idx < n_capabilities; ++cap_idx) { - debugBelch("Capability %d:\n", cap_idx); - Capability *cap = capabilities[cap_idx]; - for (StgWeak *weak = cap->weak_ptr_list_hd; weak; weak = weak->link) { - printClosure((StgClosure*)weak); + case CATCH_FRAME: + { + StgCatchFrame* u = (StgCatchFrame*)obj; + debugBelch("CATCH_FRAME("); + printPtr((StgPtr)GET_INFO((StgClosure *)u)); + debugBelch(","); + printPtr((StgPtr)u->handler); + debugBelch(")\n"); + break; } - } - for (uint32_t gen_idx = 0; gen_idx <= oldest_gen->no; ++gen_idx) { - generation *gen = &generations[gen_idx]; - debugBelch("Generation %d current weaks:\n", gen_idx); - for (StgWeak *weak = gen->weak_ptr_list; weak; weak = weak->link) { - printClosure((StgClosure*)weak); + case UNDERFLOW_FRAME: + { + StgUnderflowFrame* u = (StgUnderflowFrame*)obj; + debugBelch("UNDERFLOW_FRAME("); + printPtr((StgPtr)u->next_chunk); + debugBelch(")\n"); + break; } - debugBelch("Generation %d old weaks:\n", gen_idx); - for (StgWeak *weak = gen->old_weak_ptr_list; weak; weak = weak->link) { - printClosure((StgClosure*)weak); + + case STOP_FRAME: + { + StgStopFrame* u = (StgStopFrame*)obj; + debugBelch("STOP_FRAME("); + printPtr((StgPtr)GET_INFO((StgClosure *)u)); + debugBelch(")\n"); + break; } - } - debugBelch("=========================\n"); -} + case ARR_WORDS: + { + StgWord i; + debugBelch("ARR_WORDS(\""); + for (i=0; ipayload[i]); + debugBelch("\")\n"); + break; + } -void printLargeAndPinnedObjects() -{ - debugBelch("====== PINNED OBJECTS ======\n"); + case MUT_ARR_PTRS_CLEAN: + debugBelch("MUT_ARR_PTRS_CLEAN(size=%" FMT_Word ")\n", (W_)((StgMutArrPtrs *)obj)->ptrs); + break; - for (uint32_t cap_idx = 0; cap_idx < n_capabilities; ++cap_idx) { - Capability *cap = capabilities[cap_idx]; + case MUT_ARR_PTRS_DIRTY: + debugBelch("MUT_ARR_PTRS_DIRTY(size=%" FMT_Word ")\n", (W_)((StgMutArrPtrs *)obj)->ptrs); + break; - debugBelch("Capability %d: Current pinned object block: %p\n", - cap_idx, (void*)cap->pinned_object_block); - for (bdescr *bd = cap->pinned_object_blocks; bd; bd = bd->link) { - debugBelch("%p\n", (void*)bd); - } - } + case MUT_ARR_PTRS_FROZEN_CLEAN: + debugBelch("MUT_ARR_PTRS_FROZEN_CLEAN(size=%" FMT_Word ")\n", (W_)((StgMutArrPtrs *)obj)->ptrs); + break; - debugBelch("====== LARGE OBJECTS =======\n"); - for (uint32_t gen_idx = 0; gen_idx <= oldest_gen->no; ++gen_idx) { - generation *gen = &generations[gen_idx]; - debugBelch("Generation %d current large objects:\n", gen_idx); - for (bdescr *bd = gen->large_objects; bd; bd = bd->link) { - debugBelch("%p: ", (void*)bd); - printClosure((StgClosure*)bd->start); - } + case SMALL_MUT_ARR_PTRS_CLEAN: + debugBelch("SMALL_MUT_ARR_PTRS_CLEAN(size=%" FMT_Word ")\n", + (W_)((StgSmallMutArrPtrs *)obj)->ptrs); + break; - debugBelch("Generation %d scavenged large objects:\n", gen_idx); - for (bdescr *bd = gen->scavenged_large_objects; bd; bd = bd->link) { - debugBelch("%p: ", (void*)bd); - printClosure((StgClosure*)bd->start); - } - } + case SMALL_MUT_ARR_PTRS_DIRTY: + debugBelch("SMALL_MUT_ARR_PTRS_DIRTY(size=%" FMT_Word ")\n", + (W_)((StgSmallMutArrPtrs *)obj)->ptrs); + break; - debugBelch("============================\n"); -} + case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: + debugBelch("SMALL_MUT_ARR_PTRS_FROZEN_CLEAN(size=%" FMT_Word ")\n", + (W_)((StgSmallMutArrPtrs *)obj)->ptrs); + break; -/* -------------------------------------------------------------------------- - * Address printing code - * - * Uses symbol table in (unstripped executable) - * ------------------------------------------------------------------------*/ + case MVAR_CLEAN: + case MVAR_DIRTY: + { + StgMVar* mv = (StgMVar*)obj; -/* -------------------------------------------------------------------------- - * Simple lookup table - * address -> function name - * ------------------------------------------------------------------------*/ + debugBelch("MVAR(head="); + if ((StgClosure*)mv->head == &stg_END_TSO_QUEUE_closure) { + debugBelch("END_TSO_QUEUE"); + } else { + debugBelch("%p", mv->head); + } -static HashTable * add_to_fname_table = NULL; + debugBelch(", tail="); + if ((StgClosure*)mv->tail == &stg_END_TSO_QUEUE_closure) { + debugBelch("END_TSO_QUEUE"); + } else { + debugBelch("%p", mv->tail); + } -const char *lookupGHCName( void *addr ) -{ - if (add_to_fname_table == NULL) - return NULL; + debugBelch(", value="); + if ((StgClosure*)mv->value == &stg_END_TSO_QUEUE_closure) { + debugBelch("END_TSO_QUEUE"); + } else { + debugBelch("%p", mv->value); + } + debugBelch(")\n"); - return lookupHashTable(add_to_fname_table, (StgWord)addr); -} + break; + } -/* -------------------------------------------------------------------------- - * Symbol table loading - * ------------------------------------------------------------------------*/ + case TVAR: + { + StgTVar* tv = (StgTVar*)obj; + debugBelch("TVAR(value=%p, wq=%p, num_updates=%" FMT_Word ")\n", tv->current_value, tv->first_watch_queue_entry, tv->num_updates); + break; + } -/* Causing linking trouble on Win32 plats, so I'm - disabling this for now. -*/ -#if defined(USING_LIBBFD) -# define PACKAGE 1 -# define PACKAGE_VERSION 1 -/* Those PACKAGE_* defines are workarounds for bfd: - * https://sourceware.org/bugzilla/show_bug.cgi?id=14243 - * ghc's build system filter PACKAGE_* values out specifically to avoid clashes - * with user's autoconf-based Cabal packages. - * It's a shame checks for unrelated fields instead of actually used - * macros. - */ -# include + case MUT_VAR_CLEAN: + { + StgMutVar* mv = (StgMutVar*)obj; + debugBelch("MUT_VAR_CLEAN(var=%p)\n", mv->var); + break; + } -/* Fairly ad-hoc piece of code that seems to filter out a lot of - * rubbish like the obj-splitting symbols - */ + case MUT_VAR_DIRTY: + { + StgMutVar* mv = (StgMutVar*)obj; + debugBelch("MUT_VAR_DIRTY(var=%p)\n", mv->var); + break; + } -static bool isReal( flagword flags STG_UNUSED, const char *name ) -{ -#if 0 - /* ToDo: make this work on BFD */ - int tp = type & N_TYPE; - if (tp == N_TEXT || tp == N_DATA) { - return (name[0] == '_' && name[1] != '_'); - } else { - return false; - } -#else - if (*name == '\0' || - (name[0] == 'g' && name[1] == 'c' && name[2] == 'c') || - (name[0] == 'c' && name[1] == 'c' && name[2] == '.')) { - return false; - } - return true; -#endif -} + case WEAK: + debugBelch("WEAK("); + debugBelch("key=%p value=%p finalizer=%p", + (StgPtr)(((StgWeak*)obj)->key), + (StgPtr)(((StgWeak*)obj)->value), + (StgPtr)(((StgWeak*)obj)->finalizer)); + debugBelch(")\n"); + /* ToDo: chase 'link' ? */ + break; -extern void DEBUG_LoadSymbols( const char *name ) -{ - bfd* abfd; - char **matching; + case TSO: + debugBelch("TSO("); + debugBelch("%lu (%p)",(unsigned long)(((StgTSO*)obj)->id), (StgTSO*)obj); + debugBelch(")\n"); + break; - bfd_init(); - abfd = bfd_openr(name, "default"); - if (abfd == NULL) { - barf("can't open executable %s to get symbol table", name); - } - if (!bfd_check_format_matches (abfd, bfd_object, &matching)) { - barf("mismatch"); - } + case STACK: + debugBelch("STACK\n"); + break; - { - long storage_needed; - asymbol **symbol_table; - long number_of_symbols; - long num_real_syms = 0; - long i; +#if 0 + /* Symptomatic of a problem elsewhere, have it fall-through & fail */ + case EVACUATED: + debugBelch("EVACUATED("); + printClosure((StgEvacuated*)obj->evacuee); + debugBelch(")\n"); + break; +#endif - storage_needed = bfd_get_symtab_upper_bound (abfd); + case COMPACT_NFDATA: + debugBelch("COMPACT_NFDATA(size=%" FMT_Word ")\n", + (W_)((StgCompactNFData *)obj)->totalW * (W_)sizeof(W_)); + break; - if (storage_needed < 0) { - barf("can't read symbol table"); - } - symbol_table = (asymbol **) stgMallocBytes(storage_needed,"DEBUG_LoadSymbols"); + case TREC_CHUNK: + debugBelch("TREC_CHUNK\n"); + break; - number_of_symbols = bfd_canonicalize_symtab (abfd, symbol_table); + default: + //barf("printClosure %d",get_itbl(obj)->type); + debugBelch("*** printClosure: unknown type %d ****\n", + (int)get_itbl(obj)->type ); + barf("printClosure %d",get_itbl(obj)->type); + return; + } +} - if (number_of_symbols < 0) { - barf("can't canonicalise symbol table"); +static void +printSmallBitmap( StgPtr spBottom, StgPtr payload, StgWord bitmap, + uint32_t size ) +{ + uint32_t i; + + for(i = 0; i < size; i++, bitmap >>= 1 ) { + debugBelch(" stk[%ld] (%p) = ", (long)(spBottom-(payload+i)), payload+i); + if ((bitmap & 1) == 0) { + printPtr((P_)payload[i]); + debugBelch(" -- "); + printObj((StgClosure*) payload[i]); + } else { + debugBelch("Word# %" FMT_Word "\n", (W_)payload[i]); } + } +} - if (add_to_fname_table == NULL) - add_to_fname_table = allocHashTable(); +static void +printLargeBitmap( StgPtr spBottom, StgPtr payload, StgLargeBitmap* large_bitmap, + uint32_t size ) +{ + StgWord bmp; + uint32_t i, j; - for( i = 0; i != number_of_symbols; ++i ) { - symbol_info info; - bfd_get_symbol_info(abfd,symbol_table[i],&info); - if (isReal(info.type, info.name)) { - insertHashTable(add_to_fname_table, - info.value, (void*)info.name); - num_real_syms += 1; + i = 0; + for (bmp=0; i < size; bmp++) { + StgWord bitmap = large_bitmap->bitmap[bmp]; + j = 0; + for(; i < size && j < BITS_IN(W_); j++, i++, bitmap >>= 1 ) { + debugBelch(" stk[%" FMT_Word "] (%p) = ", (W_)(spBottom-(payload+i)), payload+i); + if ((bitmap & 1) == 0) { + printPtr((P_)payload[i]); + debugBelch(" -- "); + printObj((StgClosure*) payload[i]); + } else { + debugBelch("Word# %" FMT_Word "\n", (W_)payload[i]); } } - - IF_DEBUG(interpreter, - debugBelch("Loaded %ld symbols. Of which %ld are real symbols\n", - number_of_symbols, num_real_syms) - ); - - stgFree(symbol_table); } } -#else /* USING_LIBBFD */ - -extern void DEBUG_LoadSymbols( const char *name STG_UNUSED ) +void +printStackChunk( StgPtr sp, StgPtr spBottom ) { - /* nothing, yet */ -} + const StgInfoTable *info; -#endif /* USING_LIBBFD */ + ASSERT(sp <= spBottom); + for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) { -void findPtr(P_ p, int); /* keep gcc -Wall happy */ + info = get_itbl((StgClosure *)sp); -int searched = 0; + switch (info->type) { -static int -findPtrBlocks (StgPtr p, bdescr *bd, StgPtr arr[], int arr_size, int i) -{ - StgPtr q, r, end; - for (; bd; bd = bd->link) { - searched++; - for (q = bd->start; q < bd->free; q++) { - if (UNTAG_CONST_CLOSURE((StgClosure*)*q) == (const StgClosure *)p) { - if (i < arr_size) { - for (r = bd->start; r < bd->free; r = end) { - // skip over zeroed-out slop - while (*r == 0) r++; - if (!LOOKS_LIKE_CLOSURE_PTR(r)) { - debugBelch("%p found at %p, no closure at %p\n", - p, q, r); - break; - } - end = r + closure_sizeW((StgClosure*)r); - if (q < end) { - debugBelch("%p = ", r); - printClosure((StgClosure *)r); - arr[i++] = r; - break; - } - } - if (r >= bd->free) { - debugBelch("%p found at %p, closure?", p, q); - } - } else { - return i; - } + case UPDATE_FRAME: + case CATCH_FRAME: + case UNDERFLOW_FRAME: + case STOP_FRAME: + printClosure((StgClosure*)sp); + continue; + + case RET_SMALL: { + StgWord c = *sp; + if (c == (StgWord)&stg_ctoi_R1p_info) { + debugBelch("tstg_ctoi_ret_R1p_info\n" ); + } else if (c == (StgWord)&stg_ctoi_R1n_info) { + debugBelch("stg_ctoi_ret_R1n_info\n" ); + } else if (c == (StgWord)&stg_ctoi_F1_info) { + debugBelch("stg_ctoi_ret_F1_info\n" ); + } else if (c == (StgWord)&stg_ctoi_D1_info) { + debugBelch("stg_ctoi_ret_D1_info\n" ); + } else if (c == (StgWord)&stg_ctoi_V_info) { + debugBelch("stg_ctoi_ret_V_info\n" ); + } else if (c == (StgWord)&stg_ap_v_info) { + debugBelch("stg_ap_v_info\n" ); + } else if (c == (StgWord)&stg_ap_f_info) { + debugBelch("stg_ap_f_info\n" ); + } else if (c == (StgWord)&stg_ap_d_info) { + debugBelch("stg_ap_d_info\n" ); + } else if (c == (StgWord)&stg_ap_l_info) { + debugBelch("stg_ap_l_info\n" ); + } else if (c == (StgWord)&stg_ap_n_info) { + debugBelch("stg_ap_n_info\n" ); + } else if (c == (StgWord)&stg_ap_p_info) { + debugBelch("stg_ap_p_info\n" ); + } else if (c == (StgWord)&stg_ap_pp_info) { + debugBelch("stg_ap_pp_info\n" ); + } else if (c == (StgWord)&stg_ap_ppp_info) { + debugBelch("stg_ap_ppp_info\n" ); + } else if (c == (StgWord)&stg_ap_pppp_info) { + debugBelch("stg_ap_pppp_info\n" ); + } else if (c == (StgWord)&stg_ap_ppppp_info) { + debugBelch("stg_ap_ppppp_info\n" ); + } else if (c == (StgWord)&stg_ap_pppppp_info) { + debugBelch("stg_ap_pppppp_info\n" ); + } else if (c == (StgWord)&stg_ret_v_info) { + debugBelch("stg_ret_v_info\n" ); + } else if (c == (StgWord)&stg_ret_p_info) { + debugBelch("stg_ret_p_info\n" ); + } else if (c == (StgWord)&stg_ret_n_info) { + debugBelch("stg_ret_n_info\n" ); + } else if (c == (StgWord)&stg_ret_f_info) { + debugBelch("stg_ret_f_info\n" ); + } else if (c == (StgWord)&stg_ret_d_info) { + debugBelch("stg_ret_d_info\n" ); + } else if (c == (StgWord)&stg_ret_l_info) { + debugBelch("stg_ret_l_info\n" ); +#if defined(PROFILING) + } else if (c == (StgWord)&stg_restore_cccs_info) { + debugBelch("stg_restore_cccs_info\n" ); + fprintCCS(stderr, (CostCentreStack*)sp[1]); + debugBelch("\n" ); + continue; + } else if (c == (StgWord)&stg_restore_cccs_eval_info) { + debugBelch("stg_restore_cccs_eval_info\n" ); + fprintCCS(stderr, (CostCentreStack*)sp[1]); + debugBelch("\n" ); + continue; +#endif + } else { + debugBelch("RET_SMALL (%p)\n", info); } + StgWord bitmap = info->layout.bitmap; + printSmallBitmap(spBottom, sp+1, + BITMAP_BITS(bitmap), BITMAP_SIZE(bitmap)); + continue; } - } - return i; -} -void -findPtr(P_ p, int follow) -{ - uint32_t g, n; - bdescr *bd; - const int arr_size = 1024; - StgPtr arr[arr_size]; - int i = 0; - searched = 0; + case RET_BCO: { + StgBCO *bco; -#if 0 - // We can't search the nursery, because we don't know which blocks contain - // valid data, because the bd->free pointers in the nursery are only reset - // just before a block is used. - for (n = 0; n < n_capabilities; n++) { - bd = nurseries[i].blocks; - i = findPtrBlocks(p,bd,arr,arr_size,i); - if (i >= arr_size) return; - } -#endif + bco = ((StgBCO *)sp[1]); - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - bd = generations[g].blocks; - i = findPtrBlocks(p,bd,arr,arr_size,i); - bd = generations[g].large_objects; - i = findPtrBlocks(p,bd,arr,arr_size,i); - if (i >= arr_size) return; - for (n = 0; n < n_capabilities; n++) { - i = findPtrBlocks(p, gc_threads[n]->gens[g].part_list, - arr, arr_size, i); - i = findPtrBlocks(p, gc_threads[n]->gens[g].todo_bd, - arr, arr_size, i); - } - if (i >= arr_size) return; - } - if (follow && i == 1) { - debugBelch("-->\n"); - findPtr(arr[0], 1); - } -} + debugBelch("RET_BCO (%p)\n", sp); + printLargeBitmap(spBottom, sp+2, + BCO_BITMAP(bco), BCO_BITMAP_SIZE(bco)); + continue; + } -const char *what_next_strs[] = { - [0] = "(unknown)", - [ThreadRunGHC] = "ThreadRunGHC", - [ThreadInterpret] = "ThreadInterpret", - [ThreadKilled] = "ThreadKilled", - [ThreadComplete] = "ThreadComplete" -}; + case RET_BIG: + debugBelch("RET_BIG (%p)\n", sp); + StgLargeBitmap* bitmap = GET_LARGE_BITMAP(info); + printLargeBitmap(spBottom, + (StgPtr)((StgClosure *) sp)->payload, + bitmap, + bitmap->size); + continue; + case RET_FUN: + { + const StgFunInfoTable *fun_info; + StgRetFun *ret_fun; -#else /* DEBUG */ -void printPtr( StgPtr p ) -{ - debugBelch("ptr 0x%p (enable -DDEBUG for more info) " , p ); + ret_fun = (StgRetFun *)sp; + fun_info = get_fun_itbl(UNTAG_CLOSURE(ret_fun->fun)); + debugBelch("RET_FUN (%p) (type=%d)\n", ret_fun->fun, (int)fun_info->f.fun_type); + switch (fun_info->f.fun_type) { + case ARG_GEN: + printSmallBitmap(spBottom, sp+2, + BITMAP_BITS(fun_info->f.b.bitmap), + BITMAP_SIZE(fun_info->f.b.bitmap)); + break; + case ARG_GEN_BIG: + printLargeBitmap(spBottom, sp+2, + GET_FUN_LARGE_BITMAP(fun_info), + GET_FUN_LARGE_BITMAP(fun_info)->size); + break; + default: + printSmallBitmap(spBottom, sp+2, + BITMAP_BITS(stg_arg_bitmaps[fun_info->f.fun_type]), + BITMAP_SIZE(stg_arg_bitmaps[fun_info->f.fun_type])); + break; + } + continue; + } + + default: + debugBelch("unknown object %d\n", (int)info->type); + barf("printStackChunk"); + } + } } -void printObj( StgClosure *obj ) +void printStack( StgStack *stack ) { - debugBelch("obj 0x%p (enable -DDEBUG for more info) " , obj ); + printStackChunk( stack->sp, stack->stack + stack->stack_size ); } -#endif /* DEBUG */ - /* ----------------------------------------------------------------------------- Closure types ===================================== rts/Printer.h ===================================== @@ -20,9 +20,10 @@ const char * info_type ( const StgClosure *closure ); const char * info_type_by_ip ( const StgInfoTable *ip ); const char * info_update_frame ( const StgClosure *closure ); -#if defined(DEBUG) extern void printClosure ( const StgClosure *obj ); extern void printStackChunk ( StgPtr sp, StgPtr spLim ); + +#if defined(DEBUG) extern void printTSO ( StgTSO *tso ); extern void printMutableList( bdescr *bd ); extern void printStaticObjects ( StgClosure *obj ); ===================================== rts/RtsSymbols.c ===================================== @@ -13,6 +13,7 @@ #include "TopHandler.h" #include "HsFFI.h" #include "CloneStack.h" +#include "rts/PrinterAPI.h" #include "sm/Storage.h" #include "sm/NonMovingMark.h" @@ -1001,6 +1002,7 @@ SymI_HasProto(_assertFail) \ SymI_HasProto(keepCAFs) \ SymI_HasProto(sendCloneStackMessage) \ + SymI_HasProto(printStack) \ RTS_USER_SIGNALS_SYMBOLS \ RTS_INTCHAR_SYMBOLS View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e2fac38419a9f76ba1aadd081c58009e8a7ca9a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e2fac38419a9f76ba1aadd081c58009e8a7ca9a 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 Mon Nov 2 08:24:08 2020 From: gitlab at gitlab.haskell.org (Alan Zimmerman) Date: Mon, 02 Nov 2020 03:24:08 -0500 Subject: [Git][ghc/ghc][wip/T18888] Restrict Linear arrow %1 to exactly literal 1 only Message-ID: <5f9fc228db3f0_785102e0ddc3592e0@gitlab.haskell.org.mail> Alan Zimmerman pushed to branch wip/T18888 at Glasgow Haskell Compiler / GHC Commits: 791cb337 by Alan Zimmerman at 2020-11-02T08:23:42+00:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 7 changed files: - compiler/GHC/Hs/Type.hs - compiler/GHC/Parser/PostProcess.hs - + testsuite/tests/linear/should_fail/T18888.hs - + testsuite/tests/linear/should_fail/T18888.stderr - + testsuite/tests/linear/should_fail/T18888_datakinds.hs - + testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/all.T Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1982,8 +1982,8 @@ ppr_fun_ty mult ty1 ty2 -------------------------- ppr_tylit :: HsTyLit -> SDoc -ppr_tylit (HsNumTy _ i) = integer i -ppr_tylit (HsStrTy _ s) = text (show s) +ppr_tylit (HsNumTy source i) = pprWithSourceText source (integer i) +ppr_tylit (HsStrTy source s) = pprWithSourceText source (text (show s)) -- | @'hsTypeNeedsParens' p t@ returns 'True' if the type @t@ needs parentheses ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -2620,7 +2620,8 @@ mkLHsOpTy x op y = in L loc (mkHsOpTy x op y) mkMultTy :: IsUnicodeSyntax -> Located Token -> LHsType GhcPs -> (HsArrow GhcPs, AddAnn) -mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy _ 1))) +mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy (SourceText "1") 1))) + -- See #18888 for the use of (SourceText "1") above = (HsLinearArrow u, AddAnn AnnPercentOne (combineLocs tok t)) mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok)) ===================================== testsuite/tests/linear/should_fail/T18888.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE LinearTypes #-} +module T18888 where + +f :: a %001 -> b +f x = undefined x ===================================== testsuite/tests/linear/should_fail/T18888.stderr ===================================== @@ -0,0 +1,3 @@ + +T18888.hs:4:9: + Illegal type: ‘001’ Perhaps you intended to use DataKinds ===================================== testsuite/tests/linear/should_fail/T18888_datakinds.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE LinearTypes #-} +{-# LANGUAGE DataKinds #-} +module T18888 where + +f :: a %001 -> b +f x = undefined x ===================================== testsuite/tests/linear/should_fail/T18888_datakinds.stderr ===================================== @@ -0,0 +1,5 @@ + +T18888_datakinds.hs:5:9: + Expected kind ‘GHC.Types.Multiplicity’, + but ‘001’ has kind ‘GHC.Num.Natural.Natural’ + In the type signature: f :: a %001 -> b ===================================== testsuite/tests/linear/should_fail/all.T ===================================== @@ -32,3 +32,5 @@ test('LinearIf', normal, compile_fail, ['']) test('LinearPatternGuardWildcard', normal, compile_fail, ['']) test('LinearFFI', normal, compile_fail, ['']) test('LinearTHFail', normal, compile_fail, ['']) +test('T18888', normal, compile_fail, ['']) +test('T18888_datakinds', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/791cb337549df002ff4323299e6baf825fe994f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/791cb337549df002ff4323299e6baf825fe994f4 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 Mon Nov 2 10:00:25 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 05:00:25 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [CmmSized] bump submodules Message-ID: <5f9fd8b985289_7853fb61da6134c3718df@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 5f836b02 by Moritz Angermann at 2020-11-02T10:00:09+00:00 [CmmSized] bump submodules - - - - - 4 changed files: - libraries/array - libraries/binary - libraries/bytestring - libraries/text Changes: ===================================== libraries/array ===================================== @@ -1 +1 @@ -Subproject commit 10e6c7e0522367677e4c33cc1c56eb852ef13420 +Subproject commit c7a696e3e6d5a6b00d3e00ca694af916f15bcff5 ===================================== libraries/binary ===================================== @@ -1 +1 @@ -Subproject commit dfaf780596328c9184758452b78288e8f405fcc1 +Subproject commit 6462b2f024d18fa6f47da180825bcd765a440f6c ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit e043aacfc4202a59ccae8b8c8cf0e1ad83a3f209 +Subproject commit fe4e14486e9b7125e41af5ad344b031685bdeaf8 ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit 80cb9ee2eb7141171171318bbd6760fe80012524 +Subproject commit f6b05066506550a8e965eb0082c92aba09772e50 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f836b0299e93d9978984773fd3b5a7da8dafd53 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f836b0299e93d9978984773fd3b5a7da8dafd53 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 Mon Nov 2 13:47:38 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 08:47:38 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] Fix T8832 Message-ID: <5fa00dfae5ab1_785ec59d8441709f@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: f42424ad by Moritz Angermann at 2020-11-02T13:47:24+00:00 Fix T8832 - - - - - 2 changed files: - libraries/base/GHC/Word.hs - testsuite/tests/simplCore/should_compile/T8832.stdout Changes: ===================================== libraries/base/GHC/Word.hs ===================================== @@ -183,8 +183,7 @@ instance Bits Word8 where (W8# x#) .&. (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `and#` (extendWord8# y#))) (W8# x#) .|. (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `or#` (extendWord8# y#))) (W8# x#) `xor` (W8# y#) = W8# (narrowWord8# ((extendWord8# x#) `xor#` (extendWord8# y#))) - complement (W8# x#) = W8# (narrowWord8# ((extendWord8# x#) `xor#` (extendWord8# mb#))) - where !(W8# mb#) = maxBound + complement (W8# x#) = W8# (narrowWord8# (not# (extendWord8# x#))) (W8# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = W8# (narrowWord8# ((extendWord8# x#) `shiftL#` i#)) | otherwise = W8# (narrowWord8# ((extendWord8# x#) `shiftRL#` negateInt# i#)) @@ -375,8 +374,7 @@ instance Bits Word16 where (W16# x#) .&. (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `and#` (extendWord16# y#))) (W16# x#) .|. (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `or#` (extendWord16# y#))) (W16# x#) `xor` (W16# y#) = W16# (narrowWord16# ((extendWord16# x#) `xor#` (extendWord16# y#))) - complement (W16# x#) = W16# (narrowWord16# ((extendWord16# x#) `xor#` (extendWord16# mb#))) - where !(W16# mb#) = maxBound + complement (W16# x#) = W16# (narrowWord16# (not# (extendWord16# x#))) (W16# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = W16# (narrowWord16# ((extendWord16# x#) `shiftL#` i#)) | otherwise = W16# (narrowWord16# ((extendWord16# x#) `shiftRL#` negateInt# i#)) @@ -613,8 +611,7 @@ instance Bits Word32 where (W32# x#) .&. (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `and#` (extendWord32# y#))) (W32# x#) .|. (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `or#` (extendWord32# y#))) (W32# x#) `xor` (W32# y#) = W32# (narrowWord32# ((extendWord32# x#) `xor#` (extendWord32# y#))) - complement (W32# x#) = W32# (narrowWord32# ((extendWord32# x#) `xor#` (extendWord32# mb#))) - where !(W32# mb#) = maxBound + complement (W32# x#) = W32# (narrowWord32# (not# (extendWord32# x#))) (W32# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = W32# (narrowWord32# ((extendWord32# x#) `shiftL#` i#)) | otherwise = W32# (narrowWord32# ((extendWord32# x#) `shiftRL#` negateInt# i#)) @@ -975,8 +972,7 @@ instance Bits Word64 where (W64# x#) .&. (W64# y#) = W64# (x# `and#` y#) (W64# x#) .|. (W64# y#) = W64# (x# `or#` y#) (W64# x#) `xor` (W64# y#) = W64# (x# `xor#` y#) - complement (W64# x#) = W64# (x# `xor#` mb#) - where !(W64# mb#) = maxBound + complement (W64# x#) = W64# (not# x#) (W64# x#) `shift` (I# i#) | isTrue# (i# >=# 0#) = W64# (x# `shiftL#` i#) | otherwise = W64# (x# `shiftRL#` negateInt# i#) ===================================== testsuite/tests/simplCore/should_compile/T8832.stdout ===================================== @@ -4,8 +4,8 @@ i16 = GHC.Int.I16# (GHC.Prim.narrowInt16# 0#) i32 = GHC.Int.I32# (GHC.Prim.narrowInt32# 0#) i64 = GHC.Int.I64# 0# w = GHC.Types.W# 0## -w8 = GHC.Word.W8# 0## -w16 = GHC.Word.W16# 0## -w32 = GHC.Word.W32# 0## +w8 = GHC.Word.W8# (GHC.Prim.narrowWord8# 0##) +w16 = GHC.Word.W16# (GHC.Prim.narrowWord16# 0##) +w32 = GHC.Word.W32# (GHC.Prim.narrowWord32# 0##) w64 = GHC.Word.W64# 0## z = 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f42424ad9b7daacce022c5d0d46553afae45e361 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f42424ad9b7daacce022c5d0d46553afae45e361 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 Mon Nov 2 13:55:46 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Mon, 02 Nov 2020 08:55:46 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-debug_gc_roots Message-ID: <5fa00fe26b8f3_7853fb6403c3aa842469c@gitlab.haskell.org.mail> David Eichmann pushed new branch wip/ghc-debug_gc_roots at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-debug_gc_roots 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 Mon Nov 2 14:09:36 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Mon, 02 Nov 2020 09:09:36 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/test_pkg_db Message-ID: <5fa01320d856f_7853fb641966db04282e4@gitlab.haskell.org.mail> Andreas Klebinger pushed new branch wip/andreask/test_pkg_db at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/test_pkg_db 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 Mon Nov 2 14:10:32 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Mon, 02 Nov 2020 09:10:32 -0500 Subject: [Git][ghc/ghc][wip/andreask/test_pkg_db] Testsuite: Support for user supplied package dbs Message-ID: <5fa013581c7e1_7853fb6436e66ec428467@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/test_pkg_db at Glasgow Haskell Compiler / GHC Commits: 0e68813c by Andreas Klebinger at 2020-11-02T15:10:09+01:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 3 changed files: - testsuite/driver/runtests.py - testsuite/driver/testlib.py - testsuite/mk/test.mk Changes: ===================================== testsuite/driver/runtests.py ===================================== @@ -71,6 +71,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -104,6 +105,8 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e68813ce47f170c6007597773514f46a3ad50df -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e68813ce47f170c6007597773514f46a3ad50df 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 Mon Nov 2 14:14:42 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 09:14:42 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: testsuite: Add --top flag to driver Message-ID: <5fa0145277882_7858fc850c43275b@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: ee6e4f5f by GHC GitLab CI at 2020-11-02T09:14:33-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - dce54ee9 by Ben Gamari at 2020-11-02T09:14:34-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 541a7c3f by Ryan Scott at 2020-11-02T09:14:34-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - 7b45b66c by Simon Peyton Jones at 2020-11-02T09:14:34-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 737d467f by Ben Gamari at 2020-11-02T09:14:35-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 24 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/ffi.rst - hadrian/src/Builder.hs - hadrian/src/Settings/Builders/RunTest.hs - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - testsuite/tests/callarity/unittest/CallArity1.hs - + testsuite/tests/ghci/scripts/T13795.script - + testsuite/tests/ghci/scripts/T13795.stdout - + testsuite/tests/ghci/scripts/T18828.hs - + testsuite/tests/ghci/scripts/T18828.script - + testsuite/tests/ghci/scripts/T18828.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/rts/T5423.hs - testsuite/tests/rts/T5423.stdout - testsuite/tests/rts/T5423_c.c - testsuite/tests/rts/T5423_cmm.cmm Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -19,8 +19,8 @@ module GHC.Core.Lint ( -- ** Debug output endPass, endPassIO, - dumpPassResult, - GHC.Core.Lint.dumpIfSet, + displayLintResults, dumpPassResult, + dumpIfSet, ) where #include "HsVersions.h" @@ -65,7 +65,8 @@ import GHC.Core.TyCon as TyCon import GHC.Core.Coercion.Axiom import GHC.Core.Unify import GHC.Types.Basic -import GHC.Utils.Error as Err +import GHC.Utils.Error hiding ( dumpIfSet ) +import qualified GHC.Utils.Error as Err import GHC.Data.List.SetOps import GHC.Builtin.Names import GHC.Utils.Outputable as Outputable @@ -372,33 +373,38 @@ lintPassResult hsc_env pass binds | not (gopt Opt_DoCoreLinting dflags) = return () | otherwise - = do { let (warns, errs) = lintCoreBindings dflags pass (interactiveInScope hsc_env) binds + = do { let warns_and_errs = lintCoreBindings dflags pass (interactiveInScope hsc_env) binds ; Err.showPass dflags ("Core Linted result of " ++ showPpr dflags pass) - ; displayLintResults dflags pass warns errs binds } + ; displayLintResults dflags (showLintWarnings pass) (ppr pass) + (pprCoreBindings binds) warns_and_errs } where dflags = hsc_dflags hsc_env -displayLintResults :: DynFlags -> CoreToDo - -> Bag Err.MsgDoc -> Bag Err.MsgDoc -> CoreProgram +displayLintResults :: DynFlags + -> Bool -- ^ If 'True', display linter warnings. + -- If 'False', ignore linter warnings. + -> SDoc -- ^ The source of the linted program + -> SDoc -- ^ The linted program, pretty-printed + -> WarnsAndErrs -> IO () -displayLintResults dflags pass warns errs binds +displayLintResults dflags display_warnings pp_what pp_pgm (warns, errs) | not (isEmptyBag errs) = do { putLogMsg dflags NoReason Err.SevDump noSrcSpan $ withPprStyle defaultDumpStyle - (vcat [ lint_banner "errors" (ppr pass), Err.pprMessageBag errs + (vcat [ lint_banner "errors" pp_what, Err.pprMessageBag errs , text "*** Offending Program ***" - , pprCoreBindings binds + , pp_pgm , text "*** End of Offense ***" ]) ; Err.ghcExit dflags 1 } | not (isEmptyBag warns) , not (hasNoDebugOutput dflags) - , showLintWarnings pass + , display_warnings -- If the Core linter encounters an error, output to stderr instead of -- stdout (#13342) = putLogMsg dflags NoReason Err.SevInfo noSrcSpan $ withPprStyle defaultDumpStyle - (lint_banner "warnings" (ppr pass) $$ Err.pprMessageBag (mapBag ($$ blankLine) warns)) + (lint_banner "warnings" pp_what $$ Err.pprMessageBag (mapBag ($$ blankLine) warns)) | otherwise = return () @@ -413,29 +419,18 @@ showLintWarnings :: CoreToDo -> Bool showLintWarnings (CoreDoSimplify _ (SimplMode { sm_phase = InitialPhase })) = False showLintWarnings _ = True -lintInteractiveExpr :: String -> HscEnv -> CoreExpr -> IO () +lintInteractiveExpr :: SDoc -- ^ The source of the linted expression + -> HscEnv -> CoreExpr -> IO () lintInteractiveExpr what hsc_env expr | not (gopt Opt_DoCoreLinting dflags) = return () | Just err <- lintExpr dflags (interactiveInScope hsc_env) expr - = do { display_lint_err err - ; Err.ghcExit dflags 1 } + = displayLintResults dflags False what (pprCoreExpr expr) (emptyBag, err) | otherwise = return () where dflags = hsc_dflags hsc_env - display_lint_err err - = do { putLogMsg dflags NoReason Err.SevDump - noSrcSpan - $ withPprStyle defaultDumpStyle - (vcat [ lint_banner "errors" (text what) - , err - , text "*** Offending Program ***" - , pprCoreExpr expr - , text "*** End of Offense ***" ]) - ; Err.ghcExit dflags 1 } - interactiveInScope :: HscEnv -> [Var] -- In GHCi we may lint expressions, or bindings arising from 'deriving' -- clauses, that mention variables bound in the interactive context. @@ -464,7 +459,7 @@ interactiveInScope hsc_env -- where t is a RuntimeUnk (see TcType) -- | Type-check a 'CoreProgram'. See Note [Core Lint guarantee]. -lintCoreBindings :: DynFlags -> CoreToDo -> [Var] -> CoreProgram -> (Bag MsgDoc, Bag MsgDoc) +lintCoreBindings :: DynFlags -> CoreToDo -> [Var] -> CoreProgram -> WarnsAndErrs -- Returns (warnings, errors) -- If you edit this function, you may need to update the GHC formalism -- See Note [GHC Formalism] @@ -540,16 +535,16 @@ hence the `TopLevelFlag` on `tcPragExpr` in GHC.IfaceToCore. -} -lintUnfolding :: Bool -- True <=> is a compulsory unfolding +lintUnfolding :: Bool -- True <=> is a compulsory unfolding -> DynFlags -> SrcLoc - -> VarSet -- Treat these as in scope + -> VarSet -- Treat these as in scope -> CoreExpr - -> Maybe MsgDoc -- Nothing => OK + -> Maybe (Bag MsgDoc) -- Nothing => OK lintUnfolding is_compulsory dflags locn var_set expr | isEmptyBag errs = Nothing - | otherwise = Just (pprMessageBag errs) + | otherwise = Just errs where vars = nonDetEltsUniqSet var_set (_warns, errs) = initL dflags (defaultLintFlags dflags) vars $ @@ -563,11 +558,11 @@ lintUnfolding is_compulsory dflags locn var_set expr lintExpr :: DynFlags -> [Var] -- Treat these as in scope -> CoreExpr - -> Maybe MsgDoc -- Nothing => OK + -> Maybe (Bag MsgDoc) -- Nothing => OK lintExpr dflags vars expr | isEmptyBag errs = Nothing - | otherwise = Just (pprMessageBag errs) + | otherwise = Just errs where (_warns, errs) = initL dflags (defaultLintFlags dflags) vars linter linter = addLoc TopLevelBindings $ @@ -2326,13 +2321,15 @@ lintCoercion (HoleCo h) -} lintAxioms :: DynFlags + -> SDoc -- ^ The source of the linted axioms -> [CoAxiom Branched] - -> WarnsAndErrs -lintAxioms dflags axioms - = initL dflags (defaultLintFlags dflags) [] $ - do { mapM_ lint_axiom axioms - ; let axiom_groups = groupWith coAxiomTyCon axioms - ; mapM_ lint_axiom_group axiom_groups } + -> IO () +lintAxioms dflags what axioms = + displayLintResults dflags True what (vcat $ map pprCoAxiom axioms) $ + initL dflags (defaultLintFlags dflags) [] $ + do { mapM_ lint_axiom axioms + ; let axiom_groups = groupWith coAxiomTyCon axioms + ; mapM_ lint_axiom_group axiom_groups } lint_axiom :: CoAxiom Branched -> LintM () lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1713,7 +1713,7 @@ hscParsedStmt hsc_env stmt = runInteractiveHsc hsc_env $ do -- Desugar it ds_expr <- ioMsgMaybe $ deSugarExpr hsc_env tc_expr - liftIO (lintInteractiveExpr "desugar expression" hsc_env ds_expr) + liftIO (lintInteractiveExpr (text "desugar expression") hsc_env ds_expr) handleWarnings -- Then code-gen, and link it @@ -1955,7 +1955,7 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr ; prepd_expr <- corePrepExpr hsc_env tidy_expr {- Lint if necessary -} - ; lintInteractiveExpr "hscCompileExpr" hsc_env prepd_expr + ; lintInteractiveExpr (text "hscCompileExpr") hsc_env prepd_expr {- Convert to BCOs -} ; bcos <- coreExprToBCOs hsc_env ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -62,6 +62,7 @@ import GHC.Core.TyCon import GHC.Core.ConLike import GHC.Core.DataCon import GHC.Core.Opt.OccurAnal ( occurAnalyseExpr ) +import GHC.Core.Ppr import GHC.Unit.External import GHC.Unit.Module @@ -73,6 +74,7 @@ import GHC.Utils.Outputable import GHC.Utils.Misc import GHC.Utils.Panic +import GHC.Data.Bag import GHC.Data.Maybe import GHC.Data.FastString import GHC.Data.List.SetOps @@ -1199,13 +1201,11 @@ tcIfaceRule (IfaceRule {ifRuleName = name, ifActivation = act, ifRuleBndrs = bnd bndrs' ++ exprsFreeIdsList args') ; case lintExpr dflags in_scope rhs' of - Nothing -> return () - Just fail_msg -> do { mod <- getIfModule - ; pprPanic "Iface Lint failure" - (vcat [ text "In interface for" <+> ppr mod - , hang doc 2 fail_msg - , ppr name <+> equals <+> ppr rhs' - , text "Iface expr =" <+> ppr rhs ]) } } + Nothing -> return () + Just errs -> liftIO $ + displayLintResults dflags False doc + (pprCoreExpr rhs') + (emptyBag, errs) } ; return (bndrs', args', rhs') } ; let mb_tcs = map ifTopFreeName args ; this_mod <- getIfModule @@ -1724,13 +1724,10 @@ tcPragExpr is_compulsory toplvl name expr in_scope <- get_in_scope dflags <- getDynFlags case lintUnfolding is_compulsory dflags noSrcLoc in_scope core_expr' of - Nothing -> return () - Just fail_msg -> do { mod <- getIfModule - ; pprPanic "Iface Lint failure" - (vcat [ text "In interface for" <+> ppr mod - , hang doc 2 fail_msg - , ppr name <+> equals <+> ppr core_expr' - , text "Iface expr =" <+> ppr expr ]) } + Nothing -> return () + Just errs -> liftIO $ + displayLintResults dflags False doc + (pprCoreExpr core_expr') (emptyBag, errs) return core_expr' where doc = ppWhen is_compulsory (text "Compulsory") <+> ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -296,11 +296,7 @@ tcRnModuleTcRnM hsc_env mod_sum tcRnSrcDecls explicit_mod_hdr local_decls export_ies ; whenM (goptM Opt_DoCoreLinting) $ - do { let (warns, errs) = lintGblEnv (hsc_dflags hsc_env) tcg_env - ; mapBagM_ (addWarn NoReason) warns - ; mapBagM_ addErr errs - ; failIfErrsM } -- if we have a lint error, we're only - -- going to get in deeper trouble by proceeding + lintGblEnv (hsc_dflags hsc_env) tcg_env ; setGblEnv tcg_env $ do { -- Process the export list @@ -2629,12 +2625,13 @@ tcRnType hsc_env flexi normalise rdr_type -- Do validity checking on type ; checkValidType (GhciCtxt True) ty - ; ty' <- if normalise - then do { fam_envs <- tcGetFamInstEnvs - ; let (_, ty') - = normaliseType fam_envs Nominal ty - ; return ty' } - else return ty ; + -- Optionally (:k vs :k!) normalise the type. Does two things: + -- normaliseType: expand type-family applications + -- expandTypeSynonyms: expand type synonyms (#18828) + ; fam_envs <- tcGetFamInstEnvs + ; let ty' | normalise = expandTypeSynonyms $ snd $ + normaliseType fam_envs Nominal ty + | otherwise = ty ; return (ty', mkInfForAllTys kvs (tcTypeKind ty')) } ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -1712,7 +1712,8 @@ getRoleAnnots bndrs role_env -- | Check the 'TcGblEnv' for consistency. Currently, only checks -- axioms, but should check other aspects, too. -lintGblEnv :: DynFlags -> TcGblEnv -> (Bag SDoc, Bag SDoc) -lintGblEnv dflags tcg_env = lintAxioms dflags axioms +lintGblEnv :: DynFlags -> TcGblEnv -> TcM () +lintGblEnv dflags tcg_env = + liftIO $ lintAxioms dflags (text "TcGblEnv axioms") axioms where axioms = typeEnvCoAxioms (tcg_type_env tcg_env) ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -37,6 +37,9 @@ Compiler - Type checker plugins which work with the natural numbers now should use ``naturalTy`` kind instead of ``typeNatKind``, which has been removed. +- GHCi's ``:kind!`` command now expands through type synonyms in addition to type + families. See :ghci-cmd:`:kind`. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -83,6 +83,21 @@ For more details on the implementation see the Paper: Last known to be accessible `here `_. +Varargs not supported by ``ccall`` calling convention +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Note that functions requiring varargs arguments are unsupported by the ``ccall`` +calling convention. Foreign imports needing to call such functions should rather +use the ``capi`` convention, giving an explicit signature for the needed +call-pattern. For instance, one could write: :: + + foreign import "capi" "printf" + my_printf :: Ptr CChar -> CInt -> IO () + + printInt :: CInt -> IO () + printInt n = my_printf "printed number %d" n + + .. _ffi-ghcexts: GHC extensions to the FFI Chapter ===================================== hadrian/src/Builder.hs ===================================== @@ -304,6 +304,11 @@ instance H.Builder Builder where Makeindex -> unit $ cmd' [Cwd output] [path] (buildArgs ++ [input]) Tar _ -> cmd' buildOptions echo [path] buildArgs + + -- RunTest produces a very large amount of (colorised) output; + -- Don't attempt to capture it. + RunTest -> cmd echo [path] buildArgs + _ -> cmd' echo [path] buildArgs -- TODO: Some builders are required only on certain platforms. For example, ===================================== hadrian/src/Settings/Builders/RunTest.hs ===================================== @@ -102,6 +102,7 @@ runTestBuilderArgs = builder RunTest ? do -- TODO: set CABAL_MINIMAL_BUILD/CABAL_PLUGIN_BUILD mconcat [ arg $ "testsuite/driver/runtests.py" , pure [ "--rootdir=" ++ testdir | testdir <- rootdirs ] + , arg "--top", arg (top -/- "testsuite") , arg "-e", arg $ "windows=" ++ show windowsHost , arg "-e", arg $ "darwin=" ++ show osxHost , arg "-e", arg $ "config.local=False" @@ -129,7 +130,6 @@ runTestBuilderArgs = builder RunTest ? do , arg "-e", arg $ "config.ghc_dynamic_by_default=" ++ show hasDynamicByDefault , arg "-e", arg $ "config.ghc_dynamic=" ++ show hasDynamic - , arg "-e", arg $ "config.top=" ++ show (top -/- "testsuite") , arg "-e", arg $ "config.wordsize=" ++ show wordsize , arg "-e", arg $ "config.os=" ++ show os , arg "-e", arg $ "config.arch=" ++ show arch ===================================== testsuite/driver/runtests.py ===================================== @@ -14,6 +14,7 @@ import tempfile import time import re import traceback +from pathlib import Path # We don't actually need subprocess in runtests.py, but: # * We do need it in testlibs.py @@ -56,6 +57,7 @@ parser = argparse.ArgumentParser(description="GHC's testsuite driver") perf_group = parser.add_mutually_exclusive_group() parser.add_argument("-e", action='append', help="A string to execute from the command line.") +parser.add_argument("--top", type=Path, help="path to top of testsuite/ tree") parser.add_argument("--config-file", action="append", help="config file") parser.add_argument("--config", action='append', help="config field") parser.add_argument("--rootdir", action='append', help="root of tree containing tests (default: .)") @@ -104,6 +106,9 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +if args.top: + config.top = args.top + if args.only: config.only = args.only config.run_only_some_tests = True @@ -277,7 +282,7 @@ testopts_local.x = TestOptions() # if timeout == -1 then we try to calculate a sensible value if config.timeout == -1: - config.timeout = int(read_no_crs(config.top + '/timeout/calibrate.out')) + config.timeout = int(read_no_crs(config.top / 'timeout' / 'calibrate.out')) print('Timeout is ' + str(config.timeout)) print('Known ways: ' + ', '.join(config.other_ways)) ===================================== testsuite/driver/testglobals.py ===================================== @@ -22,7 +22,7 @@ class TestConfig: def __init__(self): # Where the testsuite root is - self.top = '' + self.top = Path('.') # Directories below which to look for test description files (foo.T) self.rootdirs = [] ===================================== testsuite/driver/testlib.py ===================================== @@ -1110,7 +1110,7 @@ def do_test(name: TestName, dst_makefile = in_testdir('Makefile') if src_makefile.exists(): makefile = src_makefile.read_text(encoding='UTF-8') - makefile = re.sub('TOP=.*', 'TOP=' + config.top, makefile, 1) + makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1) dst_makefile.write_text(makefile, encoding='UTF-8') if opts.pre_cmd: ===================================== testsuite/mk/test.mk ===================================== @@ -256,13 +256,13 @@ endif RUNTEST_OPTS += \ --rootdir=. \ --config-file=$(CONFIG) \ + --top="$(TOP_ABS)" \ -e 'config.platform="$(TARGETPLATFORM)"' \ -e 'config.os="$(TargetOS_CPP)"' \ -e 'config.arch="$(TargetARCH_CPP)"' \ -e 'config.wordsize="$(WORDSIZE)"' \ -e 'config.timeout=int($(TIMEOUT)) or config.timeout' \ - -e 'config.exeext="$(exeext)"' \ - -e 'config.top="$(TOP_ABS)"' + -e 'config.exeext="$(exeext)"' # Wrap non-empty program paths in quotes, because they may contain spaces. Do # it here, so we don't have to (and don't forget to do it) in the .T test ===================================== testsuite/tests/callarity/unittest/CallArity1.hs ===================================== @@ -172,7 +172,7 @@ main = do dflags <- getSessionDynFlags liftIO $ forM_ exprs $ \(n,e) -> do case lintExpr dflags [f,scrutf,scruta] e of - Just msg -> putMsg dflags (msg $$ text "in" <+> text n) + Just errs -> putMsg dflags (pprMessageBag errs $$ text "in" <+> text n) Nothing -> return () putMsg dflags (text n Outputable.<> char ':') -- liftIO $ putMsg dflags (ppr e) ===================================== testsuite/tests/ghci/scripts/T13795.script ===================================== @@ -0,0 +1,2 @@ +type A = () +:kind! A ===================================== testsuite/tests/ghci/scripts/T13795.stdout ===================================== @@ -0,0 +1,2 @@ +A :: * += () ===================================== testsuite/tests/ghci/scripts/T18828.hs ===================================== @@ -0,0 +1,31 @@ +{-# Language ConstraintKinds #-} +{-# Language DataKinds #-} +{-# Language GADTs #-} +{-# Language PolyKinds #-} +{-# Language RankNTypes #-} +{-# Language StandaloneKindSignatures #-} +{-# Language TypeFamilies #-} +{-# Language TypeOperators #-} +module T18828 where + +import Data.Kind + +type Cat :: Type -> Type +type Cat ob = ob -> ob -> Type + +type Dict :: Constraint -> Type +data Dict cls where + Dict :: cls => Dict cls + +type (:-) :: Cat Constraint +newtype cls1 :- cls2 where + Sub :: (cls1 => Dict cls2) -> (cls1 :- cls2) + +type ObjectSyn :: Cat ob -> Type +type ObjectSyn (cat :: ob -> ob -> Type) = ob + +type + ObjectFam :: Cat ob -> Type +type family + ObjectFam cat where + ObjectFam @ob cat = ob ===================================== testsuite/tests/ghci/scripts/T18828.script ===================================== @@ -0,0 +1,9 @@ +:load T18828 +:set -XDataKinds -XKindSignatures -XRankNTypes +import Data.Type.Equality +:k! ObjectSyn (->) +:k! forall ob. ObjectSyn ((:~:) :: Cat ob) +:k! ObjectSyn (:-) +:k! ObjectFam (->) +:k! forall ob. ObjectFam ((:~:) :: Cat ob) +:k! ObjectFam (:-) ===================================== testsuite/tests/ghci/scripts/T18828.stdout ===================================== @@ -0,0 +1,12 @@ +ObjectSyn (->) :: * += * +forall ob. ObjectSyn ((:~:) :: Cat ob) :: * += ob +ObjectSyn (:-) :: * += Constraint +ObjectFam (->) :: * += * +forall ob. ObjectFam ((:~:) :: Cat ob) :: * += ob +ObjectFam (:-) :: * += Constraint ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -279,6 +279,7 @@ test('T13591', expect_broken(13591), ghci_script, ['T13591.script']) test('T13699', normal, ghci_script, ['T13699.script']) test('T13988', normal, ghci_script, ['T13988.script']) test('T13407', normal, ghci_script, ['T13407.script']) +test('T13795', normal, ghci_script, ['T13795.script']) test('T13963', normal, ghci_script, ['T13963.script']) test('T14342', [extra_hc_opts("-XOverloadedStrings -XRebindableSyntax")], ghci_script, ['T14342.script']) @@ -322,3 +323,4 @@ test('T17669', [extra_run_opts('-fexternal-interpreter -fobject-code'), expect_b test('T18501', normal, ghci_script, ['T18501.script']) test('T18644', normal, ghci_script, ['T18644.script']) test('T18755', normal, ghci_script, ['T18755.script']) +test('T18828', normal, ghci_script, ['T18828.script']) ===================================== testsuite/tests/rts/T5423.hs ===================================== @@ -1,3 +1,5 @@ +-- | Verify that @foreign import prim@ calls with more than 10 arguments +-- are lowered correctly. {-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-} ===================================== testsuite/tests/rts/T5423.stdout ===================================== @@ -1,2 +1,2 @@ -111 112 113 114 115 116 117 118 119 120 +111 112 113 114 115 116 117 118 119 120 120 ===================================== testsuite/tests/rts/T5423_c.c ===================================== @@ -1,6 +1,34 @@ +#include #include void flush_stdout(void) { fflush(stdout); } + +void print_it( + StgWord r1, + StgWord r2, + StgWord r3, + StgWord r4, + StgWord r5, + StgWord r6, + StgWord r7, + StgWord r8, + StgWord r9, + StgWord r10 + ) +{ + printf("%" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word "\n", + r1, r2, r3, r4, r5, + r6, r7, r8, r9, r10); +} ===================================== testsuite/tests/rts/T5423_cmm.cmm ===================================== @@ -10,7 +10,6 @@ test (W_ r1, W_ r9, W_ r10) { - foreign "C" printf("%d %d %d %d %d %d %d %d %d %d\n", - r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); + foreign "C" print_it(r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); return (r10); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e015d2824c5c17dd3be9fbb7f1467c800b219a75...737d467ffc0200dbe173ccd345a16fc3d8e1bac3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e015d2824c5c17dd3be9fbb7f1467c800b219a75...737d467ffc0200dbe173ccd345a16fc3d8e1bac3 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 Mon Nov 2 14:18:45 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Mon, 02 Nov 2020 09:18:45 -0500 Subject: [Git][ghc/ghc][wip/andreask/32bit_cmp_fix] 2 commits: Testsuite: Support for user supplied package dbs Message-ID: <5fa015453bc0f_7853fb61d049f6c441047@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/32bit_cmp_fix at Glasgow Haskell Compiler / GHC Commits: 755d56b7 by Andreas Klebinger at 2020-11-02T14:22:36+01:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 092d1eea by Andreas Klebinger at 2020-11-02T15:15:14+01:00 Test 64bit comparison codegen - - - - - 6 changed files: - testsuite/driver/runtests.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm Changes: ===================================== testsuite/driver/runtests.py ===================================== @@ -71,6 +71,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -104,6 +105,8 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,20 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , reqlib('primitive') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,160 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +module Main where + +#ifdef __GLASGOW_HASKELL__ +#include "MachDeps.h" +#endif + +import Data.Primitive.ByteArray +import GHC.Types +import GHC.Exts +import Data.Word +import Data.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#else +#define INT64 Int# +#define WORD64 Word# +#endif + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- Moving values int Int64# / Word64# is currently +-- quite annoying. The only way to do this on both +-- 64 and 32bit platforms is to go through a byte +-- array. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +getInts a1 a2 = do + mba@(MutableByteArray ba) <- newPinnedByteArray 16 + writeByteArray mba 0 a1 + writeByteArray mba 1 a2 + i1 <- readInt 0 ba + i2 <- readInt 1 ba + return ( i1, i2 ) + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +getWords a1 a2 = do + mba@(MutableByteArray ba) <- newPinnedByteArray 16 + writeByteArray mba 0 a1 + writeByteArray mba 1 a2 + w1 <- readWord 0 ba :: IO W64 + w2 <- readWord 1 ba + return ( w1, w2 ) + +readInt :: Int -> MutableByteArray# RealWorld -> IO I64 +readInt (I# i) ba = IO $ \s -> + case (readInt64Array# ba i s) of + (# s', x #) -> (# s', I64 x #) + +readWord :: Int -> MutableByteArray# RealWorld -> IO W64 +readWord (I# i) ba = IO $ \s -> + case (readWord64Array# ba i s) of + (# s', x #) -> (# s', W64 x #) ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/55dd45fdbb7afa88e56b1290deb6f2588adc8fad...092d1eeafe6f24b5fab1ff7c4aff622331677717 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/55dd45fdbb7afa88e56b1290deb6f2588adc8fad...092d1eeafe6f24b5fab1ff7c4aff622331677717 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 Mon Nov 2 15:00:07 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Mon, 02 Nov 2020 10:00:07 -0500 Subject: [Git][ghc/ghc][wip/con-info] 1061 commits: Remove custom ExceptionMonad class (#18075) (updating haddock submodule accordingly) Message-ID: <5fa01ef71b0c4_7853fb5dd2f99644533e5@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 30272412 by Artem Pelenitsyn at 2020-05-04T13:19:59-04:00 Remove custom ExceptionMonad class (#18075) (updating haddock submodule accordingly) - - - - - b9f7c08f by jneira at 2020-05-04T13:20:37-04:00 Remove unused hs-boot file - - - - - 1d8f80cd by Sylvain Henry at 2020-05-05T03:22:46-04:00 Remove references to -package-key * remove references to `-package-key` which has been removed in 2016 (240ddd7c39536776e955e881d709bbb039b48513) * remove support for `-this-package-key` which has been deprecated at the same time - - - - - 7bc3a65b by Sylvain Henry at 2020-05-05T03:23:31-04:00 Remove SpecConstrAnnotation (#13681) This has been deprecated since 2013. Use GHC.Types.SPEC instead. Make GHC.Exts "not-home" for haddock Metric Decrease: haddock.base - - - - - 3c862f63 by DenisFrezzato at 2020-05-05T03:24:15-04:00 Fix Haskell98 short description in documentation - - - - - 2420c555 by Ryan Scott at 2020-05-05T03:24:53-04:00 Add regression tests for #16244, #16245, #16758 Commit e3c374cc5bd7eb49649b9f507f9f7740697e3f70 ended up fixing quite a few bugs: * This commit fixes #16244 completely. A regression test has been added. * This commit fixes one program from #16245. (The program in https://gitlab.haskell.org/ghc/ghc/issues/16245#note_211369 still panics, and the program in https://gitlab.haskell.org/ghc/ghc/issues/16245#note_211400 still loops infinitely.) A regression test has been added for this program. * This commit fixes #16758. Accordingly, this patch removes the `expect_broken` label from the `T16758` test case, moves it from `should_compile` to `should_fail` (as it should produce an error message), and checks in the expected stderr. - - - - - 40c71c2c by Sylvain Henry at 2020-05-05T03:25:31-04:00 Fix colorized error messages (#18128) In b3df9e780fb2f5658412c644849cd0f1e6f50331 I broke colorized messages by using "dump" style instead of "user" style. This commits fixes it. - - - - - 7ab6ab09 by Richard Eisenberg at 2020-05-06T04:39:32-04:00 Refactor hole constraints. Previously, holes (both expression holes / out of scope variables and partial-type-signature wildcards) were emitted as *constraints* via the CHoleCan constructor. While this worked fine for error reporting, there was a fair amount of faff in keeping these constraints in line. In particular, and unlike other constraints, we could never change a CHoleCan to become CNonCanonical. In addition: * the "predicate" of a CHoleCan constraint was really the type of the hole, which is not a predicate at all * type-level holes (partial type signature wildcards) carried evidence, which was never used * tcNormalise (used in the pattern-match checker) had to create a hole constraint just to extract it again; it was quite messy The new approach is to record holes directly in WantedConstraints. It flows much more nicely now. Along the way, I did some cleaning up of commentary in GHC.Tc.Errors.Hole, which I had a hard time understanding. This was instigated by a future patch that will refactor the way predicates are handled. The fact that CHoleCan's "predicate" wasn't really a predicate is incompatible with that future patch. No test case, because this is meant to be purely internal. It turns out that this change improves the performance of the pattern-match checker, likely because fewer constraints are sloshing about in tcNormalise. I have not investigated deeply, but an improvement is not a surprise here: ------------------------- Metric Decrease: PmSeriesG ------------------------- - - - - - 420b957d by Ben Gamari at 2020-05-06T04:40:08-04:00 rts: Zero block flags with -DZ Block flags are very useful for determining the state of a block. However, some block allocator users don't touch them, leading to misleading values. Ensure that we zero then when zero-on-gc is set. This is safe and makes the flags more useful during debugging. - - - - - 740b3b8d by Ben Gamari at 2020-05-06T04:40:08-04:00 nonmoving: Fix incorrect failed_to_evac value during deadlock gc Previously we would incorrectly set the failed_to_evac flag if we evacuated a value due to a deadlock GC. This would cause us to mark more things as dirty than strictly necessary. It also turned up a nasty but which I will fix next. - - - - - b2d72c75 by Ben Gamari at 2020-05-06T04:40:08-04:00 nonmoving: Fix handling of dirty objects Previously we (incorrectly) relied on failed_to_evac to be "precise". That is, we expected it to only be true if *all* of an object's fields lived outside of the non-moving heap. However, does not match the behavior of failed_to_evac, which is true if *any* of the object's fields weren't promoted (meaning that some others *may* live in the non-moving heap). This is problematic as we skip the non-moving write barrier for dirty objects (which we can only safely do if *all* fields point outside of the non-moving heap). Clearly this arises due to a fundamental difference in the behavior expected of failed_to_evac in the moving and non-moving collector. e.g., in the moving collector it is always safe to conservatively say failed_to_evac=true whereas in the non-moving collector the safe value is false. This issue went unnoticed as I never wrote down the dirtiness invariant enforced by the non-moving collector. We now define this invariant as An object being marked as dirty implies that all of its fields are on the mark queue (or, equivalently, update remembered set). To maintain this invariant we teach nonmovingScavengeOne to push the fields of objects which we fail to evacuate to the update remembered set. This is a simple and reasonably cheap solution and avoids the complexity and fragility that other, more strict alternative invariants would require. All of this is described in a new Note, Note [Dirty flags in the non-moving collector] in NonMoving.c. - - - - - 9f3e6884 by Zubin Duggal at 2020-05-06T04:41:08-04:00 Allow atomic update of NameCache in readHieFile The situation arises in ghcide where multiple different threads may need to update the name cache, therefore with the older interface it could happen that you start reading a hie file with name cache A and produce name cache A + B, but another thread in the meantime updated the namecache to A + C. Therefore if you write the new namecache you will lose the A' updates from the second thread. Updates haddock submodule - - - - - edec6a6c by Ryan Scott at 2020-05-06T04:41:57-04:00 Make isTauTy detect higher-rank contexts Previously, `isTauTy` would only detect higher-rank `forall`s, not higher-rank contexts, which led to some minor bugs observed in #18127. Easily fixed by adding a case for `(FunTy InvisArg _ _)`. Fixes #18127. - - - - - a95e7fe0 by Ömer Sinan Ağacan at 2020-05-06T04:42:39-04:00 ELF linker: increment curSymbol after filling in fields of current entry The bug was introduced in a8b7cef4d45 which added a field to the `symbols` array elements and then updated this code incorrectly: - oc->symbols[curSymbol++] = nm; + oc->symbols[curSymbol++].name = nm; + oc->symbols[curSymbol].addr = symbol->addr; - - - - - cab1871a by Sylvain Henry at 2020-05-06T04:43:21-04:00 Move LeadingUnderscore into Platform (#17957) Avoid direct use of DynFlags to know if symbols must be prefixed by an underscore. - - - - - 94e7c563 by Sylvain Henry at 2020-05-06T04:43:21-04:00 Don't use DynFlags in showLinkerState (#17957) - - - - - 9afd9251 by Ryan Scott at 2020-05-06T04:43:58-04:00 Refactoring: Use bindSigTyVarsFV in rnMethodBinds `rnMethodBinds` was explicitly using `xoptM` to determine if `ScopedTypeVariables` is enabled before bringing type variables bound by the class/instance header into scope. However, this `xoptM` logic is already performed by the `bindSigTyVarsFV` function. This patch uses `bindSigTyVarsFV` in `rnMethodBinds` to reduce the number of places where we need to consult if `ScopedTypeVariables` is on. This is purely refactoring, and there should be no user-visible change in behavior. - - - - - 6f6d72b2 by Brian Foley at 2020-05-08T15:29:25-04:00 Remove further dead code found by a simple Python script. Avoid removing some functions that are part of an API even though they're not used in-tree at the moment. - - - - - 78bf8bf9 by Julien Debon at 2020-05-08T15:29:28-04:00 Add doc examples for Bifoldable See #17929 - - - - - 66f0a847 by Julien Debon at 2020-05-08T15:29:29-04:00 doc (Bitraversable): Add examples to Bitraversable * Add examples to Data.Bitraversable * Fix formatting for (,) in Bitraversable and Bifoldable * Fix mistake on bimapAccumR documentation See #17929 - - - - - 9749fe12 by Baldur Blöndal at 2020-05-08T15:29:32-04:00 Specify kind variables for inferred kinds in base. - - - - - 4e9aef9e by John Ericson at 2020-05-08T15:29:36-04:00 HsSigWcTypeScoping: Pull in documentation from stray location - - - - - f4d5c6df by John Ericson at 2020-05-08T15:29:36-04:00 Rename local `real_fvs` to `implicit_vs` It doesn't make sense to call the "free" variables we are about to implicitly bind the real ones. - - - - - 20570b4b by John Ericson at 2020-05-08T15:29:36-04:00 A few tiny style nits with renaming - Use case rather than guards that repeatedly scrutenize same thing. - No need for view pattern when `L` is fine. - Use type synnonym to convey the intent like elsewhere. - - - - - 09ac8de5 by John Ericson at 2020-05-08T15:29:36-04:00 Add `forAllOrNothing` function with note - - - - - bb35c0e5 by Joseph C. Sible at 2020-05-08T15:29:40-04:00 Document lawlessness of Ap's Num instance - - - - - cdd229ff by Joseph C. Sible at 2020-05-08T15:29:40-04:00 Apply suggestion to libraries/base/Data/Monoid.hs - - - - - 926d2aab by Joseph C. Sible at 2020-05-08T15:29:40-04:00 Apply more suggestions from Simon Jakobi - - - - - 7a763cff by Adam Gundry at 2020-05-08T15:29:41-04:00 Reject all duplicate declarations involving DuplicateRecordFields (fixes #17965) This fixes a bug that resulted in some programs being accepted that used the same identifier as a field label and another declaration, depending on the order they appeared in the source code. - - - - - 88e3c815 by Simon Peyton Jones at 2020-05-08T15:29:41-04:00 Fix specialisation for DFuns When specialising a DFun we must take care to saturate the unfolding. See Note [Specialising DFuns] in Specialise. Fixes #18120 - - - - - 86c77b36 by Greg Steuck at 2020-05-08T15:29:45-04:00 Remove unused SEGMENT_PROT_RWX It's been unused for a year and is problematic on any OS which requires W^X for security. - - - - - 9d97f4b5 by nineonine at 2020-05-08T15:30:03-04:00 Add test for #16167 - - - - - aa318338 by Ryan Scott at 2020-05-08T15:30:04-04:00 Bump exceptions submodule so that dist-boot is .gitignore'd `exceptions` is a stage-0 boot library as of commit 30272412fa437ab8e7a8035db94a278e10513413, which means that building `exceptions` in a GHC tree will generate a `dist-boot` directory. However, this directory was not specified in `exceptions`' `.gitignore` file, which causes it to dirty up the current `git` working directory. Accordingly, this bumps the `exceptions` submodule to commit ghc/packages/exceptions at 23c0b8a50d7592af37ca09beeec16b93080df98f, which adds `dist-boot` to the `.gitignore` file. - - - - - ea86360f by Ömer Sinan Ağacan at 2020-05-08T15:30:30-04:00 Linker.c: initialize n_symbols of ObjectCode with other fields - - - - - 951c1fb0 by Sylvain Henry at 2020-05-09T21:46:38-04:00 Fix unboxed-sums GC ptr-slot rubbish value (#17791) This patch allows boot libraries to use unboxed sums without implicitly depending on `base` package because of `absentSumFieldError`. See updated Note [aBSENT_SUM_FIELD_ERROR_ID] in GHC.Core.Make - - - - - b352d63c by Ben Gamari at 2020-05-09T21:47:14-04:00 rts: Make non-existent linker search path merely a warning As noted in #18105, previously this resulted in a rather intrusive error message. This is in contrast to the general expectation that search paths are merely places to look, not places that must exist. Fixes #18105. - - - - - cf4f1e2f by Ben Gamari at 2020-05-13T02:02:33-04:00 rts/CNF: Fix fixup comparison function Previously we would implicitly convert the difference between two words to an int, resulting in an integer overflow on 64-bit machines. Fixes #16992 - - - - - a03da9bf by Ömer Sinan Ağacan at 2020-05-13T02:03:16-04:00 Pack some of IdInfo fields into a bit field This reduces residency of compiler quite a bit on some programs. Example stats when building T10370: Before: 2,871,242,832 bytes allocated in the heap 4,693,328,008 bytes copied during GC 33,941,448 bytes maximum residency (276 sample(s)) 375,976 bytes maximum slop 83 MiB total memory in use (0 MB lost due to fragmentation) After: 2,858,897,344 bytes allocated in the heap 4,629,255,440 bytes copied during GC 32,616,624 bytes maximum residency (278 sample(s)) 314,400 bytes maximum slop 80 MiB total memory in use (0 MB lost due to fragmentation) So -3.9% residency, -1.3% bytes copied and -0.4% allocations. Fixes #17497 Metric Decrease: T9233 T9675 - - - - - 670c3e5c by Ben Gamari at 2020-05-13T02:03:54-04:00 get-win32-tarballs: Fix base URL Revert a change previously made for testing purposes. - - - - - 8ad8dc41 by Ben Gamari at 2020-05-13T02:03:54-04:00 get-win32-tarballs: Improve diagnostics output - - - - - 8c0740b7 by Simon Jakobi at 2020-05-13T02:04:33-04:00 docs: Add examples for Data.Semigroup.Arg{Min,Max} Context: #17153 - - - - - cb22348f by Ben Gamari at 2020-05-13T02:05:11-04:00 Add few cleanups of the CAF logic Give the NameSet of non-CAFfy names a proper newtype to distinguish it from all of the other NameSets floating about. - - - - - 90e38b81 by Emeka Nkurumeh at 2020-05-13T02:05:51-04:00 fix printf warning when using with ghc with clang on mingw - - - - - 86d8ac22 by Sebastian Graf at 2020-05-13T02:06:29-04:00 CprAnal: Don't attach CPR sigs to expandable bindings (#18154) Instead, look through expandable unfoldings in `cprTransform`. See the new Note [CPR for expandable unfoldings]: ``` Long static data structures (whether top-level or not) like xs = x1 : xs1 xs1 = x2 : xs2 xs2 = x3 : xs3 should not get CPR signatures, because they * Never get WW'd, so their CPR signature should be irrelevant after analysis (in fact the signature might even be harmful for that reason) * Would need to be inlined/expanded to see their constructed product * Recording CPR on them blows up interface file sizes and is redundant with their unfolding. In case of Nested CPR, this blow-up can be quadratic! But we can't just stop giving DataCon application bindings the CPR property, for example fac 0 = 1 fac n = n * fac (n-1) fac certainly has the CPR property and should be WW'd! But FloatOut will transform the first clause to lvl = 1 fac 0 = lvl If lvl doesn't have the CPR property, fac won't either. But lvl doesn't have a CPR signature to extrapolate into a CPR transformer ('cprTransform'). So instead we keep on cprAnal'ing through *expandable* unfoldings for these arity 0 bindings via 'cprExpandUnfolding_maybe'. In practice, GHC generates a lot of (nested) TyCon and KindRep bindings, one for each data declaration. It's wasteful to attach CPR signatures to each of them (and intractable in case of Nested CPR). ``` Fixes #18154. - - - - - e34bf656 by Ben Gamari at 2020-05-13T02:07:08-04:00 users-guide: Add discussion of shared object naming Fixes #18074. - - - - - 5d0f2445 by Ben Gamari at 2020-05-13T02:07:47-04:00 testsuite: Print sign of performance changes Executes the minor formatting change in the tabulated performance changes suggested in #18135. - - - - - 9e4b981f by Ben Gamari at 2020-05-13T02:08:24-04:00 testsuite: Add testcase for #18129 - - - - - 266310c3 by Ivan-Yudin at 2020-05-13T02:09:03-04:00 doc: Reformulate the opening paragraph of Ch. 4 in User's guide Removes mentioning of Hugs (it is not helpful for new users anymore). Changes the wording for the rest of the paragraph. Fixes #18132. - - - - - 55e35c0b by Baldur Blöndal at 2020-05-13T20:02:48-04:00 Predicate, Equivalence derive via `.. -> a -> All' - - - - - d7e0b57f by Alp Mestanogullari at 2020-05-13T20:03:30-04:00 hadrian: add a --freeze2 option to freeze stage 1 and 2 - - - - - d880d6b2 by Artem Pelenitsyn at 2020-05-13T20:04:11-04:00 Don't reload environment files on every setSessionDynFlags Makes `interpretPackageEnv` (which loads envirinment files) a part of `parseDynamicFlags` (parsing command-line arguments, which is typically done once) instead of `setSessionDynFlags` (which is typically called several times). Making several (transitive) calls to `interpretPackageEnv`, as before, caused #18125 #16318, which should be fixed now. - - - - - 102cfd67 by Ryan Scott at 2020-05-13T20:04:46-04:00 Factor out HsPatSigType for pat sigs/RULE term sigs (#16762) This implements chunks (2) and (3) of https://gitlab.haskell.org/ghc/ghc/issues/16762#note_270170. Namely, it introduces a dedicated `HsPatSigType` AST type, which represents the types that can appear in pattern signatures and term-level `RULE` binders. Previously, these were represented with `LHsSigWcType`. Although `LHsSigWcType` is isomorphic to `HsPatSigType`, the intended semantics of the two types are slightly different, as evidenced by the fact that they have different code paths in the renamer and typechecker. See also the new `Note [Pattern signature binders and scoping]` in `GHC.Hs.Types`. - - - - - b17574f7 by Hécate at 2020-05-13T20:05:28-04:00 fix(documentation): Fix the RST links to GHC.Prim - - - - - df021fb1 by Baldur Blöndal at 2020-05-13T20:06:06-04:00 Document (->) using inferred quantification for its runtime representations. Fixes #18142. - - - - - 1a93ea57 by Takenobu Tani at 2020-05-13T20:06:54-04:00 Tweak man page for ghc command This commit updates the ghc command's man page as followings: * Enable `man_show_urls` to show URL addresses in the `DESCRIPTION` section of ghc.rst, because sphinx currently removes hyperlinks for man pages. * Add a `SEE ALSO` section to point to the GHC homepage - - - - - a951e1ba by Takenobu Tani at 2020-05-13T20:07:37-04:00 GHCi: Add link to the user's guide in help message This commit adds a link to the user's guide in ghci's `:help` message. Newcomers could easily reach to details of ghci. - - - - - 404581ea by Jeff Happily at 2020-05-13T20:08:15-04:00 Handle single unused import - - - - - 1c999e5d by Ben Gamari at 2020-05-13T20:09:07-04:00 Ensure that printMinimalImports closes handle Fixes #18166. - - - - - c9f5a8f4 by Ben Gamari at 2020-05-13T20:09:51-04:00 hadrian: Tell testsuite driver about LLVM availability This reflects the logic present in the Make build system into Hadrian. Fixes #18167. - - - - - c05c0659 by Simon Jakobi at 2020-05-14T03:31:21-04:00 Improve some folds over Uniq[D]FM * Replace some non-deterministic lazy folds with strict folds. * Replace some O(n log n) folds in deterministic order with O(n) non-deterministic folds. * Replace some folds with set-operations on the underlying IntMaps. This reduces max residency when compiling `nofib/spectral/simple/Main.hs` with -O0 by about 1%. Maximum residency when compiling Cabal also seems reduced on the order of 3-9%. - - - - - 477f13bb by Simon Jakobi at 2020-05-14T03:31:58-04:00 Use Data.IntMap.disjoint Data.IntMap gained a dedicated `disjoint` function in containers-0.6.2.1. This patch applies this function where appropriate in hopes of modest compiler performance improvements. Closes #16806. - - - - - e9c0110c by Ben Gamari at 2020-05-14T12:25:53-04:00 IdInfo: Add reference to bitfield-packing ticket - - - - - 9bd20e83 by Sebastian Graf at 2020-05-15T10:42:09-04:00 DmdAnal: Improve handling of precise exceptions This patch does two things: Fix possible unsoundness in what was called the "IO hack" and implement part 2.1 of the "fixing precise exceptions" plan in https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions, which, in combination with !2956, supersedes !3014 and !2525. **IO hack** The "IO hack" (which is a fallback to preserve precise exceptions semantics and thus soundness, rather than some smart thing that increases precision) is called `exprMayThrowPreciseException` now. I came up with two testcases exemplifying possible unsoundness (if twisted enough) in the old approach: - `T13380d`: Demonstrating unsoundness of the "IO hack" when resorting to manual state token threading and direct use of primops. More details below. - `T13380e`: Demonstrating unsoundness of the "IO hack" when we have Nested CPR. Not currently relevant, as we don't have Nested CPR yet. - `T13380f`: Demonstrating unsoundness of the "IO hack" for safe FFI calls. Basically, the IO hack assumed that precise exceptions can only be thrown from a case scrutinee of type `(# State# RealWorld, _ #)`. I couldn't come up with a program using the `IO` abstraction that violates this assumption. But it's easy to do so via manual state token threading and direct use of primops, see `T13380d`. Also similar code might be generated by Nested CPR in the (hopefully not too) distant future, see `T13380e`. Hence, we now have a more careful test in `forcesRealWorld` that passes `T13380{d,e}` (and will hopefully be robust to Nested CPR). **Precise exceptions** In #13380 and #17676 we saw that we didn't preserve precise exception semantics in demand analysis. We fixed that with minimal changes in !2956, but that was terribly unprincipled. That unprincipledness resulted in a loss of precision, which is tracked by these new test cases: - `T13380b`: Regression in dead code elimination, because !2956 was too syntactic about `raiseIO#` - `T13380c`: No need to apply the "IO hack" when the IO action may not throw a precise exception (and the existing IO hack doesn't detect that) Fixing both issues in !3014 turned out to be too complicated and had the potential to regress in the future. Hence we decided to only fix `T13380b` and augment the `Divergence` lattice with a new middle-layer element, `ExnOrDiv`, which means either `Diverges` (, throws an imprecise exception) or throws a *precise* exception. See the wiki page on Step 2.1 for more implementational details: https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions#dead-code-elimination-for-raiseio-with-isdeadenddiv-introducing-exnordiv-step-21 - - - - - 568d7279 by Ben Gamari at 2020-05-15T10:42:46-04:00 GHC.Cmm.Opt: Handle MO_XX_Conv This MachOp was introduced by 2c959a1894311e59cd2fd469c1967491c1e488f3 but a wildcard match in cmmMachOpFoldM hid the fact that it wasn't handled. Ideally we would eliminate the match but this appears to be a larger task. Fixes #18141. - - - - - 5bcf8606 by Ryan Scott at 2020-05-17T08:46:38-04:00 Remove duplicate Note [When to print foralls] in GHC.Core.TyCo.Ppr There are two different Notes named `[When to print foralls]`. The most up-to-date one is in `GHC.Iface.Type`, but there is a second one in `GHC.Core.TyCo.Ppr`. The latter is less up-to-date, as it was written before GHC switched over to using ifaces to pretty-print types. I decided to just remove the latter and replace it with a reference to the former. [ci skip] - - - - - 55f0e783 by Fumiaki Kinoshita at 2020-05-21T12:10:44-04:00 base: Add Generic instances to various datatypes under GHC.* * GHC.Fingerprint.Types: Fingerprint * GHC.RTS.Flags: GiveGCStats, GCFlags, ConcFlags, DebugFlags, CCFlags, DoHeapProfile, ProfFlags, DoTrace, TraceFlags, TickyFlags, ParFlags and RTSFlags * GHC.Stats: RTSStats and GCStats * GHC.ByteOrder: ByteOrder * GHC.Unicode: GeneralCategory * GHC.Stack.Types: SrcLoc Metric Increase: haddock.base - - - - - a9311cd5 by Gert-Jan Bottu at 2020-05-21T12:11:31-04:00 Explicit Specificity Implementation for Ticket #16393. Explicit specificity allows users to manually create inferred type variables, by marking them with braces. This way, the user determines which variables can be instantiated through visible type application. The additional syntax is included in the parser, allowing users to write braces in type variable binders (type signatures, data constructors etc). This information is passed along through the renamer and verified in the type checker. The AST for type variable binders, data constructors, pattern synonyms, partial signatures and Template Haskell has been updated to include the specificity of type variables. Minor notes: - Bumps haddock submodule - Disables pattern match checking in GHC.Iface.Type with GHC 8.8 - - - - - 24e61aad by Ben Price at 2020-05-21T12:12:17-04:00 Lint should say when it is checking a rule It is rather confusing that when lint finds an error in a rule attached to a binder, it reports the error as in the RHS, not the rule: ... In the RHS of foo We add a clarifying line: ... In the RHS of foo In a rule attached to foo The implication that the rule lives inside the RHS is a bit odd, but this niggle is already present for unfoldings, whose pattern we are following. - - - - - 78c6523c by Ben Gamari at 2020-05-21T12:13:01-04:00 nonmoving: Optimise the write barrier - - - - - 13f6c9d0 by Andreas Klebinger at 2020-05-21T12:13:45-04:00 Refactor linear reg alloc to remember past assignments. When assigning registers we now first try registers we assigned to in the past, instead of picking the "first" one. This is in extremely helpful when dealing with loops for which variables are dead for part of the loop. This is important for patterns like this: foo = arg1 loop: use(foo) ... foo = getVal() goto loop; There we: * assign foo to the register of arg1. * use foo, it's dead after this use as it's overwritten after. * do other things. * look for a register to put foo in. If we pick an arbitrary one it might differ from the register the start of the loop expect's foo to be in. To fix this we simply look for past register assignments for the given variable. If we find one and the register is free we use that register. This reduces the need for fixup blocks which match the register assignment between blocks. In the example above between the end and the head of the loop. This patch also moves branch weight estimation ahead of register allocation and adds a flag to control it (cmm-static-pred). * It means the linear allocator is more likely to assign the hotter code paths first. * If it assign these first we are: + Less likely to spill on the hot path. + Less likely to introduce fixup blocks on the hot path. These two measure combined are surprisingly effective. Based on nofib we get in the mean: * -0.9% instructions executed * -0.1% reads/writes * -0.2% code size. * -0.1% compiler allocations. * -0.9% compile time. * -0.8% runtime. Most of the benefits are simply a result of removing redundant moves and spills. Reduced compiler allocations likely are the result of less code being generated. (The added lookup is mostly non-allocating). - - - - - edc2cc58 by Andreas Klebinger at 2020-05-21T12:14:25-04:00 NCG: Codelayout: Distinguish conditional and other branches. In #18053 we ended up with a suboptimal code layout because the code layout algorithm didn't distinguish between conditional and unconditional control flow. We can completely eliminate unconditional control flow instructions by placing blocks next to each other, not so much for conditionals. In terms of implementation we simply give conditional branches less weight before computing the layout. Fixes #18053 - - - - - b7a6b2f4 by Gleb Popov at 2020-05-21T12:15:26-04:00 gitlab-ci: Set locale to C.UTF-8. - - - - - a8c27cf6 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Allow spaces in GHCi :script file names This patch updates the user interface of GHCi so that file names passed to the ':script' command may contain spaces escaped with a backslash. For example: :script foo\ bar.script The implementation uses a modified version of 'words' that does not break on escaped spaces. Fixes #18027. - - - - - 82663959 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Add extra tests for GHCi :script syntax checks The syntax for GHCi's ":script" command allows for only a single file name to be passed as an argument. This patch adds a test for the cases in which a file name is missing or multiple file names are passed. Related to #T18027. - - - - - a0b79e1b by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Allow GHCi :script file names in double quotes This patch updates the user interface of GHCi so that file names passed to the ':script' command can be wrapped in double quotes. For example: :script "foo bar.script" The implementation uses a modified version of 'words' that treats character sequences enclosed in double quotes as single words. Fixes #18027. - - - - - cf566330 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Update documentation for GHCi :script This patch adds the fixes that allow for file names containing spaces to be passed to GHCi's ':script' command to the release notes for 8.12 and expands the user-guide documentation for ':script' by mentioning how such file names can be passed. Related to #18027. - - - - - 0004ccb8 by Tuan Le at 2020-05-21T12:16:46-04:00 llvmGen: Consider Relocatable read-only data as not constantReferences: #18137 - - - - - 964d3ea2 by John Ericson at 2020-05-21T12:17:30-04:00 Use `Checker` for `tc_pat` - - - - - b797aa42 by John Ericson at 2020-05-21T12:17:30-04:00 Use `Checker` for `tc_lpat` and `tc_lpats` - - - - - 5108e84a by John Ericson at 2020-05-21T12:17:30-04:00 More judiciously panic in `ts_pat` - - - - - 510e0451 by John Ericson at 2020-05-21T12:17:30-04:00 Put `PatEnv` first in `GHC.Tc.Gen.Pat.Checker` - - - - - cb4231db by John Ericson at 2020-05-21T12:17:30-04:00 Tiny cleaup eta-reduce away a function argument In GHC, not in the code being compiled! - - - - - 6890c38d by John Ericson at 2020-05-21T12:17:30-04:00 Use braces with do in `SplicePat` case for consistency - - - - - 3451584f by buggymcbugfix at 2020-05-21T12:18:06-04:00 Fix spelling mistakes and typos - - - - - b552e531 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Add INLINABLE pragmas to Enum list producers The INLINABLE pragmas ensure that we export stable (unoptimised) unfoldings in the interface file so we can do list fusion at usage sites. Related tickets: #15185, #8763, #18178. - - - - - e7480063 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Piggyback on Enum Word methods for Word64 If we are on a 64 bit platform, we can use the efficient Enum Word methods for the Enum Word64 instance. - - - - - 892b0c41 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Document INLINE(ABLE) pragmas that enable fusion - - - - - 2b363ebb by Richard Eisenberg at 2020-05-21T12:18:45-04:00 MR template should ask for key part - - - - - a95bbd0b by Sebastian Graf at 2020-05-21T12:19:37-04:00 Make `Int`'s `mod` and `rem` strict in their first arguments They used to be strict until 4d2ac2d (9 years ago). It's obviously better to be strict for performance reasons. It also blocks #18067. NoFib results: ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- integer -1.1% +0.4% wheel-sieve2 +21.2% +20.7% -------------------------------------------------------------------------------- Min -1.1% -0.0% Max +21.2% +20.7% Geometric Mean +0.2% +0.2% ``` The regression in `wheel-sieve2` is due to reboxing that likely will go away with the resolution of #18067. See !3282 for details. Fixes #18187. - - - - - d3d055b8 by Galen Huntington at 2020-05-21T12:20:18-04:00 Clarify pitfalls of NegativeLiterals; see #18022. - - - - - 1b508a9e by Alexey Kuleshevich at 2020-05-21T12:21:02-04:00 Fix wording in primops documentation to reflect the correct reasoning: * Besides resizing functions, shrinking ones also mutate the size of a mutable array and because of those two `sizeofMutabeByteArray` and `sizeofSmallMutableArray` are now deprecated * Change reference in documentation to the newer functions `getSizeof*` instead of `sizeof*` for shrinking functions * Fix incorrect mention of "byte" instead of "small" - - - - - 4ca0c8a1 by Andreas Klebinger at 2020-05-21T12:21:53-04:00 Don't variable-length encode magic iface constant. We changed to use variable length encodings for many types by default, including Word32. This makes sense for numbers but not when Word32 is meant to represent four bytes. I added a FixedLengthEncoding newtype to Binary who's instances interpret their argument as a collection of bytes instead of a number. We then use this when writing/reading magic numbers to the iface file. I also took the libery to remove the dummy iface field. This fixes #18180. - - - - - a1275081 by Krzysztof Gogolewski at 2020-05-21T12:22:35-04:00 Add a regression test for #11506 The testcase works now. See explanation in https://gitlab.haskell.org/ghc/ghc/issues/11506#note_273202 - - - - - 8a816e5f by Krzysztof Gogolewski at 2020-05-21T12:23:55-04:00 Sort deterministically metric output Previously, we sorted according to the test name and way, but the metrics (max_bytes_used/peak_megabytes_allocated etc.) were appearing in nondeterministic order. - - - - - 566cc73f by Sylvain Henry at 2020-05-21T12:24:45-04:00 Move isDynLinkName into GHC.Types.Name It doesn't belong into GHC.Unit.State - - - - - d830bbc9 by Adam Sandberg Ericsson at 2020-05-23T13:36:20-04:00 docs: fix formatting and add some links [skip ci] - - - - - 49301ad6 by Andrew Martin at 2020-05-23T13:37:01-04:00 Implement cstringLength# and FinalPtr This function and its accompanying rule resolve issue #5218. A future PR to the bytestring library will make the internal Data.ByteString.Internal.unsafePackAddress compute string length with cstringLength#. This will improve the status quo because it is eligible for constant folding. Additionally, introduce a new data constructor to ForeignPtrContents named FinalPtr. This additional data constructor, when used in the IsString instance for ByteString, leads to more Core-to-Core optimization opportunities, fewer runtime allocations, and smaller binaries. Also, this commit re-exports all the functions from GHC.CString (including cstringLength#) in GHC.Exts. It also adds a new test driver. This test driver is used to perform substring matches on Core that is dumped after all the simplifier passes. In this commit, it is used to check that constant folding of cstringLength# works. - - - - - dcd6bdcc by Ben Gamari at 2020-05-23T13:37:48-04:00 simplCore: Ignore ticks in rule templates This fixes #17619, where a tick snuck in to the template of a rule, resulting in a panic during rule matching. The tick in question was introduced via post-inlining, as discussed in `Note [Simplifying rules]`. The solution we decided upon was to simply ignore ticks in the rule template, as discussed in `Note [Tick annotations in RULE matching]`. Fixes #18162. Fixes #17619. - - - - - 82cb8913 by John Ericson at 2020-05-23T13:38:32-04:00 Fix #18145 and also avoid needless work with implicit vars - `forAllOrNothing` now is monadic, so we can trace whether we bind an explicit `forall` or not. - #18145 arose because the free vars calculation was needlessly complex. It is now greatly simplified. - Replaced some other implicit var code with `filterFreeVarsToBind`. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - a60dc835 by Ben Gamari at 2020-05-23T13:39:12-04:00 Bump process submodule Fixes #17926. - - - - - 856adf54 by Ben Gamari at 2020-05-23T13:40:21-04:00 users-guide: Clarify meaning of -haddock flag Fixes #18206. - - - - - 7ae57afd by Ben Gamari at 2020-05-23T13:41:03-04:00 git: Add ignored commits file This can be used to tell git to ignore bulk renaming commits like the recently-finished module hierarchy refactoring. Configured with, git config blame.ignoreRevsFile .git-ignore-revs - - - - - 63d30e60 by jneira at 2020-05-24T01:54:42-04:00 Add hie-bios script for windows systems It is a direct translation of the sh script - - - - - 59182b88 by jneira at 2020-05-24T01:54:42-04:00 Honour previous values for CABAL and CABFLAGS The immediate goal is let the hie-bios.bat script set CABFLAGS with `-v0` and remove all cabal output except the compiler arguments - - - - - 932dc54e by jneira at 2020-05-24T01:54:42-04:00 Add specific configuration for windows in hie.yaml - - - - - e0eda070 by jneira at 2020-05-24T01:54:42-04:00 Remove not needed hie-bios output - - - - - a0ea59d6 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Move Config module into GHC.Settings - - - - - 37430251 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Rename GHC.Core.Arity into GHC.Core.Opt.Arity - - - - - a426abb9 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Rename GHC.Hs.Types into GHC.Hs.Type See discussion in https://gitlab.haskell.org/ghc/ghc/issues/13009#note_268610 - - - - - 1c91a7a0 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Bump haddock submodule - - - - - 66bd24d1 by Ryan Scott at 2020-05-24T01:56:03-04:00 Add orderingTyCon to wiredInTyCons (#18185) `Ordering` needs to be wired in for use in the built-in `CmpNat` and `CmpSymbol` type families, but somehow it was never added to the list of `wiredInTyCons`, leading to the various oddities observed in #18185. Easily fixed by moving `orderingTyCon` from `basicKnownKeyNames` to `wiredInTyCons`. Fixes #18185. - - - - - 01c43634 by Matthew Pickering at 2020-05-24T01:56:42-04:00 Remove unused hs-boot file - - - - - 7a07aa71 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix cross-compiler build (#16051) - - - - - 15ccca16 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix distDir per stage - - - - - b420fb24 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix hp2ps error during cross-compilation Fixed by @alp (see https://gitlab.haskell.org/ghc/ghc/issues/16051#note_274265) - - - - - cd339ef0 by Joshua Price at 2020-05-24T15:22:56-04:00 Make Unicode brackets opening/closing tokens (#18225) The tokens `[|`, `|]`, `(|`, and `|)` are opening/closing tokens as described in GHC Proposal #229. This commit makes the unicode variants (`⟦`, `⟧`, `⦇`, and `⦈`) act the same as their ASCII counterparts. - - - - - 013d7120 by Ben Gamari at 2020-05-25T09:48:17-04:00 Revert "Specify kind variables for inferred kinds in base." As noted in !3132, this has rather severe knock-on consequences in user-code. We'll need to revisit this before merging something along these lines. This reverts commit 9749fe1223d182b1f8e7e4f7378df661c509f396. - - - - - 4c4312ed by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Drop redundant ad-hoc boot module check To determine whether the module is a boot module Coverage.addTicksToBinds was checking for a `boot` suffix in the module source filename. This is quite ad-hoc and shouldn't be necessary; the callsite in `deSugar` already checks that the module isn't a boot module. - - - - - 1abf3c84 by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Make tickBoxCount strict This could otherwise easily cause a leak of (+) thunks. - - - - - b2813750 by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Make ccIndices strict This just seems like a good idea. - - - - - 02e278eb by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Don't produce ModBreaks if not HscInterpreted emptyModBreaks contains a bottom and consequently it's important that we don't use it unless necessary. - - - - - b8c014ce by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Factor out addMixEntry - - - - - 53814a64 by Zubin Duggal at 2020-05-26T03:03:24-04:00 Add info about typeclass evidence to .hie files See `testsuite/tests/hiefile/should_run/HieQueries.hs` and `testsuite/tests/hiefile/should_run/HieQueries.stdout` for an example of this We add two new fields, `EvidenceVarBind` and `EvidenceVarUse` to the `ContextInfo` associated with an Identifier. These are associated with the appropriate identifiers for the evidence variables collected when we come across `HsWrappers`, `TcEvBinds` and `IPBinds` while traversing the AST. Instance dictionary and superclass selector dictionaries from `tcg_insts` and classes defined in `tcg_tcs` are also recorded in the AST as originating from their definition span This allows us to save a complete picture of the evidence constructed by the constraint solver, and will let us report this to the user, enabling features like going to the instance definition from the invocation of a class method(or any other method taking a constraint) and finding all usages of a particular instance. Additionally, - Mark NodeInfo with an origin so we can differentiate between bindings origininating in the source vs those in ghc - Along with typeclass evidence info, also include information on Implicit Parameters - Add a few utility functions to HieUtils in order to query the new info Updates haddock submodule - - - - - 6604906c by Sebastian Graf at 2020-05-26T03:04:04-04:00 Make WorkWrap.Lib.isWorkerSmallEnough aware of the old arity We should allow a wrapper with up to 82 parameters when the original function had 82 parameters to begin with. I verified that this made no difference on NoFib, but then again it doesn't use huge records... Fixes #18122. - - - - - cf772f19 by Sylvain Henry at 2020-05-26T03:04:45-04:00 Enhance Note [About units] for Backpack - - - - - ede24126 by Takenobu Tani at 2020-05-27T00:13:55-04:00 core-spec: Modify file paths according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * GHC/Core.hs <= coreSyn/CoreSyn.hs * GHC/Core/Coercion.hs <= types/Coercion.hs * GHC/Core/Coercion/Axiom.hs <= types/CoAxiom.hs * GHC/Core/Coercion/Opt.hs <= types/OptCoercion.hs * GHC/Core/DataCon.hs <= basicTypes/DataCon.hs * GHC/Core/FamInstEnv.hs <= types/FamInstEnv.hs * GHC/Core/Lint.hs <= coreSyn/CoreLint.hs * GHC/Core/Subst.hs <= coreSyn/CoreSubst.hs * GHC/Core/TyCo/Rep.hs <= types/TyCoRep.hs * GHC/Core/TyCon.hs <= types/TyCon.hs * GHC/Core/Type.hs <= types/Type.hs * GHC/Core/Unify.hs <= types/Unify.hs * GHC/Types/Literal.hs <= basicTypes/Literal.hs * GHC/Types/Var.hs <= basicTypes/Var.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [skip ci] - - - - - 04750304 by Ben Gamari at 2020-05-27T00:14:33-04:00 eventlog: Fix racy flushing Previously no attempt was made to avoid multiple threads writing their capability-local eventlog buffers to the eventlog writer simultaneously. This could result in multiple eventlog streams being interleaved. Fix this by documenting that the EventLogWriter's write() and flush() functions may be called reentrantly and fix the default writer to protect its FILE* by a mutex. Fixes #18210. - - - - - d6203f24 by Joshua Price at 2020-05-27T00:15:17-04:00 Make `identifier` parse unparenthesized `->` (#18060) - - - - - 28deee28 by Ben Gamari at 2020-05-28T16:23:21-04:00 GHC.Core.Unfold: Refactor traceInline This reduces duplication as well as fixes a bug wherein -dinlining-check would override -ddump-inlinings. Moreover, the new variant - - - - - 1f393e1e by Ben Gamari at 2020-05-28T16:23:21-04:00 Avoid unnecessary allocations due to tracing utilities While ticky-profiling the typechecker I noticed that hundreds of millions of SDocs are being allocated just in case -ddump-*-trace is enabled. This is awful. We avoid this by ensuring that the dump flag check is inlined into the call site, ensuring that the tracing document needn't be allocated unless it's actually needed. See Note [INLINE conditional tracing utilities] for details. Fixes #18168. Metric Decrease: T9961 haddock.Cabal haddock.base haddock.compiler - - - - - 5f621a78 by Vladislav Zavialov at 2020-05-28T16:23:58-04:00 Add Semigroup/Monoid for Q (#18123) - - - - - dc5f004c by Xavier Denis at 2020-05-28T16:24:37-04:00 Fix #18071 Run the core linter on candidate instances to ensure they are well-kinded. Better handle quantified constraints by using a CtWanted to avoid having unsolved constraints thrown away at the end by the solver. - - - - - 10e6982c by Sebastian Graf at 2020-05-28T16:25:14-04:00 FloatOut: Only eta-expand dead-end RHS if arity will increase (#18231) Otherwise we risk turning trivial RHS into non-trivial RHS, introducing unnecessary bindings in the next Simplifier run, resulting in more churn. Fixes #18231. - - - - - 08dab5f7 by Sebastian Graf at 2020-05-28T16:25:14-04:00 DmdAnal: Recognise precise exceptions from case alternatives (#18086) Consider ```hs m :: IO () m = do putStrLn "foo" error "bar" ``` `m` (from #18086) always throws a (precise or imprecise) exception or diverges. Yet demand analysis infers `<L,A>` as demand signature instead of `<L,A>x` for it. That's because the demand analyser sees `putStrLn` occuring in a case scrutinee and decides that it has to `deferAfterPreciseException`, because `putStrLn` throws a precise exception on some control flow paths. This will mask the `botDiv` `Divergence`of the single case alt containing `error` to `topDiv`. Since `putStrLn` has `topDiv` itself, the final `Divergence` is `topDiv`. This is easily fixed: `deferAfterPreciseException` works by `lub`ing with the demand type of a virtual case branch denoting the precise exceptional control flow. We used `nopDmdType` before, but we can be more precise and use `exnDmdType`, which is `nopDmdType` with `exnDiv`. Now the `Divergence` from the case alt will degrade `botDiv` to `exnDiv` instead of `topDiv`, which combines with the result from the scrutinee to `exnDiv`, and all is well. Fixes #18086. - - - - - aef95f11 by Ben Gamari at 2020-05-28T16:25:53-04:00 Ticky-ticky: Record DataCon name in ticker name This makes it significantly easier to spot the nature of allocations regressions and comes at a reasonably low cost. - - - - - 8f021b8c by Ben Gamari at 2020-05-28T16:26:34-04:00 hadrian: Don't track GHC's verbosity argument Teach hadrian to ignore GHC's -v argument in its recompilation check, thus fixing #18131. - - - - - 13d9380b by Ben Gamari at 2020-05-28T16:27:20-04:00 Rip out CmmStackInfo(updfr_space) As noted in #18232, this field is currently completely unused and moreover doesn't have a clear meaning. - - - - - f10d11fa by Andreas Klebinger at 2020-05-29T01:38:42-04:00 Fix "build/elem" RULE. An redundant constraint prevented the rule from matching. Fixing this allows a call to elem on a known list to be translated into a series of equality checks, and eventually a simple case expression. Surprisingly this seems to regress elem for strings. To avoid this we now also allow foldrCString to inline and add an UTF8 variant. This results in elem being compiled to a tight non-allocating loop over the primitive string literal which performs a linear search. In the process this commit adds UTF8 variants for some of the functions in GHC.CString. This is required to make this work for both ASCII and UTF8 strings. There are also small tweaks to the CString related rules. We now allow ourselfes the luxury to compare the folding function via eqExpr, which helps to ensure the rule fires before we inline foldrCString*. Together with a few changes to allow matching on both the UTF8 and ASCII variants of the CString functions. - - - - - bbeb2389 by Ben Gamari at 2020-05-29T01:39:19-04:00 CoreToStg: Add Outputable ArgInfo instance - - - - - 0e3361ca by Simon Peyton Jones at 2020-05-29T01:39:19-04:00 Make Lint check return type of a join point Consider join x = rhs in body It's important that the type of 'rhs' is the same as the type of 'body', but Lint wasn't checking that invariant. Now it does! This was exposed by investigation into !3113. - - - - - c49f7df0 by Simon Peyton Jones at 2020-05-29T01:39:19-04:00 Do not float join points in exprIsConApp_maybe We hvae been making exprIsConApp_maybe cleverer in recent times: commit b78cc64e923716ac0512c299f42d4d0012306c05 Date: Thu Nov 15 17:14:31 2018 +0100 Make constructor wrappers inline only during the final phase commit 7833cf407d1f608bebb1d38bb99d3035d8d735e6 Date: Thu Jan 24 17:58:50 2019 +0100 Look through newtype wrappers (Trac #16254) commit c25b135ff5b9c69a90df0ccf51b04952c2dc6ee1 Date: Thu Feb 21 12:03:22 2019 +0000 Fix exprIsConApp_maybe But alas there was still a bug, now immortalised in Note [Don't float join points] in SimpleOpt. It's quite hard to trigger because it requires a dead join point, but it came up when compiling Cabal Cabal.Distribution.Fields.Lexer.hs, when working on !3113. Happily, the fix is extremly easy. Finding the bug was not so easy. - - - - - 46720997 by Ben Gamari at 2020-05-29T01:39:19-04:00 Allow simplification through runRW# Because runRW# inlines so late, we were previously able to do very little simplification across it. For instance, given even a simple program like case runRW# (\s -> let n = I# 42# in n) of I# n# -> f n# we previously had no way to avoid the allocation of the I#. This patch allows the simplifier to push strict contexts into the continuation of a runRW# application, as explained in in Note [Simplification of runRW#] in GHC.CoreToStg.Prep. Fixes #15127. Metric Increase: T9961 Metric Decrease: ManyConstructors Co-Authored-By: Simon Peyton-Jone <simonpj at microsoft.com> - - - - - 277c2f26 by Ben Gamari at 2020-05-29T01:39:55-04:00 Eta expand un-saturated primops Now since we no longer try to predict CAFfyness we have no need for the solution to #16846. Eta expanding unsaturated primop applications is conceptually simpler, especially in the presence of levity polymorphism. This essentially reverts cac8dc9f51e31e4c0a6cd9bc302f7e1bc7c03beb, as suggested in #18079. Closes #18079. - - - - - f44d7ae0 by Simon Jakobi at 2020-05-29T01:40:34-04:00 base: Scrap deprecation plan for Data.Monoid.{First,Last} See the discussion on the libraries mailing list for context: https://mail.haskell.org/pipermail/libraries/2020-April/030357.html - - - - - 8b494895 by Jeremy Schlatter at 2020-05-29T01:41:12-04:00 Fix typo in documentation - - - - - 998450f4 by Gleb Popov at 2020-05-29T01:41:53-04:00 Always define USE_PTHREAD_FOR_ITIMER for FreeBSD. - - - - - f9a513e0 by Alp Mestanogullari at 2020-05-29T01:42:36-04:00 hadrian: introduce 'install' target Its logic is very simple. It `need`s the `binary-dist-dir` target and runs suitable `configure` and `make install` commands for the user. A new `--prefix` command line argument is introduced to specify where GHC should be installed. - - - - - 67738db1 by Travis Whitaker at 2020-05-29T13:34:48-04:00 Build a threaded stage 1 if the bootstrapping GHC supports it. - - - - - aac19e6c by Peter Trommler at 2020-05-29T13:35:24-04:00 PPC NCG: No per-symbol .section ".toc" directives All position independent symbols are collected during code generation and emitted in one go. Prepending each symbol with a .section ".toc" directive is redundant. This patch drops the per-symbol directives leading to smaller assembler files. Fixes #18250 - - - - - 4413828b by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Teach getNumProcessors to return available processors Previously we would report the number of physical processors, which can be quite wrong in a containerized setting. Now we rather return how many processors are in our affinity mask when possible. I also refactored the code to prefer platform-specific since this will report logical CPUs instead of physical (using `machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD). Fixes #14781. - - - - - 1449435c by Ben Gamari at 2020-05-30T06:07:31-04:00 users-guide: Note change in getNumProcessors in users guide - - - - - 3d960169 by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Drop compatibility shims for Windows Vista We can now assume that the thread and processor group interfaces are available. - - - - - 7f8f948c by Peter Trommler at 2020-05-30T06:08:07-04:00 PPC NCG: Fix .size directive on powerpc64 ELF v1 Thanks to Sergei Trofimovich for pointing out the issue. Fixes #18237 - - - - - 7c555b05 by Andreas Klebinger at 2020-05-30T06:08:43-04:00 Optimize GHC.Utils.Monad. Many functions in this module are recursive and as such are marked loop breakers. Which means they are unlikely to get an unfolding. This is *bad*. We always want to specialize them to specific Monads. Which requires a visible unfolding at the use site. I rewrote the recursive ones from: foo f x = ... foo x' ... to foo f x = go x where go x = ... As well as giving some pragmas to make all of them available for specialization. The end result is a reduction of allocations of about -1.4% for nofib/spectral/simple/Main.hs when compiled with `-O`. ------------------------- Metric Decrease: T12425 T14683 T5631 T9233 T9675 T9961 WWRec ------------------------- - - - - - 8b1cb5df by Ben Gamari at 2020-05-30T06:09:20-04:00 Windows: Bump Windows toolchain to 0.2 - - - - - 6947231a by Zubin Duggal at 2020-05-30T06:10:02-04:00 Simplify contexts in GHC.Iface.Ext.Ast - - - - - 2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00 Cleanup OVERWRITING_CLOSURE logic The code is just more confusing than it needs to be. We don't need to mix the threaded check with the ldv profiling check since ldv's init already checks for this. Hence they can be two separate checks. Taking the sanity checking into account is also cleaner via DebugFlags.sanity. No need for checking the DEBUG define. The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the old code had also make things a lot more opaque IMO so I removed those. - - - - - 6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00 Fix OVERWRITING_CLOSURE assuming closures are not inherently used The new ASSERT in LDV_recordDead() was being tripped up by MVars when removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via OVERWRITE_INFO(). - - - - - 38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00 Always zero shrunk mutable array slop when profiling When shrinking arrays in the profiling way we currently don't always zero the leftover slop. This means we can't traverse such closures in the heap profiler. The old Note [zeroing slop] and #8402 have some rationale for why this is so but I belive the reasoning doesn't apply to mutable closures. There users already have to ensure multiple threads don't step on each other's toes so zeroing should be safe. - - - - - b0c1f2a6 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for #18151 - - - - - 9a99a178 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for desugaring of PostfixOperators - - - - - 2b89ca5b by Ben Gamari at 2020-06-01T06:33:37-04:00 HsToCore: Eta expand left sections Strangely, the comment next to this code already alluded to the fact that even simply eta-expanding will sacrifice laziness. It's quite unclear how we regressed so far. See #18151. - - - - - d412d7a3 by Kirill Elagin at 2020-06-01T06:34:21-04:00 Winferred-safe-imports: Do not exit with error Currently, when -Winferred-safe-imports is enabled, even when it is not turned into an error, the compiler will still exit with exit code 1 if this warning was emitted. Make sure it is really treated as a warning. - - - - - f945eea5 by Ben Gamari at 2020-06-01T06:34:58-04:00 nonmoving: Optimise log2_ceil - - - - - aab606e4 by Bodigrim at 2020-06-01T06:35:36-04:00 Clarify description of fromListN - - - - - 7e5220e2 by Bodigrim at 2020-06-01T06:35:36-04:00 Apply suggestion to libraries/base/GHC/Exts.hs - - - - - f3fb1ce9 by fendor at 2020-06-01T06:36:18-04:00 Add `isInScope` check to `lintCoercion` Mirrors the behaviour of `lintType`. - - - - - 5ac4d946 by fendor at 2020-06-01T06:36:18-04:00 Lint rhs of IfaceRule - - - - - 1cef6126 by Jeremy Schlatter at 2020-06-01T06:37:00-04:00 Fix wording in documentation The duplicate "orphan instance" phrase here doesn't make sense, and was probably an accident. - - - - - 5aaf08f2 by Takenobu Tani at 2020-06-01T06:37:43-04:00 configure: Modify aclocal.m4 according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * Rename: * compiler/GHC/Parser.hs <= compiler/parser/Parser.hs * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs * Add: * compiler/GHC/Cmm/Lexer.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular - - - - - 15857ad8 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Don't fail if we can't unlink __symlink_test Afterall, it's possible we were unable to create it due to lack of symlink permission. - - - - - 4a7229ef by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Refactor ghostscript detection Tamar reported that he saw crashes due to unhandled exceptions. - - - - - 2ab37eaf by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/perf_notes: Fix ill-typed assignments - - - - - e45d5b66 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/testutil: Fix bytes/str mismatch - - - - - 7002d0cb by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Work around spurious mypy failure - - - - - 11390e3a by Takenobu Tani at 2020-06-01T06:39:05-04:00 Clean up file paths for new module hierarchy This updates comments only. This patch replaces file references according to new module hierarchy. See also: * https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular * https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 8f2e5732 by Takenobu Tani at 2020-06-01T06:39:05-04:00 Modify file paths to module paths for new module hierarchy This updates comments only. This patch replaces module references according to new module hierarchy [1][2]. For files under the `compiler/` directory, I replace them as module paths instead of file paths. For instance, `GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3]. For current and future haddock's markup, this patch encloses the module name with "" [4]. [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 [3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613 [4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules - - - - - 68b71c4a by Tom Ellis at 2020-06-01T06:39:55-04:00 Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo - - - - - 95da76c2 by Sylvain Henry at 2020-06-01T06:40:41-04:00 Hadrian: fix binary-dist target for cross-compilation - - - - - 730fcd54 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for the @-operator Since GHC diverges from the Haskell Report by allowing the user to define (@) as an infix operator, we better give a good error message when the user does so unintentionally. In general, this is rather hard to do, as some failures will be discovered only in the renamer or the type checker: x :: (Integer, Integer) x @ (a, b) = (1, 2) This patch does *not* address this general case. However, it gives much better error messages when the binding is not syntactically valid: pairs xs @ (_:xs') = zip xs xs' Before this patch, the error message was rather puzzling: <interactive>:1:1: error: Parse error in pattern: pairs After this patch, the error message includes a hint: <interactive>:1:1: error: Parse error in pattern: pairs In a function binding for the ‘@’ operator. Perhaps you meant an as-pattern, which must not be surrounded by whitespace - - - - - 0fde5377 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TypeApplications With this patch, we always parse f @t as a type application, thereby producing better error messages. This steals two syntactic forms: * Prefix form of the @-operator in expressions. Since the @-operator is a divergence from the Haskell Report anyway, this is not a major loss. * Prefix form of @-patterns. Since we are stealing loose infix form anyway, might as well sacrifice the prefix form for the sake of much better error messages. - - - - - c68e7e1e by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TemplateHaskellQuotes While [e| |], [t| |], [d| |], and so on, steal syntax from list comprehensions, [| |] and [|| ||] do not steal any syntax. Thus we can improve error messages by always accepting them in the lexer. Turns out the renamer already performs necessary validation. - - - - - 120aedbd by Ben Gamari at 2020-06-01T16:07:02-04:00 gitlab-ci: Disable use of ld.lld on ARMv7 It turns out that lld non-deterministically fails on ARMv7. I suspect this may be due to the a kernel regression as this only started happening when we upgraded to 5.4. Nevertheless, easily avoided by simply sticking with gold. Works around #18280. - - - - - d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00 gitlab-ci: Ensure that workaround for #18280 applies to bindisttest We need to ensure that the `configure` flags working around #18280 are propagated to the bindisttest `configure` as well. - - - - - cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00 gitlab-ci: Allow ARMv7 job to fail Due to #18298. - - - - - 32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00 Clean up boot vs non-boot disambiguating types We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule. - - - - - c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00 docs: Add more details on InterruptibleFFI. Details from https://gitlab.haskell.org/ghc/ghc/issues/8684 and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430 - - - - - 1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00 Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr. MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd. This regression did not make it into a release of GHC. Here, the original behavior is restored, and FinalPtr is given the same treatment as PlainPtr. - - - - - 2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00 Fix documentation on type families not being extracted It looks like the location of the Names used for CoAxioms on type families are now located at their type constructors. Previously, Docs.hs thought the Names were located in the RHS, so the RealSrcSpan in the instanceMap and getInstLoc didn't match up. Fixes #18241 - - - - - 6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00 GHC.Hs.Instances: Compile with -O0 This module contains exclusively Data instances, which are going to be slow no matter what we do. Furthermore, they are incredibly slow to compile with optimisation (see #9557). Consequently we compile this with -O0. See #18254. - - - - - c330331a by nineonine at 2020-06-04T04:37:59-04:00 Add test for #17669 - - - - - cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00 rts: Add Windows-specific implementation of rtsSleep Previously we would use the POSIX path, which uses `nanosleep`. However, it turns out that `nanosleep` is provided by `libpthread` on Windows. In general we don't want to incur such a dependency. Avoid this by simply using `Sleep` on Windows. Fixes #18272. - - - - - ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00 compiler: Disable use of process jobs with process < 1.6.9 Due to #17926. - - - - - 6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00 [linker] Adds void printLoadedObjects(void); This allows us to dump in-memory object code locations for debugging. Fixup printLoadedObjects prototype - - - - - af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00 base: fix sign confusion in log1mexp implementation (fix #17125) author: claude (https://gitlab.haskell.org/trac-claude) The correct threshold for log1mexp is -(log 2) with the current specification of log1mexp. This change improves accuracy for large negative inputs. To avoid code duplication, a small helper function is added; it isn't the default implementation in Floating because it needs Ord. This patch does nothing to address that the Haskell specification is different from that in common use in other languages. - - - - - 2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00 Simple subsumption This patch simplifies GHC to use simple subsumption. Ticket #17775 Implements GHC proposal #287 https://github.com/ghc-proposals/ghc-proposals/blob/master/ proposals/0287-simplify-subsumption.rst All the motivation is described there; I will not repeat it here. The implementation payload: * tcSubType and friends become noticably simpler, because it no longer uses eta-expansion when checking subsumption. * No deeplyInstantiate or deeplySkolemise That in turn means that some tests fail, by design; they can all be fixed by eta expansion. There is a list of such changes below. Implementing the patch led me into a variety of sticky corners, so the patch includes several othe changes, some quite significant: * I made String wired-in, so that "foo" :: String rather than "foo" :: [Char] This improves error messages, and fixes #15679 * The pattern match checker relies on knowing about in-scope equality constraints, andd adds them to the desugarer's environment using addTyCsDs. But the co_fn in a FunBind was missed, and for some reason simple-subsumption ends up with dictionaries there. So I added a call to addTyCsDs. This is really part of #18049. * I moved the ic_telescope field out of Implication and into ForAllSkol instead. This is a nice win; just expresses the code much better. * There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader. We called checkDataKindSig inside tc_kind_sig, /before/ solveEqualities and zonking. Obviously wrong, easily fixed. * solveLocalEqualitiesX: there was a whole mess in here, around failing fast enough. I discovered a bad latent bug where we could successfully kind-check a type signature, and use it, but have unsolved constraints that could fill in coercion holes in that signature -- aargh. It's all explained in Note [Failure in local type signatures] in GHC.Tc.Solver. Much better now. * I fixed a serious bug in anonymous type holes. IN f :: Int -> (forall a. a -> _) -> Int that "_" should be a unification variable at the /outer/ level; it cannot be instantiated to 'a'. This was plain wrong. New fields mode_lvl and mode_holes in TcTyMode, and auxiliary data type GHC.Tc.Gen.HsType.HoleMode. This fixes #16292, but makes no progress towards the more ambitious #16082 * I got sucked into an enormous refactoring of the reporting of equality errors in GHC.Tc.Errors, especially in mkEqErr1 mkTyVarEqErr misMatchMsg misMatchMsgOrCND In particular, the very tricky mkExpectedActualMsg function is gone. It took me a full day. But the result is far easier to understand. (Still not easy!) This led to various minor improvements in error output, and an enormous number of test-case error wibbles. One particular point: for occurs-check errors I now just say Can't match 'a' against '[a]' rather than using the intimidating language of "occurs check". * Pretty-printing AbsBinds Tests review * Eta expansions T11305: one eta expansion T12082: one eta expansion (undefined) T13585a: one eta expansion T3102: one eta expansion T3692: two eta expansions (tricky) T2239: two eta expansions T16473: one eta determ004: two eta expansions (undefined) annfail06: two eta (undefined) T17923: four eta expansions (a strange program indeed!) tcrun035: one eta expansion * Ambiguity check at higher rank. Now that we have simple subsumption, a type like f :: (forall a. Eq a => Int) -> Int is no longer ambiguous, because we could write g :: (forall a. Eq a => Int) -> Int g = f and it'd typecheck just fine. But f's type is a bit suspicious, and we might want to consider making the ambiguity check do a check on each sub-term. Meanwhile, these tests are accepted, whereas they were previously rejected as ambiguous: T7220a T15438 T10503 T9222 * Some more interesting error message wibbles T13381: Fine: one error (Int ~ Exp Int) rather than two (Int ~ Exp Int, Exp Int ~ Int) T9834: Small change in error (improvement) T10619: Improved T2414: Small change, due to order of unification, fine T2534: A very simple case in which a change of unification order means we get tow unsolved constraints instead of one tc211: bizarre impredicative tests; just accept this for now Updates Cabal and haddock submodules. Metric Increase: T12150 T12234 T5837 haddock.base Metric Decrease: haddock.compiler haddock.Cabal haddock.base Merge note: This appears to break the `UnliftedNewtypesDifficultUnification` test. It has been marked as broken in the interest of merging. (cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5) - - - - - 2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00 Simplify bindLHsTyVarBndrs and bindHsQTyVars Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate `Maybe` arguments, which I find terribly confusing. Thankfully, it's possible to remove one `Maybe` argument from each of these functions, which this patch accomplishes: * `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if GHC should warn about any of the quantified type variables going unused. However, every call site uses `Nothing` in practice. This makes sense, since it doesn't really make sense to warn about unused type variables bound by an `LHsQTyVars`. For instance, you wouldn't warn about the `a` in `data Proxy a = Proxy` going unused. As a result, I simply remove this `Maybe SDoc` argument altogether. * `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same reasons that `bindHsQTyVars` took one. To make things more confusing, however, `bindLHsTyVarBndrs` also takes a separate `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in warnings and error messages. In practice, the `Maybe SDoc` and the `HsDocContext` often contain the same text. See the call sites for `bindLHsTyVarBndrs` in `rnFamInstEqn` and `rnConDecl`, for instance. There are only a handful of call sites where the text differs between the `Maybe SDoc` and `HsDocContext` arguments: * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`" and the `HsDocContext` says "`In the transformation rule`". * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says "`In the type`" but the `HsDocContext` is inhereted from the surrounding context (e.g., if `rnHsTyKi` were called on a top-level type signature, the `HsDocContext` would be "`In the type signature`" instead) In both cases, warnings/error messages arguably _improve_ by unifying making the `Maybe SDoc`'s text match that of the `HsDocContext`. As a result, I decided to remove the `Maybe SDoc` argument to `bindLHsTyVarBndrs` entirely and simply reuse the text from the `HsDocContext`. (I decided to change the phrase "transformation rule" to "rewrite rule" while I was in the area.) The `Maybe SDoc` argument has one other purpose: signaling when to emit "`Unused quantified type variable`" warnings. To recover this functionality, I replaced the `Maybe SDoc` argument with a boolean-like `WarnUnusedForalls` argument. The only `bindLHsTyVarBndrs` call site that chooses _not_ to emit these warnings in `bindHsQTyVars`. - - - - - e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00 hadrian: Add missing deriveConstants dependency on ghcplatform.h deriveConstants wants to compile C sources which #include PosixSource.h, which itself #includes ghcplatform.h. Make sure that Hadrian knows about this dependency. Fixes #18290. - - - - - b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00 ghc-prim needs to depend on libc and libm libm is just an empty shell on musl, and all the math functions are contained in libc. - - - - - 6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00 Disable DLL loading if without system linker Some platforms (musl, aarch64) do not have a working dynamic linker implemented in the libc, even though we might see dlopen. It will ultimately just return that this is not supported. Hence we'll add a flag to the compiler to flat our disable loading dlls. This is needed as we will otherwise try to load the shared library even if this will subsequently fail. At that point we have given up looking for static options though. - - - - - 4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00 Range is actually +/-2^32, not +/-2^31 See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf - - - - - f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00 OccurAnal: Avoid exponential behavior due to where clauses Previously the `Var` case of `occAnalApp` could in some cases (namely in the case of `runRW#` applications) call `occAnalRhs` two. In the case of nested `runRW#`s this results in exponential complexity. In some cases the compilation time that resulted would be very long indeed (see #18296). Fixes #18296. Metric Decrease: T9961 T12150 T12234 - - - - - 9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00 Add link to GHC's wiki in the GHC API header This adds a URL to point to GHC's wiki in the GHC API header. Newcomers could easily find more information from the GHC API's web like [1]. [1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html [skip ci] - - - - - 72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00 Make GADT constructors adhere to the forall-or-nothing rule properly Issue #18191 revealed that the types of GADT constructors don't quite adhere to the `forall`-or-nothing rule. This patch serves to clean up this sad state of affairs somewhat. The main change is not in the code itself, but in the documentation, as this patch introduces two sections to the GHC User's Guide: * A "Formal syntax for GADTs" section that presents a BNF-style grammar for what is and isn't allowed in GADT constructor types. This mostly exists to codify GHC's existing behavior, but it also imposes a new restriction that addresses #18191: the outermost `forall` and/or context in a GADT constructor is not allowed to be surrounded by parentheses. Doing so would make these `forall`s/contexts nested, and GADTs do not support nested `forall`s/contexts at present. * A "`forall`-or-nothing rule" section that describes exactly what the `forall`-or-nothing rule is all about. Surprisingly, there was no mention of this anywhere in the User's Guide up until now! To adhere the new specification in the "Formal syntax for GADTs" section of the User's Guide, the following code changes were made: * A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced. This is very much like `splitLHsSigmaTy`, except that it avoids splitting apart any parentheses, which can be syntactically significant for GADT types. See `Note [No nested foralls or contexts in GADT constructors]` in `GHC.Hs.Type`. * `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return it when given a prefix GADT constructor. Unlike `ConDeclGADT`, `ConDeclGADTPrefixPs` does not split the GADT type into its argument and result types, as this cannot be done until after the type is renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why this is the case). * `GHC.Renamer.Module.rnConDecl` now has an additional case for `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into its `forall`s, context, argument types, and result type, and (2) checks for nested `forall`s/contexts. Step (2) used to be performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather than the renamer, but now the relevant code from the typechecker can simply be deleted. One nice side effect of this change is that we are able to give a more accurate error message for GADT constructors that use visible dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`), which improves the stderr in the `T16326_Fail6` test case. Fixes #18191. Bumps the Haddock submodule. - - - - - a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00 Always use rnImplicitBndrs to bring implicit tyvars into scope This implements a first step towards #16762 by changing the renamer to always use `rnImplicitBndrs` to bring implicitly bound type variables into scope. The main change is in `rnFamInstEqn` and `bindHsQTyVars`, which previously used _ad hoc_ methods of binding their implicit tyvars. There are a number of knock-on consequences: * One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding mechanism was to give more precise source locations in `-Wunused-type-patterns` warnings. (See https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an example of this.) However, these warnings are actually a little _too_ precise, since implicitly bound type variables don't have exact binding sites like explicitly bound type variables do. A similar problem existed for "`Different names for the same type variable`" errors involving implicit tyvars bound by `bindHsQTyVars`. Therefore, we simply accept the less precise (but more accurate) source locations from `rnImplicitBndrs` in `rnFamInstEqn` and `bindHsQTyVars`. See `Note [Source locations for implicitly bound type variables]` in `GHC.Rename.HsType` for the full story. * In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs to be able to look up names from the parent class (in the event that we are renaming an associated type family instance). As a result, `rnImplicitBndrs` now takes an argument of type `Maybe assoc`, which is `Just` in the event that a type family instance is associated with a class. * Previously, GHC kept track of three type synonyms for free type variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups` (which are allowed to contain duplicates), and `FreeKiTyVarsNoDups` (which contain no duplicates). However, making is a distinction between `-Dups` and `-NoDups` is now pointless, as all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually end up being passed to `rnImplicitBndrs`, which removes duplicates. As a result, I decided to just get rid of `FreeKiTyVarsDups` and `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`. * The `bindLRdrNames` and `deleteBys` functions are now dead code, so I took the liberty of removing them. - - - - - 24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00 Clarify leaf module names for new module hierarchy This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00 rts: Remove unused GET_ENTRY closure macro This macro is not used and got broken in the meantime, as ENTRY_CODE was deleted. - - - - - 87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00 Fix -fkeep-cafs flag name in users guide - - - - - ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00 Expose impliedGFlags, impledOffGFlags, impliedXFlags - - - - - 7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00 Cross-module LambdaFormInfo passing - Store LambdaFormInfos of exported Ids in interface files - Use them in importing modules This is for optimization purposes: if we know LambdaFormInfo of imported Ids we can generate more efficient calling code, see `getCallMethod`. Exporting (putting them in interface files or in ModDetails) and importing (reading them from interface files) are both optional. We don't assume known LambdaFormInfos anywhere and do not change how we call Ids with unknown LambdaFormInfos. Runtime, allocation, and residency numbers when building Cabal-the-library (commit 0d4ee7ba3): (Log and .hp files are in the MR: !2842) | | GHC HEAD | This patch | Diff | |-----|----------|------------|----------------| | -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% | | -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% | | -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% | | | GHC HEAD | This patch | Diff | |-----|-----------------|-----------------|----------------------------| | -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% | | -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% | | -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% | NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively turn all GCs into major GCs, and do GC more often. | | GHC HEAD | This patch | Diff | |-----|----------------------------|------------------------------|----------------------------| | -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% | | -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% | | -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% | NoFib results: -------------------------------------------------------------------------------- Program Size Allocs Instrs Reads Writes -------------------------------------------------------------------------------- CS 0.0% 0.0% +0.0% +0.0% +0.0% CSD 0.0% 0.0% 0.0% +0.0% +0.0% FS 0.0% 0.0% +0.0% +0.0% +0.0% S 0.0% 0.0% +0.0% +0.0% +0.0% VS 0.0% 0.0% +0.0% +0.0% +0.0% VSD 0.0% 0.0% +0.0% +0.0% +0.1% VSM 0.0% 0.0% +0.0% +0.0% +0.0% anna 0.0% 0.0% -0.3% -0.8% -0.0% ansi 0.0% 0.0% -0.0% -0.0% 0.0% atom 0.0% 0.0% -0.0% -0.0% 0.0% awards 0.0% 0.0% -0.1% -0.3% 0.0% banner 0.0% 0.0% -0.0% -0.0% -0.0% bernouilli 0.0% 0.0% -0.0% -0.0% -0.0% binary-trees 0.0% 0.0% -0.0% -0.0% +0.0% boyer 0.0% 0.0% -0.0% -0.0% 0.0% boyer2 0.0% 0.0% -0.0% -0.0% 0.0% bspt 0.0% 0.0% -0.0% -0.2% 0.0% cacheprof 0.0% 0.0% -0.1% -0.4% +0.0% calendar 0.0% 0.0% -0.0% -0.0% 0.0% cichelli 0.0% 0.0% -0.9% -2.4% 0.0% circsim 0.0% 0.0% -0.0% -0.0% 0.0% clausify 0.0% 0.0% -0.1% -0.3% 0.0% comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0% compress 0.0% 0.0% -0.0% -0.0% -0.0% compress2 0.0% 0.0% -0.0% -0.0% 0.0% constraints 0.0% 0.0% -0.1% -0.2% -0.0% cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0% cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0% cse 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0% dom-lt 0.0% 0.0% -0.1% -0.2% 0.0% eliza 0.0% 0.0% -0.5% -1.5% 0.0% event 0.0% 0.0% -0.0% -0.0% -0.0% exact-reals 0.0% 0.0% -0.1% -0.3% +0.0% exp3_8 0.0% 0.0% -0.0% -0.0% -0.0% expert 0.0% 0.0% -0.3% -1.0% -0.0% fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0% fasta 0.0% 0.0% -0.0% -0.0% +0.0% fem 0.0% 0.0% -0.0% -0.0% 0.0% fft 0.0% 0.0% -0.0% -0.0% 0.0% fft2 0.0% 0.0% -0.0% -0.0% 0.0% fibheaps 0.0% 0.0% -0.0% -0.0% +0.0% fish 0.0% 0.0% 0.0% -0.0% +0.0% fluid 0.0% 0.0% -0.4% -1.2% +0.0% fulsom 0.0% 0.0% -0.0% -0.0% 0.0% gamteb 0.0% 0.0% -0.1% -0.3% 0.0% gcd 0.0% 0.0% -0.0% -0.0% 0.0% gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0% genfft 0.0% 0.0% -0.0% -0.0% 0.0% gg 0.0% 0.0% -0.0% -0.0% +0.0% grep 0.0% 0.0% -0.0% -0.0% -0.0% hidden 0.0% 0.0% -0.1% -0.4% -0.0% hpg 0.0% 0.0% -0.2% -0.5% +0.0% ida 0.0% 0.0% -0.0% -0.0% +0.0% infer 0.0% 0.0% -0.3% -0.8% -0.0% integer 0.0% 0.0% -0.0% -0.0% +0.0% integrate 0.0% 0.0% -0.0% -0.0% 0.0% k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0% kahan 0.0% 0.0% -0.0% -0.0% +0.0% knights 0.0% 0.0% -2.2% -5.4% 0.0% lambda 0.0% 0.0% -0.6% -1.8% 0.0% last-piece 0.0% 0.0% -0.0% -0.0% 0.0% lcss 0.0% 0.0% -0.0% -0.1% 0.0% life 0.0% 0.0% -0.0% -0.1% 0.0% lift 0.0% 0.0% -0.2% -0.6% +0.0% linear 0.0% 0.0% -0.0% -0.0% -0.0% listcompr 0.0% 0.0% -0.0% -0.0% 0.0% listcopy 0.0% 0.0% -0.0% -0.0% 0.0% maillist 0.0% 0.0% -0.1% -0.3% +0.0% mandel 0.0% 0.0% -0.0% -0.0% 0.0% mandel2 0.0% 0.0% -0.0% -0.0% -0.0% mate +0.0% 0.0% -0.0% -0.0% -0.0% minimax 0.0% 0.0% -0.2% -1.0% 0.0% mkhprog 0.0% 0.0% -0.1% -0.2% -0.0% multiplier 0.0% 0.0% -0.0% -0.0% -0.0% n-body 0.0% 0.0% -0.0% -0.0% +0.0% nucleic2 0.0% 0.0% -0.1% -0.2% 0.0% para 0.0% 0.0% -0.0% -0.0% -0.0% paraffins 0.0% 0.0% -0.0% -0.0% 0.0% parser 0.0% 0.0% -0.2% -0.7% 0.0% parstof 0.0% 0.0% -0.0% -0.0% +0.0% pic 0.0% 0.0% -0.0% -0.0% 0.0% pidigits 0.0% 0.0% +0.0% +0.0% +0.0% power 0.0% 0.0% -0.2% -0.6% +0.0% pretty 0.0% 0.0% -0.0% -0.0% -0.0% primes 0.0% 0.0% -0.0% -0.0% 0.0% primetest 0.0% 0.0% -0.0% -0.0% -0.0% prolog 0.0% 0.0% -0.3% -1.1% 0.0% puzzle 0.0% 0.0% -0.0% -0.0% 0.0% queens 0.0% 0.0% -0.0% -0.0% +0.0% reptile 0.0% 0.0% -0.0% -0.0% 0.0% reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0% rewrite 0.0% 0.0% -0.7% -2.5% -0.0% rfib 0.0% 0.0% -0.0% -0.0% 0.0% rsa 0.0% 0.0% -0.0% -0.0% 0.0% scc 0.0% 0.0% -0.1% -0.2% -0.0% sched 0.0% 0.0% -0.0% -0.0% -0.0% scs 0.0% 0.0% -1.0% -2.6% +0.0% simple 0.0% 0.0% +0.0% -0.0% +0.0% solid 0.0% 0.0% -0.0% -0.0% 0.0% sorting 0.0% 0.0% -0.6% -1.6% 0.0% spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0% sphere 0.0% 0.0% -0.0% -0.0% -0.0% symalg 0.0% 0.0% -0.0% -0.0% +0.0% tak 0.0% 0.0% -0.0% -0.0% 0.0% transform 0.0% 0.0% -0.0% -0.0% 0.0% treejoin 0.0% 0.0% -0.0% -0.0% 0.0% typecheck 0.0% 0.0% -0.0% -0.0% +0.0% veritas +0.0% 0.0% -0.2% -0.4% +0.0% wang 0.0% 0.0% -0.0% -0.0% 0.0% wave4main 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0% x2n1 0.0% 0.0% -0.0% -0.0% -0.0% -------------------------------------------------------------------------------- Min 0.0% 0.0% -2.2% -5.4% -0.0% Max +0.0% 0.0% +0.0% +0.0% +0.1% Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0% Metric increases micro benchmarks tracked in #17686: Metric Increase: T12150 T12234 T12425 T13035 T5837 T6048 T9233 Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00 Give Language a Bounded instance - - - - - 9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Optimisation in Unique.Supply This patch switches on -fno-state-hack in GHC.Types.Unique.Supply. It turned out that my fixes for #18078 (coercion floating) changed the optimisation pathway for mkSplitUniqSupply in such a way that we had an extra allocation inside the inner loop. Adding -fno-state-hack fixed that -- and indeed the loop in mkSplitUniqSupply is a classic example of the way in which -fno-state-hack can be bad; see #18238. Moreover, the new code is better than the old. They allocate the same, but the old code ends up with a partial application. The net effect is that the test perf/should_run/UniqLoop runs 20% faster! From 2.5s down to 2.0s. The allocation numbers are the same -- but elapsed time falls. Good! The bad thing about this is that it's terribly delicate. But at least it's a good example of such delicacy in action. There is a long Note [Optimising the unique supply] which now explains all this. - - - - - 6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Implement cast worker/wrapper properly The cast worker/wrapper transformation transforms x = e |> co into y = e x = y |> co This is done by the simplifier, but we were being careless about transferring IdInfo from x to y, and about what to do if x is a NOINLNE function. This resulted in a series of bugs: #17673, #18093, #18078. This patch fixes all that: * Main change is in GHC.Core.Opt.Simplify, and the new prepareBinding function, which does this cast worker/wrapper transform. See Note [Cast worker/wrappers]. * There is quite a bit of refactoring around prepareRhs, makeTrivial etc. It's nicer now. * Some wrappers from strictness and cast w/w, notably those for a function with a NOINLINE, should inline very late. There wasn't really a mechanism for that, which was an existing bug really; so I invented a new finalPhase = Phase (-1). It's used for all simplifier runs after the user-visible phase 2,1,0 have run. (No new runs of the simplifier are introduced thereby.) See new Note [Compiler phases] in GHC.Types.Basic; the main changes are in GHC.Core.Opt.Driver * Doing this made me trip over two places where the AnonArgFlag on a FunTy was being lost so we could end up with (Num a -> ty) rather than (Num a => ty) - In coercionLKind/coercionRKind - In contHoleType in the Simplifier I fixed the former by defining mkFunctionType and using it in coercionLKind/RKind. I could have done the same for the latter, but the information is almost to hand. So I fixed the latter by - adding sc_hole_ty to ApplyToVal (like ApplyToTy), - adding as_hole_ty to ValArg (like TyArg) - adding sc_fun_ty to StrictArg Turned out I could then remove ai_type from ArgInfo. This is just moving the deck chairs around, but it worked out nicely. See the new Note [AnonArgFlag] in GHC.Types.Var * When looking at the 'arity decrease' thing (#18093) I discovered that stable unfoldings had a much lower arity than the actual optimised function. That's what led to the arity-decrease message. Simple solution: eta-expand. It's described in Note [Eta-expand stable unfoldings] in GHC.Core.Opt.Simplify * I also discovered that unsafeCoerce wasn't being inlined if the context was boring. So (\x. f (unsafeCoerce x)) would create a thunk -- yikes! I fixed that by making inlineBoringOK a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold. I also found that unsafeCoerceName was unused, so I removed it. I made a test case for #18078, and a very similar one for #17673. The net effect of all this on nofib is very modest, but positive: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.4% -0.1% -3.1% -3.1% 0.0% fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0% maillist -0.4% -0.1% -7.8% -1.0% -14.3% primetest -0.4% -15.6% -7.1% -6.6% 0.0% -------------------------------------------------------------------------------- Min -0.9% -15.6% -13.3% -14.2% -14.3% Max -0.3% 0.0% +12.1% +12.4% 0.0% Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1% All following metric decreases are compile-time allocation decreases between -1% and -3%: Metric Decrease: T5631 T13701 T14697 T15164 - - - - - 32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00 Fix lookupGlobalOccRn_maybe sometimes reporting an error In some cases it was possible for lookupGlobalOccRn_maybe to return an error, when it should be returning a Nothing. If it called lookupExactOcc_either when there were no matching GlobalRdrElts in the otherwise case, it would return an error message. This could be caused when lookupThName_maybe in Template Haskell was looking in different namespaces (thRdrNameGuesses), guessing different namespaces that the name wasn't guaranteed to be found in. However, by addressing this some more accurate errors were being lost in the conversion to Maybes. So some of the lookup* functions have been shuffled about so that errors should always be ignored in lookup*_maybes, and propagated otherwise. This fixes #18263 - - - - - 9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00 Initialize the allocation counter in GHCi to 0 (Fixes #16012) According to the documentation for the function `getAllocationCounter` in [System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html) initialize the allocationCounter also in GHCi to 0. - - - - - 8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00 test: fix conc038 We had spurious failures of conc038 test on CI with stdout: ``` newThread started -mainThread -Haskell: 2 newThread back again +mainThread 1 sec later shutting down +Haskell: 2 ``` - - - - - 4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00 Release Notes: Add news from the pattern-match checker [skip ci] - - - - - 3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00 Only test T16190 with the NCG T16190 is meant to test a NCG feature. It has already caused spurious failures in other MRs (e.g. !2165) when LLVM is used. - - - - - 2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00 DynFlags refactoring VIII (#17957) * Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.* * Add LlvmOpts datatype to store Llvm backend options * Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and Llvm.MetaExpr) which require LlvmOpts. * Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`) - - - - - 7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove unused code - - - - - 72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor homeUnit * rename thisPackage into homeUnit * document and refactor several Backpack things - - - - - 8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Rename unsafeGetUnitInfo into unsafeLookupUnit - - - - - f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Add allowVirtualUnits field in PackageState Instead of always querying DynFlags to know whether we are allowed to use virtual units (i.e. instantiated on-the-fly, cf Note [About units] in GHC.Unit), we store it once for all in `PackageState.allowVirtualUnits`. This avoids using DynFlags too much (cf #17957) and is preliminary work for #14335. - - - - - e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Enhance UnitId use * use UnitId instead of String to identify wired-in units * use UnitId instead of Unit in the backend (Unit are only use by Backpack to produce type-checked interfaces, not real code) * rename lookup functions for consistency * documentation - - - - - 9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove LinkerUnitId type alias - - - - - d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor WiredMap * Remove WiredInUnitId and WiredUnitId type aliases - - - - - 3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document and refactor `mkUnit` and `mkUnitInfoMap` - - - - - d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove PreloadUnitId type alias - - - - - f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename listUnitInfoMap into listUnitInfo There is no Map involved - - - - - ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc. - - - - - 202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Make ClosureUnitInfoMap uses UnitInfoMap - - - - - 55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove ClosureUnitInfoMap - - - - - 653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit (2) * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc. - - - - - ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move dump_mod_map into initUnits - - - - - 598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move wiring of homeUnitInstantiations outside of mkUnitState - - - - - 437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00 Avoid timing module map dump in initUnits - - - - - 9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove preload parameter of mkUnitState * Remove preload parameter (unused) * Don't explicitly return preloaded units: redundant because already returned as "preloadUnits" field of UnitState - - - - - 266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: refactor unwireUnit - - - - - 9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document getPreloadUnitsAnd - - - - - bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: remove useless add_package parameter - - - - - 36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: make listVisibleModuleNames take a UnitState - - - - - 5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document add_package - - - - - 4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document closeUnitDeps - - - - - 42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: findWiredInUnits - - - - - a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: reportCycles, reportUnusable - - - - - 8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: merge_databases - - - - - fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: add UnitConfig datatype Avoid directly querying flags from DynFlags to build the UnitState. Instead go via UnitConfig so that we could reuse this to make another UnitState for plugins. - - - - - 4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move distrustAll into mkUnitState - - - - - 28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Create helper upd_wired_in_home_instantiations - - - - - ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Put database cache in UnitConfig - - - - - bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00 Don't return preload units when we set DyNFlags Preload units can be retrieved in UnitState when needed (i.e. in GHCi) - - - - - 1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 NCGConfig: remove useless ncgUnitId field - - - - - c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Doc: fix some comments - - - - - 456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Bump haddock submodule and allow metric decrease Metric Decrease: T12150 T12234 T5837 Metric Increase: T16190 - - - - - 42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00 Trim the demand for recursive product types Ticket #18304 showed that we need to be very careful when exploring the demand (esp usage demand) on recursive product types. This patch solves the problem by trimming the demand on such types -- in effect, a form of "widening". See the Note [Trimming a demand to a type] in DmdAnal, which explains how I did this by piggy-backing on an existing mechansim for trimming demands becuase of GADTs. The significant payload of this patch is very small indeed: * Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to avoid looking through recursive types. But on the way * I found that ae_rec_tc was entirely inoperative and did nothing. So I removed it altogether from DmdAnal. * I moved some code around in DmdAnal and Demand. (There are no actual changes in dmdFix.) * I changed the API of DmsAnal.dmdAnalRhsLetDown to return a StrictSig rather than a decorated Id * I removed the dead function peelTsFuns from Demand Performance effects: Nofib: 0.0% changes. Not surprising, because they don't use recursive products Perf tests T12227: 1% increase in compiler allocation, becuase $cto gets w/w'd. It did not w/w before because it takes a deeply nested argument, so the worker gets too many args, so we abandon w/w altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough) With this patch we trim the demands. That is not strictly necessary (since these Generic type constructors are like tuples -- they can't cause a loop) but the net result is that we now w/w $cto which is fine. UniqLoop: 16% decrease in /runtime/ allocation. The UniqSupply is a recursive product, so currently we abandon all strictness on 'churn'. With this patch 'churn' gets useful strictness, and we w/w it. Hooray Metric Decrease: UniqLoop Metric Increase: T12227 - - - - - 87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00 Add introductory prose for Data.Traversable - - - - - 9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00 Fix #12073: Add MonadFix Q instance - - - - - 220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00 testsuite: Increase size of T12150 As noted in #18319, this test was previously very fragile. Increase its size to make it more likely that its fails with its newly-increased acceptance threshold. Metric Increase: T12150 - - - - - 8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00 gitlab-ci: Always push perf notes Previously we ci.sh would run with `set -e` implying that we wouldn't push perf notes if the testsuite were to fail, even if it *only* failed due to perf notes. This rendered the whole performance testing story quite fragile as a single regressing commit would cause every successive commit to fail since a new baseline would not be uploaded. Fix this by ensuring that we always push performance notes. - - - - - 7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00 gitlab-ci: Eliminate redundant push of CI metrics - - - - - a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00 Use HsForAllTelescope to avoid inferred, visible foralls Currently, `HsForAllTy` permits the combination of `ForallVis` and `Inferred`, but you can't actually typecheck code that uses it (e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a new `HsForAllTelescope` data type that makes a type-level distinction between visible and invisible `forall`s such that visible `forall`s do not track `Specificity`. That part of the patch is actually quite small; the rest is simply changing consumers of `HsType` to accommodate this new type. Fixes #18235. Bumps the `haddock` submodule. - - - - - c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00 winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges. The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00 codeGen: Don't discard live case binders in unsafeEqualityProof logic Previously CoreToStg would unconditionally discard cases of the form: case unsafeEqualityProof of wild { _ -> rhs } and rather replace the whole thing with `rhs`. However, in some cases (see #18227) the case binder is still live, resulting in unbound occurrences in `rhs`. Fix this by only discarding the case if the case binder is dead. Fixes #18227. - - - - - e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00 testsuite: Add tests for #18227 T18227A is the original issue which gave rise to the ticket and depends upon bytestring. T18227B is a minimized reproducer. - - - - - 8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Fix rts include and library paths Fixes two bugs: * (?) and (<>) associated in a surprising way * We neglected to include libdw paths in the rts configure flags - - - - - bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Drop redundant GHC arguments Cabal should already be passing this arguments to GHC. - - - - - 01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00 FFI: Fix pass small ints in foreign call wrappers The Haskell calling convention requires integer parameters smaller than wordsize to be promoted to wordsize (where the upper bits are don't care). To access such small integer parameter read a word from the parameter array and then cast that word to the small integer target type. Fixes #15933 - - - - - 502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00 Fix "ndecreasingIndentation" in manual (#18116) - - - - - 9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00 Use foldl' in unionManyUniqDSets - - - - - 761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00 Load .lo as well. Some archives contain so called linker objects, with the affectionate .lo suffic. For example the musl libc.a will come in that form. We still want to load those objects, hence we should not discard them and look for .lo as well. Ultimately we might want to fix this proerly by looking at the file magic. - - - - - cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00 User's Guide: KnownNat evidence is Natural This bit of documentation got outdated after commit 1fcede43d2b30f33b7505e25eb6b1f321be0407f - - - - - d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00 Fix typos and formatting in user guide - - - - - 56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00 Resolve TODO - - - - - 3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00 Rename TcHoleErrors to GHC.Tc.Errors.Hole - - - - - d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00 hadrian: Build with threaded runtime if available See #16873. - - - - - 0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00 T16190: only measure bytes_allocated Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics fluctuate by 13%. - - - - - 4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00 docs: fix formatting in users guide - - - - - eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00 Move CLabel assertions into smart constructors (#17957) It avoids using DynFlags in the Outputable instance of Clabel to check assertions at pretty-printing time. - - - - - 7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00 base: Bump to 4.15.0.0 - - - - - 20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00 configure: Use grep -q instead of --quiet The latter is apparently not supported by busybox. - - - - - 40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00 Linear types (#15981) This is the first step towards implementation of the linear types proposal (https://github.com/ghc-proposals/ghc-proposals/pull/111). It features * A language extension -XLinearTypes * Syntax for linear functions in the surface language * Linearity checking in Core Lint, enabled with -dlinear-core-lint * Core-to-core passes are mostly compatible with linearity * Fields in a data type can be linear or unrestricted; linear fields have multiplicity-polymorphic constructors. If -XLinearTypes is disabled, the GADT syntax defaults to linear fields The following items are not yet supported: * a # m -> b syntax (only prefix FUN is supported for now) * Full multiplicity inference (multiplicities are really only checked) * Decent linearity error messages * Linear let, where, and case expressions in the surface language (each of these currently introduce the unrestricted variant) * Multiplicity-parametric fields * Syntax for annotating lambda-bound or let-bound with a multiplicity * Syntax for non-linear/multiple-field-multiplicity records * Linear projections for records with a single linear field * Linear pattern synonyms * Multiplicity coercions (test LinearPolyType) A high-level description can be found at https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation Following the link above you will find a description of the changes made to Core. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Matthew Pickering * Arnaud Spiwack With contributions from: * Mark Barbone * Alexander Vershilov Updates haddock submodule. - - - - - 6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00 Various performance improvements This implements several general performance improvements to GHC, to offset the effect of the linear types change. General optimisations: - Add a `coreFullView` function which iterates `coreView` on the head. This avoids making function recursive solely because the iterate `coreView` themselves. As a consequence, this functions can be inlined, and trigger case-of-known constructor (_e.g._ `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`, `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`, `tyConAppTyCon_maybe`). The common pattern about all these functions is that they are almost always used as views, and immediately consumed by a case expression. This commit also mark them asx `INLINE`. - In `subst_ty` add a special case for nullary `TyConApp`, which avoid allocations altogether. - Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This required quite a bit of module shuffling. case. `myTyConApp` enforces crucial sharing, which was lost during substitution. See also !2952 . - Make `subst_ty` stricter. - In `eqType` (specifically, in `nonDetCmpType`), add a special case, tested first, for the very common case of nullary `TyConApp`. `nonDetCmpType` has been made `INLINE` otherwise it is actually a regression. This is similar to the optimisations in !2952. Linear-type specific optimisations: - Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in the definition of the pattern synonyms `One` and `Many`. - Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`: `Multiplicity` now import `Type` normally, rather than from the `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the `One` and `Many` pattern synonyms. - Make `updateIdTypeAndMult` strict in its type and multiplicity - The `scaleIdBy` gets a specialised definition rather than being an alias to `scaleVarBy` - `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type, Type)` instead of `Type -> Maybe (Scaled Type, Type)` - Remove the `MultMul` pattern synonym in favour of a view `isMultMul` because pattern synonyms appear not to inline well. - in `eqType`, in a `FunTy`, compare multiplicities last: they are almost always both `Many`, so it helps failing faster. - Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the instances of `TyConApp ManyDataConTy []` are physically the same. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Arnaud Spiwack Metric Decrease: haddock.base T12227 T12545 T12990 T1969 T3064 T5030 T9872b Metric Increase: haddock.base haddock.Cabal haddock.compiler T12150 T12234 T12425 T12707 T13035 T13056 T15164 T16190 T18304 T1969 T3064 T3294 T5631 T5642 T5837 T6048 T9020 T9233 T9675 T9872a T9961 WWRec - - - - - 57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Remove integer-simple integer-simple uses lists of words (`[Word]`) to represent big numbers instead of ByteArray#: * it is less efficient than the newer ghc-bignum native backend * it isn't compatible with the big number representation that is now shared by all the ghc-bignum backends (based on the one that was used only in integer-gmp before). As a consequence, we simply drop integer-simple - - - - - 9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00 ghc-bignum library ghc-bignum is a newer package that aims to replace the legacy integer-simple and integer-gmp packages. * it supports several backends. In particular GMP is still supported and most of the code from integer-gmp has been merged in the "gmp" backend. * the pure Haskell "native" backend is new and is much faster than the previous pure Haskell implementation provided by integer-simple * new backends are easier to write because they only have to provide a few well defined functions. All the other code is common to all backends. In particular they all share the efficient small/big number distinction previously used only in integer-gmp. * backends can all be tested against the "native" backend with a simple Cabal flag. Backends are only allowed to differ in performance, their results should be the same. * Add `integer-gmp` compat package: provide some pattern synonyms and function aliases for those in `ghc-bignum`. It is intended to avoid breaking packages that depend on `integer-gmp` internals. Update submodules: text, bytestring Metric Decrease: Conversions ManyAlternatives ManyConstructors Naperian T10359 T10547 T10678 T12150 T12227 T12234 T12425 T13035 T13719 T14936 T1969 T4801 T4830 T5237 T5549 T5837 T8766 T9020 parsing001 space_leak_001 T16190 haddock.base On ARM and i386, T17499 regresses (+6% > 5%). On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%). Metric Increase: T17499 T13701 - - - - - 96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update compiler Thanks to ghc-bignum, the compiler can be simplified: * Types and constructors of Integer and Natural can be wired-in. It means that we don't have to query them from interfaces. It also means that numeric literals don't have to carry their type with them. * The same code is used whatever ghc-bignum backend is enabled. In particular, conversion of bignum literals into final Core expressions is now much more straightforward. Bignum closure inspection too. * GHC itself doesn't depend on any integer-* package anymore * The `integerLibrary` setting is gone. - - - - - 0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `base` package * GHC.Natural isn't implemented in `base` anymore. It is provided by ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural primitives in `base` without fearing issues with built-in rewrite rules (cf #15286) * `base` doesn't conditionally depend on an integer-* package anymore, it depends on ghc-bignum * Some duplicated code in integer-* can now be factored in GHC.Float * ghc-bignum tries to use a uniform naming convention so most of the other changes are renaming - - - - - aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `make` based build system * replace integer-* package selection with ghc-bignum backend selection - - - - - f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update testsuite * support detection of slow ghc-bignum backend (to replace the detection of integer-simple use). There are still some test cases that the native backend doesn't handle efficiently enough. * remove tests for GMP only functions that have been removed from ghc-bignum * fix test results showing dependent packages (e.g. integer-gmp) or showing suggested instances * fix test using Integer/Natural API or showing internal names - - - - - dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update Hadrian * support ghc-bignum backend selection in flavours and command-line * support ghc-bignum "--check" flag (compare results of selected backend against results of the native one) in flavours and command-line (e.g. pass --bignum=check-gmp" to check the "gmp" backend) * remove the hack to workaround #15286 * build GMP only when the gmp backend is used * remove hacks to workaround `text` package flags about integer-*. We fix `text` to use ghc-bignum unconditionally in another patch - - - - - fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Bump bytestring and text submodules - - - - - 1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00 docs: mention -hiedir in docs for -outputdir [skip ci] - - - - - 729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00 Hadrian: fix build on Mac OS Catalina (#17798) - - - - - 95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00 Relax allocation threshold for T12150. This test performs little work, so the most minor allocation changes often cause the test to fail. Increasing the threshold to 2% should help with this. - - - - - 8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00 hadrian: Bump pinned cabal.project to an existent index-state - - - - - 08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00 Fix uninitialized field read in Linker.c Valgrind report of the bug when running the test `linker_unload`: ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522) ==29666== by 0x36C0600: loadArchive (LoadArchive.c:626) ==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload) ==29666== ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507) ==29666== by 0x369CA8D: loadObj_ (Linker.c:1536) ==29666== by 0x369CB17: loadObj (Linker.c:1557) ==29666== by 0x3866BC: main (linker_unload.c:33) The problem is `mkOc` allocates a new `ObjectCode` and calls `setOcInitialStatus` without initializing the `status` field. `setOcInitialStatus` reads the field as first thing: static void setOcInitialStatus(ObjectCode* oc) { if (oc->status == OBJECT_DONT_RESOLVE) return; if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; } } `setOcInitialStatus` is unsed in two places for two different purposes: in `mkOc` where we don't have the `status` field initialized yet (`mkOc` is supposed to initialize it), and `loadOc` where we do have `status` field initialized and we want to update it. Instead of splitting the function into two functions which are both called just once I inline the functions in the use sites and remove it. Fixes #18342 - - - - - da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00 fix windows bootstrap due to linker changes - - - - - 2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00 DynFlags: store default depth in SDocContext (#17957) It avoids having to use DynFlags to reach for pprUserLength. - - - - - d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00 Move tablesNextToCode field into Platform tablesNextToCode is a platform setting and doesn't belong into DynFlags (#17957). Doing this is also a prerequisite to fix #14335 where we deal with two platforms (target and host) that may have different platform settings. - - - - - 809caedf by John Ericson at 2020-06-23T22:47:37-04:00 Switch from HscSource to IsBootInterface for module lookup in GhcMake We look up modules by their name, and not their contents. There is no way to separately reference a signature vs regular module; you get what you get. Only boot files can be referenced indepenently with `import {-# SOURCE #-}`. - - - - - 7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Cmm: introduce SAVE_REGS/RESTORE_REGS We don't want to save both Fn and Dn register sets on x86-64 as they are aliased to the same arch register (XMMn). Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]` which makes a set of Cmm registers alive so that they cover all arch registers used to pass parameter, we could have Fn, Dn and XMMn alive at the same time. It made the LLVM code generator choke (see #17920). Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of registers. - - - - - 2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00 CmmToC: don't add extern decl to parsed Cmm data Previously, if a .cmm file *not in the RTS* contained something like: ```cmm section "rodata" { msg : bits8[] "Test\n"; } ``` It would get compiled by CmmToC into: ```c ERW_(msg); const char msg[] = "Test\012"; ``` and fail with: ``` /tmp/ghc32129_0/ghc_4.hc:5:12: error: error: conflicting types for \u2018msg\u2019 const char msg[] = "Test\012"; ^~~ In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error: /tmp/ghc32129_0/ghc_4.hc:4:6: error: note: previous declaration of \u2018msg\u2019 was here ERW_(msg); ^ /builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error: note: in definition of macro \u2018ERW_\u2019 #define ERW_(X) extern StgWordArray (X) ^ ``` See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes Now we don't generate these extern declarations (ERW_, etc.) for top-level data. It shouldn't change anything for the RTS (the only place we use .cmm files) as it is already special cased in `GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit extern declarations when needed. Note that it allows `cgrun069` test to pass with CmmToC (cf #15467). - - - - - 5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00 LLVM: refactor and comment register padding code (#17920) - - - - - cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Add tests for #17920 Metric Decrease: T12150 T12234 - - - - - a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00 Fix issue #18262 by zonking constraints after solving Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results. - - - - - 181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00 Fix a buglet in Simplify.simplCast This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal - - - - - 625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00 Two small tweaks to Coercion.simplifyArgsWorker These tweaks affect the inner loop of simplifyArgsWorker, which in turn is called from the flattener in Flatten.hs. This is a key perf bottleneck to T9872{a,b,c,d}. These two small changes have a modest but useful benefit. No change in functionality whatsoever. Relates to #18354 - - - - - b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00 Don't use timesInt2# with GHC < 8.11 (fix #18358) - - - - - 7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00 Fix invalid printf format - - - - - a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00 Add missing entry to freeNamesItem (#18369) - - - - - 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - dc01f455 by Matthew Pickering at 2020-11-02T09:12:19+00:00 Revert "Remove GHC.Types.Unique.Map module" This reverts commit 1c7c6f1afc8e7f7ba5d256780bc9d5bb5f3e7601. - - - - - 0d17ba6c by Matthew Pickering at 2020-11-02T14:01:07+00:00 WIP: Give each constructor allocation site a unique info table This seems to do the right thing but haven't looked at how it interacts with DWARF yet. I imagine the information is still wrong there. - - - - - 1ba64ae7 by Matthew Pickering at 2020-11-02T14:59:09+00:00 fix rebase - - - - - 18 changed files: - + .git-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/merge_request_templates/merge-request.md - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - − compiler/GHC/Builtin/Names.hs-boot - compiler/GHC/Builtin/Names/TH.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c64c90075da8f6d0ffedc1cb332c27542b5f8bde...1ba64ae7d3536b2e09fa1f2aca8e8ce1aec2af6d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c64c90075da8f6d0ffedc1cb332c27542b5f8bde...1ba64ae7d3536b2e09fa1f2aca8e8ce1aec2af6d 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 Mon Nov 2 16:58:01 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 02 Nov 2020 11:58:01 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 81 commits: Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Message-ID: <5fa03a99b3dad_7853fb626cbb5bc4641c9@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4a03ac55 by Sebastian Graf at 2020-11-02T14:04:28+01:00 tmp - - - - - 93bbe37a by Sebastian Graf at 2020-11-02T14:05:03+01:00 More stuff - - - - - 12649a26 by Sebastian Graf at 2020-11-02T14:05:04+01:00 tmp - - - - - 3c49b9c2 by Sebastian Graf at 2020-11-02T14:05:48+01:00 No more errors - - - - - 82fd4eb0 by Sebastian Graf at 2020-11-02T14:07:49+01:00 It bootstraps - - - - - 75589459 by Sebastian Graf at 2020-11-02T14:07:50+01:00 Accept some test outputs - - - - - 1e4274c7 by Sebastian Graf at 2020-11-02T14:07:50+01:00 Fix absDmd - - - - - ccf9de85 by Sebastian Graf at 2020-11-02T14:07:50+01:00 More accepted test outputs - - - - - 5b84e571 by Sebastian Graf at 2020-11-02T14:07:50+01:00 Fix oversight in lubCard - - - - - 452db8eb by Sebastian Graf at 2020-11-02T14:07:51+01:00 Accept more tests - - - - - a7dcbe4c by Sebastian Graf at 2020-11-02T14:07:51+01:00 Smart constructor for product demands - - - - - ce542c65 by Sebastian Graf at 2020-11-02T14:07:51+01:00 Unrelated pretty-printing improvement - - - - - 50d3540e by Sebastian Graf at 2020-11-02T14:07:51+01:00 typo - - - - - a4d0092c by Sebastian Graf at 2020-11-02T14:07:51+01:00 Discard absent call demands in `lub` and `plus` (#18903) Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. Whenever `g` is called, the result is used according to `cd`". Example from #18903: ``` h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` We want `1C1((1(U),S(U)))` as the demand on `g`, meaning that whenever `g` is called, its second component is used strictly. But from the first case alternative, where `g` is not called at all, we get what is effectively an absent demand, which expands to `ACA(A)`. If we blindly `lub` the A with the `(1(U),S(U))` from the other case branches, we'll get `(1(U),1(U))`, so lazy in the second component. But the `A` certainly means that the nested demands are redundant! The premise for the information they encode is not met and should be ignored, effectively treated like a bottom cardinality. Thus, when we compute the `lub` or the `plus` of such an absent demand with a proper call demand like `1C1((1(U),S(U)))`, we lub with `botCleanDmd`. Thus we get `1C1((1(U),S(U)))` as the result, not `1C1((1(U),1(U)))`, as wanted. Fixes #18903. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/87f49c7af6db5813549bdad74a53d0c3c89a3ec0...a4d0092c842ac4ea374cf3f8f8c3c7f029d21fc5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/87f49c7af6db5813549bdad74a53d0c3c89a3ec0...a4d0092c842ac4ea374cf3f8f8c3c7f029d21fc5 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 Mon Nov 2 19:04:04 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 02 Nov 2020 14:04:04 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] Fix seqDemand Message-ID: <5fa058243eab9_7853fb642408a844791be@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 187cbcfc by Sebastian Graf at 2020-11-02T20:03:57+01:00 Fix seqDemand - - - - - 1 changed file: - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -441,7 +441,7 @@ plusCard C_01 C_01 = C_0N -- The upper bound is at least 1, so upper bound of plusCard C_01 C_0N = C_0N -- the result must be 1+1 ~= N. plusCard C_0N C_01 = C_0N -- But for the lower bound we have 4 cases where plusCard C_0N C_0N = C_0N -- 0+0 ~= 0 (as opposed to 1), so we match on these. -plusCard _ _ = C_1N -- Otherwise we return topCard +plusCard _ _ = C_1N -- Otherwise we return {1,n} -- | Denotes '*' on 'Card'. multCard :: Card -> Card -> Card @@ -600,8 +600,12 @@ isUsedOnceDmd (n :* _) = isUsedOnce n -- More utility functions for strictness seqDemand :: Demand -> () -seqDemand (_ :* Prod ds) = seqDemandList ds -seqDemand _ = () +seqDemand (_ :* cd) = seqCleanDemand cd + +seqCleanDemand :: CleanDemand -> () +seqCleanDemand (Prod ds) = seqDemandList ds +seqCleanDemand (Call _ cd) = seqCleanDemand cd +seqCleanDemand (Poly _) = () seqDemandList :: [Demand] -> () seqDemandList = foldr (seq . seqDemand) () @@ -710,11 +714,11 @@ isScaleInvariantCleanDmd (Call n _) = isScaleInvariantCard n -- See Note [Scalin isWeakDmd :: Demand -> Bool isWeakDmd (n :* cd) = not (isStrict n) && isScaleInvariantCleanDmd cd -keepAliveDmdEnv :: DmdEnv -> IdSet -> DmdEnv --- (keepAliveDmdType dt vs) makes sure that the Ids in vs have --- /some/ usage in the returned demand types -- they are not Absent +-- | @keepAliveDmdType dt vs@ makes sure that the Ids in @vs@ have +-- /some/ usage in the returned demand types -- they are not Absent. -- See Note [Absence analysis for stable unfoldings and RULES] --- in GHC.Core.Opt.DmdAnal +-- in "GHC.Core.Opt.DmdAnal". +keepAliveDmdEnv :: DmdEnv -> IdSet -> DmdEnv keepAliveDmdEnv env vs = nonDetStrictFoldVarSet add env vs where @@ -802,14 +806,14 @@ lubDivergence _ _ = Dunno -- defaultFvDmd (r1 `lubDivergence` r2) = defaultFvDmd r1 `lubDmd` defaultFvDmd r2 -- (See Note [Default demand on free variables and arguments] for why) -plusDivergence :: Divergence -> Divergence -> Divergence --- See Note [Asymmetry of 'plus*'], which concludes that 'plusDivergence' needs --- to be symmetric. +-- | See Note [Asymmetry of 'plus*'], which concludes that 'plusDivergence' +-- needs to be symmetric. -- Strictly speaking, we should have @plusDivergence Dunno Diverges = ExnOrDiv at . -- But that regresses in too many places (every infinite loop, basically) to be -- worth it and is only relevant in higher-order scenarios -- (e.g. Divergence of @f (throwIO blah)@). -- So 'plusDivergence' currently is 'glbDivergence', really. +plusDivergence :: Divergence -> Divergence -> Divergence plusDivergence Dunno Dunno = Dunno plusDivergence Diverges _ = Diverges plusDivergence _ Diverges = Diverges View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/187cbcfcc1d7d34a4e84782d27c107be77f5f09e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/187cbcfcc1d7d34a4e84782d27c107be77f5f09e 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 Mon Nov 2 20:58:59 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 02 Nov 2020 15:58:59 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/bgamari/sized Message-ID: <5fa073133b71c_7853fb642c8b878490621@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/bgamari/sized at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/bgamari/sized 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 Mon Nov 2 21:05:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 02 Nov 2020 16:05:25 -0500 Subject: [Git][ghc/ghc][wip/bgamari/sized] 3 commits: CodeToByteCode: Fix handling of narrow datacon fields Message-ID: <5fa07495bdd5e_7853fb583365538493663@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bgamari/sized at Glasgow Haskell Compiler / GHC Commits: 7a15e68f by Ben Gamari at 2020-11-02T16:03:55-05:00 CodeToByteCode: Fix handling of narrow datacon fields Handle the non-word-size cases specifically and emit the appropriate bytecode instructions. - - - - - 88197dc3 by Ben Gamari at 2020-11-02T16:04:22-05:00 Constant folding for extend/narrow - - - - - 92c9c279 by Ben Gamari at 2020-11-02T16:05:15-05:00 StgToCmm: Normalize padding - - - - - 5 changed files: - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/Types/Literal.hs - testsuite/tests/simplCore/should_compile/T8832.stdout Changes: ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -199,40 +199,34 @@ primOpRules nm = \case -- coercions - Int8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int8NarrowOp primop_id - return (Var (mkPrimOpId Narrow8IntOp) `App` e) ] - Int16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int16NarrowOp primop_id - return (Var (mkPrimOpId Narrow16IntOp) `App` e) ] - Int32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int32NarrowOp primop_id - return (Var (mkPrimOpId Narrow32IntOp) `App` e) ] - Int8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int16ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt8Lit + , subsumedByPrimOp Int8NarrowOp , narrowSubsumesAnd AndIOp Int8NarrowOp 8 ] - Int16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt16Lit + , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , narrowSubsumesAnd AndIOp Int16NarrowOp 16 ] - Int32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt32Lit + , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , subsumedByPrimOp Int32NarrowOp , narrowSubsumesAnd AndIOp Int32NarrowOp 32 ] - Word8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word8NarrowOp primop_id - return (Var (mkPrimOpId Narrow8WordOp) `App` e) ] - Word16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word16NarrowOp primop_id - return (Var (mkPrimOpId Narrow16WordOp) `App` e) ] - Word32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word32NarrowOp primop_id - return (Var (mkPrimOpId Narrow32WordOp) `App` e) ] - Word8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word16ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord8Lit + , subsumedByPrimOp Word8NarrowOp , narrowSubsumesAnd AndOp Word8NarrowOp 8 ] - Word16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord16Lit + , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , narrowSubsumesAnd AndOp Word16NarrowOp 16 ] - Word32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord32Lit + , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , subsumedByPrimOp Word32NarrowOp , narrowSubsumesAnd AndOp Word32NarrowOp 32 ] ===================================== compiler/GHC/CoreToByteCode.hs ===================================== @@ -1633,30 +1633,39 @@ pushAtom d p (AnnVar var) pushAtom _ _ (AnnLit lit) = do platform <- targetPlatform <$> getDynFlags - let code rep - = let size_words = WordOff (argRepSizeW platform rep) - in return (unitOL (PUSH_UBX lit (trunc16W size_words)), - wordsToBytes platform size_words) + let code :: PrimRep -> BcM (BCInstrList, ByteOff) + code rep = + return (unitOL instr, size_bytes) + where + size_bytes = ByteOff $ primRepSizeB platform rep + -- Here we handle the non-word-width cases specifically since we + -- must emit different bytecode for them. + instr = + case size_bytes of + 1 -> PUSH_UBX8 lit + 2 -> PUSH_UBX16 lit + 4 -> PUSH_UBX32 lit + _ -> PUSH_UBX lit (trunc16W $ bytesToWords platform size_bytes) case lit of - LitLabel _ _ _ -> code N - LitFloat _ -> code F - LitDouble _ -> code D - LitChar _ -> code N - LitNullAddr -> code N - LitString _ -> code N - LitRubbish -> code N + LitLabel _ _ _ -> code AddrRep + LitFloat _ -> code FloatRep + LitDouble _ -> code DoubleRep + LitChar _ -> code WordRep + LitNullAddr -> code AddrRep + LitString _ -> code AddrRep + LitRubbish -> code WordRep LitNumber nt _ -> case nt of - LitNumInt -> code N - LitNumWord -> code N - LitNumInt8 -> code (toArgRep Int8Rep) - LitNumWord8 -> code (toArgRep Word8Rep) - LitNumInt16 -> code (toArgRep Int16Rep) - LitNumWord16 -> code (toArgRep Word16Rep) - LitNumInt32 -> code (toArgRep Int32Rep) - LitNumWord32 -> code (toArgRep Word32Rep) - LitNumInt64 -> code L - LitNumWord64 -> code L + LitNumInt -> code IntRep + LitNumWord -> code WordRep + LitNumInt8 -> code Int8Rep + LitNumWord8 -> code Word8Rep + LitNumInt16 -> code Int16Rep + LitNumWord16 -> code Word16Rep + LitNumInt32 -> code Int32Rep + LitNumWord32 -> code Word32Rep + LitNumInt64 -> code Int64Rep + LitNumWord64 -> code Word64Rep -- No LitInteger's or LitNatural's should be left by the time this is -- called. CorePrep should have converted them all to a real core -- representation. ===================================== compiler/GHC/StgToCmm/DataCon.hs ===================================== @@ -102,6 +102,21 @@ cgTopRhsCon dflags id con args nv_args_w_offsets) = mkVirtHeapOffsetsWithPadding profile StdHeader (addArgReps args) + ; let + -- Decompose padding into units of length 8, 4, 2, or 1 bytes to + -- allow the implementation of mk_payload to use widthFromBytes, + -- which only handles these cases. + fix_padding (x@(Padding n off) : rest) + | n == 0 = fix_padding rest + | n `elem` [1,2,4,8] = x : fix_padding rest + | n > 8 = add_pad 8 + | n > 4 = add_pad 4 + | n > 2 = add_pad 2 + | otherwise = add_pad 1 + where add_pad m = Padding m off : fix_padding (Padding (n-m) (off+m) : rest) + fix_padding (x : rest) = x : fix_padding rest + fix_padding [] = [] + mk_payload (Padding len _) = return (CmmInt 0 (widthFromBytes len)) mk_payload (FieldOff arg _) = do amode <- getArgAmode arg @@ -117,7 +132,7 @@ cgTopRhsCon dflags id con args info_tbl = mkDataConInfoTable profile con True ptr_wds nonptr_wds - ; payload <- mapM mk_payload nv_args_w_offsets + ; payload <- mapM mk_payload (fix_padding nv_args_w_offsets) -- NB1: nv_args_w_offsets is sorted into ptrs then non-ptrs -- NB2: all the amodes should be Lits! -- TODO (osa): Why? ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -46,9 +46,11 @@ module GHC.Types.Literal -- ** Coercions , wordToIntLit, intToWordLit - , narrowLit , narrow8IntLit, narrow16IntLit, narrow32IntLit , narrow8WordLit, narrow16WordLit, narrow32WordLit + , narrowInt8Lit, narrowInt16Lit, narrowInt32Lit + , narrowWord8Lit, narrowWord16Lit, narrowWord32Lit + , extendIntLit, extendWordLit , int8Lit, int16Lit, int32Lit , word8Lit, word16Lit, word32Lit , charToIntLit, intToCharLit @@ -614,16 +616,31 @@ intToWordLit platform (LitNumber LitNumInt i) intToWordLit _ l = pprPanic "intToWordLit" (ppr l) -- | Narrow a literal number (unchecked result range) -narrowLit :: forall a. Integral a => Proxy a -> Literal -> Literal -narrowLit _ (LitNumber nt i) = LitNumber nt (toInteger (fromInteger i :: a)) -narrowLit _ l = pprPanic "narrowLit" (ppr l) - -narrow8IntLit = narrowLit (Proxy :: Proxy Int8) -narrow16IntLit = narrowLit (Proxy :: Proxy Int16) -narrow32IntLit = narrowLit (Proxy :: Proxy Int32) -narrow8WordLit = narrowLit (Proxy :: Proxy Word8) -narrow16WordLit = narrowLit (Proxy :: Proxy Word16) -narrow32WordLit = narrowLit (Proxy :: Proxy Word32) +narrowLit' :: forall a. Integral a => Proxy a -> LitNumType -> Literal -> Literal +narrowLit' _ nt' (LitNumber nt i) = LitNumber nt' (toInteger (fromInteger i :: a)) +narrowLit' _ nt' l = pprPanic "narrowLit" (ppr l) + +narrow8IntLit = narrowLit' (Proxy :: Proxy Int8) LitNumInt +narrow16IntLit = narrowLit' (Proxy :: Proxy Int16) LitNumInt +narrow32IntLit = narrowLit' (Proxy :: Proxy Int32) LitNumInt +narrow8WordLit = narrowLit' (Proxy :: Proxy Word8) LitNumWord +narrow16WordLit = narrowLit' (Proxy :: Proxy Word16) LitNumWord +narrow32WordLit = narrowLit' (Proxy :: Proxy Word32) LitNumWord + +narrowInt8Lit = narrowLit' (Proxy :: Proxy Int8) LitNumInt8 +narrowInt16Lit = narrowLit' (Proxy :: Proxy Int16) LitNumInt16 +narrowInt32Lit = narrowLit' (Proxy :: Proxy Int32) LitNumInt32 +narrowWord8Lit = narrowLit' (Proxy :: Proxy Word8) LitNumWord8 +narrowWord16Lit = narrowLit' (Proxy :: Proxy Word16) LitNumWord16 +narrowWord32Lit = narrowLit' (Proxy :: Proxy Word32) LitNumWord32 + +-- | Extend a fixed-width literal (e.g. 'Int16#') to a word-sized literal (e.g. +-- 'Int#'). +extendWordLit, extendIntLit :: Platform -> Literal -> Literal +extendWordLit platform (LitNumber _nt i) = mkLitWord platform i +extendWordLit platform l = pprPanic "extendWordLit" (ppr l) +extendIntLit platform (LitNumber _nt i) = mkLitInt platform i +extendIntLit platform l = pprPanic "extendIntLit" (ppr l) int8Lit (LitNumber _ i) = mkLitInt8 i int8Lit l = pprPanic "int8Lit" (ppr l) ===================================== testsuite/tests/simplCore/should_compile/T8832.stdout ===================================== @@ -1,11 +1,11 @@ i = GHC.Types.I# 0# -i8 = GHC.Int.I8# (GHC.Prim.narrowInt8# 0#) -i16 = GHC.Int.I16# (GHC.Prim.narrowInt16# 0#) -i32 = GHC.Int.I32# (GHC.Prim.narrowInt32# 0#) +i8 = GHC.Int.I8# 0#8 +i16 = GHC.Int.I16# 0#16 +i32 = GHC.Int.I32# 0#32 i64 = GHC.Int.I64# 0# w = GHC.Types.W# 0## -w8 = GHC.Word.W8# (GHC.Prim.narrowWord8# 0##) -w16 = GHC.Word.W16# (GHC.Prim.narrowWord16# 0##) -w32 = GHC.Word.W32# (GHC.Prim.narrowWord32# 0##) +w8 = GHC.Word.W8# 0##8 +w16 = GHC.Word.W16# 0##16 +w32 = GHC.Word.W32# 0##32 w64 = GHC.Word.W64# 0## z = 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/001378cb146868d220c8f55b43251d3b7d71ddd1...92c9c27937704e8e1aea19a12ae01b4eeb268964 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/001378cb146868d220c8f55b43251d3b7d71ddd1...92c9c27937704e8e1aea19a12ae01b4eeb268964 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 Mon Nov 2 23:02:41 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Mon, 02 Nov 2020 18:02:41 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Subtleties in Note [Instance and Given overlap] Message-ID: <5fa09011d6fe3_785f5f2fa852651e@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: ebfebd6f by Richard Eisenberg at 2020-11-02T18:02:22-05:00 Subtleties in Note [Instance and Given overlap] - - - - - 7 changed files: - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Interact.hs - compiler/GHC/Tc/Solver/Monad.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Map/Type.hs ===================================== @@ -8,6 +8,9 @@ {-# LANGUAGE TypeFamilies #-} module GHC.Core.Map.Type ( + -- * Re-export generic interface + TrieMap(..), + -- * Maps over 'Type's TypeMap, emptyTypeMap, extendTypeMap, lookupTypeMap, foldTypeMap, LooseTypeMap, ===================================== compiler/GHC/Core/TyCo/FVs.hs ===================================== @@ -26,7 +26,8 @@ module GHC.Core.TyCo.FVs injectiveVarsOfType, injectiveVarsOfTypes, invisibleVarsOfType, invisibleVarsOfTypes, - -- No Free vars + -- Any and No Free vars + anyFreeVarsOfType, anyFreeVarsOfTypes, anyFreeVarsOfCo, noFreeVarsOfType, noFreeVarsOfTypes, noFreeVarsOfCo, -- * Well-scoped free variables @@ -47,7 +48,7 @@ import GHC.Prelude import {-# SOURCE #-} GHC.Core.Type (coreView, partitionInvisibleTypes) -import Data.Monoid as DM ( Endo(..), All(..) ) +import Data.Monoid as DM ( Endo(..), Any(..) ) import GHC.Core.TyCo.Rep import GHC.Core.TyCon import GHC.Types.Var @@ -855,32 +856,43 @@ invisibleVarsOfTypes = mapUnionFV invisibleVarsOfType {- ********************************************************************* * * - No free vars + Any free vars * * ********************************************************************* -} -nfvFolder :: TyCoFolder TyCoVarSet DM.All -nfvFolder = TyCoFolder { tcf_view = noView - , tcf_tyvar = do_tcv, tcf_covar = do_tcv - , tcf_hole = do_hole, tcf_tycobinder = do_bndr } +{-# INLINE afvFolder #-} -- so that specialization to (const True) works +afvFolder :: (TyCoVar -> Bool) -> TyCoFolder TyCoVarSet DM.Any +afvFolder check_fv = TyCoFolder { tcf_view = noView + , tcf_tyvar = do_tcv, tcf_covar = do_tcv + , tcf_hole = do_hole, tcf_tycobinder = do_bndr } where - do_tcv is tv = All (tv `elemVarSet` is) - do_hole _ _ = All True -- I'm unsure; probably never happens + do_tcv is tv = Any (not (tv `elemVarSet` is) && check_fv tv) + do_hole _ _ = Any False -- I'm unsure; probably never happens do_bndr is tv _ = is `extendVarSet` tv -nfv_ty :: Type -> DM.All -nfv_tys :: [Type] -> DM.All -nfv_co :: Coercion -> DM.All -(nfv_ty, nfv_tys, nfv_co, _) = foldTyCo nfvFolder emptyVarSet +anyFreeVarsOfType :: (TyCoVar -> Bool) -> Type -> Bool +anyFreeVarsOfType check_fv ty = DM.getAny (f ty) + where (f, _, _, _) = foldTyCo (afvFolder check_fv) emptyVarSet + +anyFreeVarsOfTypes :: (TyCoVar -> Bool) -> [Type] -> Bool +anyFreeVarsOfTypes check_fv tys = DM.getAny (f tys) + where (_, f, _, _) = foldTyCo (afvFolder check_fv) emptyVarSet + +anyFreeVarsOfCo :: (TyCoVar -> Bool) -> Coercion -> Bool +anyFreeVarsOfCo check_fv co = DM.getAny (f co) + where (_, _, f, _) = foldTyCo (afvFolder check_fv) emptyVarSet noFreeVarsOfType :: Type -> Bool -noFreeVarsOfType ty = DM.getAll (nfv_ty ty) +noFreeVarsOfType ty = not $ DM.getAny (f ty) + where (f, _, _, _) = foldTyCo (afvFolder (const True)) emptyVarSet noFreeVarsOfTypes :: [Type] -> Bool -noFreeVarsOfTypes tys = DM.getAll (nfv_tys tys) +noFreeVarsOfTypes tys = not $ DM.getAny (f tys) + where (_, f, _, _) = foldTyCo (afvFolder (const True)) emptyVarSet noFreeVarsOfCo :: Coercion -> Bool -noFreeVarsOfCo co = getAll (nfv_co co) +noFreeVarsOfCo co = not $ DM.getAny (f co) + where (_, _, f, _) = foldTyCo (afvFolder (const True)) emptyVarSet {- ********************************************************************* @@ -983,4 +995,3 @@ tyCoVarsOfTypeWellScoped = scopedSort . tyCoVarsOfTypeList -- | Get the free vars of types in scoped order tyCoVarsOfTypesWellScoped :: [Type] -> [TyVar] tyCoVarsOfTypesWellScoped = scopedSort . tyCoVarsOfTypesList - ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -156,6 +156,7 @@ module GHC.Core.Type ( coVarsOfType, coVarsOfTypes, + anyFreeVarsOfType, noFreeVarsOfType, splitVisVarsOfType, splitVisVarsOfTypes, expandTypeSynonyms, ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -24,7 +24,7 @@ module GHC.Core.Unify ( liftCoMatch, -- The core flattening algorithm - flattenTys + flattenTys, flattenTysX ) where #include "HsVersions.h" @@ -1806,12 +1806,17 @@ updateInScopeSet env upd = env { fe_in_scope = upd (fe_in_scope env) } flattenTys :: InScopeSet -> [Type] -> [Type] -- See Note [Flattening] --- NB: the returned types may mention fresh type variables, --- arising from the flattening. We don't return the +flattenTys in_scope tys = fst (flattenTysX in_scope tys) + +flattenTysX :: InScopeSet -> [Type] -> ([Type], TyVarSet) +-- See Note [Flattening] +-- NB: the returned types mention the fresh type variables +-- in the returned set. We don't return the -- mapping from those fresh vars to the ty-fam -- applications they stand for (we could, but no need) -flattenTys in_scope tys - = snd $ coreFlattenTys emptyTvSubstEnv (emptyFlattenEnv in_scope) tys +flattenTysX in_scope tys + = let (env, result) = coreFlattenTys emptyTvSubstEnv (emptyFlattenEnv in_scope) tys in + (result, foldTM (flip extendVarSet) (fe_type_map env) emptyVarSet) coreFlattenTys :: TvSubstEnv -> FlattenEnv -> [Type] -> (FlattenEnv, [Type]) ===================================== compiler/GHC/Tc/Solver/Interact.hs ===================================== @@ -2116,12 +2116,7 @@ Other notes: - natural numbers - Typeable -* Flatten-skolems: we do not treat a flatten-skolem as unifiable - for this purpose. - E.g. f :: Eq (F a) => [a] -> [a] - f xs = ....(xs==xs)..... - Here we get [W] Eq [a], and we don't want to refrain from solving - it because of the given (Eq (F a)) constraint! +* See also Note [What might match later?] in GHC.Tc.Solver.Monad. * The given-overlap problem is arguably not easy to appear in practice due to our aggressive prioritization of equality solving over other ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -2124,10 +2124,31 @@ matchableGivens loc_w pred_w (IS { inert_cans = inert_cans }) = False mightMatchLater :: TcPredType -> CtLoc -> TcPredType -> CtLoc -> Bool +-- See Note [What might match later?] mightMatchLater given_pred given_loc wanted_pred wanted_loc - = not (prohibitedSuperClassSolve given_loc wanted_loc) - && isJust (tcUnifyTys bind_meta_tv [given_pred] [wanted_pred]) + | prohibitedSuperClassSolve given_loc wanted_loc + = False + + | SurelyApart <- tcUnifyTysFG bind_meta_tv flattened_given flattened_wanted + = False + + | otherwise + = True -- safe answer where + given_in_scope = mkInScopeSet $ tyCoVarsOfType given_pred + wanted_in_scope = mkInScopeSet $ tyCoVarsOfType wanted_pred + + (flattened_given, given_vars) + | anyFreeVarsOfType isMetaTyVar given_pred + = flattenTysX given_in_scope [given_pred] + | otherwise + = ([given_pred], emptyVarSet) + + (flattened_wanted, wanted_vars) + = flattenTysX wanted_in_scope [wanted_pred] + + all_flat_vars = given_vars `unionVarSet` wanted_vars + bind_meta_tv :: TcTyVar -> BindFlag -- Any meta tyvar may be unified later, so we treat it as -- bindable when unifying with givens. That ensures that we @@ -2135,8 +2156,12 @@ mightMatchLater given_pred given_loc wanted_pred wanted_loc -- something that matches the 'given', until demonstrated -- otherwise. More info in Note [Instance and Given overlap] -- in GHC.Tc.Solver.Interact - bind_meta_tv tv | isMetaTyVar tv = BindMe - | otherwise = Skolem + bind_meta_tv tv | isMetaTyVar tv + , not (isCycleBreakerTyVar tv) = BindMe + -- a cycle-breaker var really stands for a type family + -- application where all variables are skolems + | tv `elemVarSet` all_flat_vars = BindMe + | otherwise = Skolem prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool -- See Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance @@ -2154,6 +2179,39 @@ because it is a candidate for floating out of this implication. We only float equalities with a meta-tyvar on the left, so we only pull those out here. +Note [What might match later?] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We must determine whether a Given might later match a Wanted. We +definitely need to account for the possibility that any metavariable +in the Wanted might be arbitrarily instantiated. We do *not* want +to allow skolems in the Given to be instantiated. But what about +type family applications? + +We break this down into two cases: a type family application in the +Given, and a type family application in the Wanted. + +* Given: Before ever looking at Wanteds, we process and simplify all +the Givens. So any type family applications in a Given have already +been fully reduced. Furthermore, future Wanteds won't rewrite Givens, +so information we learn later can't come to bear. So we worry about +reduction of a type family application in a Given only when it has +an metavariable in it (necessarily unfilled, because these types +have been zonked before getting here). A Given with a metavariable +is rare, but it can happen. See typecheck/should_compile/InstanceGivenOverlap2, +which uses partial type signatures and polykinds to pull it off. + +* Wanted: Unlike the Given case, a type family application in a +Wanted is always a cause for concern. Further information might allow +it to reduce, so we want to say that a type family application could +unify with any type. + +How we do this: we use the *core* flattener, as defined in the +flattenTys function. See Note [Flattening] in GHC.Core.Unify. This +function takes any type family application and turns it into a fresh +variable. These fresh variables must be flagged with BindMe in the +bind_meta_tv function, so that the unifier will match them. This +is the only reason we need to collect them here. + Note [When does an implication have given equalities?] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider an implication ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -723,3 +723,6 @@ test('T18470', normal, compile, ['']) test('T18323', normal, compile, ['']) test('T18585', normal, compile, ['']) test('T15942', normal, compile, ['']) +test('CbvOverlap', normal, compile, ['']) +test('InstanceGivenOverlap', normal, compile, ['']) +test('InstanceGivenOverlap2', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ebfebd6fd6e6407bc0c8ad81d31616b76fc8ce3d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ebfebd6fd6e6407bc0c8ad81d31616b76fc8ce3d 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 Mon Nov 2 23:15:07 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 18:15:07 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: testsuite: Add --top flag to driver Message-ID: <5fa092fb8ebc0_785d7790cc533427@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 8ff95f7e by GHC GitLab CI at 2020-11-02T18:14:57-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 71110975 by Ben Gamari at 2020-11-02T18:14:58-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - aa43281e by David Eichmann at 2020-11-02T18:14:58-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 3889281e by Ryan Scott at 2020-11-02T18:14:59-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - 87d6dfe4 by Simon Peyton Jones at 2020-11-02T18:14:59-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 2dc83580 by Ben Gamari at 2020-11-02T18:15:00-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/ffi.rst - hadrian/src/Builder.hs - hadrian/src/Settings/Builders/RunTest.hs - includes/RtsAPI.h - includes/rts/Threads.h - rts/Capability.c - rts/RtsAPI.c - rts/Schedule.c - rts/Task.c - rts/Task.h - rts/sm/NonMoving.c - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - testsuite/tests/callarity/unittest/CallArity1.hs - + testsuite/tests/ghci/scripts/T13795.script - + testsuite/tests/ghci/scripts/T13795.stdout - + testsuite/tests/ghci/scripts/T18828.hs - + testsuite/tests/ghci/scripts/T18828.script - + testsuite/tests/ghci/scripts/T18828.stdout - testsuite/tests/ghci/scripts/all.T - testsuite/tests/rts/T5423.hs - testsuite/tests/rts/T5423.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/737d467ffc0200dbe173ccd345a16fc3d8e1bac3...2dc835801c5bb0eba9fb8e55874e2cb1876a8f4c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/737d467ffc0200dbe173ccd345a16fc3d8e1bac3...2dc835801c5bb0eba9fb8e55874e2cb1876a8f4c 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 Tue Nov 3 00:39:08 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 02 Nov 2020 19:39:08 -0500 Subject: [Git][ghc/ghc][wip/bgamari/sized] 2 commits: Constant folding for extend/narrow Message-ID: <5fa0a6acd40bd_7853fb65d83220c543049@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bgamari/sized at Glasgow Haskell Compiler / GHC Commits: f6fb87a1 by Ben Gamari at 2020-11-02T19:39:00-05:00 Constant folding for extend/narrow - - - - - 41ee3db9 by Ben Gamari at 2020-11-02T19:39:00-05:00 StgToCmm: Normalize padding - - - - - 4 changed files: - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/Types/Literal.hs - testsuite/tests/simplCore/should_compile/T8832.stdout Changes: ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -199,40 +199,34 @@ primOpRules nm = \case -- coercions - Int8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int8NarrowOp primop_id - return (Var (mkPrimOpId Narrow8IntOp) `App` e) ] - Int16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int16NarrowOp primop_id - return (Var (mkPrimOpId Narrow16IntOp) `App` e) ] - Int32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int32NarrowOp primop_id - return (Var (mkPrimOpId Narrow32IntOp) `App` e) ] - Int8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int16ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt8Lit + , subsumedByPrimOp Int8NarrowOp , narrowSubsumesAnd AndIOp Int8NarrowOp 8 ] - Int16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt16Lit + , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , narrowSubsumesAnd AndIOp Int16NarrowOp 16 ] - Int32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt32Lit + , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , subsumedByPrimOp Int32NarrowOp , narrowSubsumesAnd AndIOp Int32NarrowOp 32 ] - Word8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word8NarrowOp primop_id - return (Var (mkPrimOpId Narrow8WordOp) `App` e) ] - Word16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word16NarrowOp primop_id - return (Var (mkPrimOpId Narrow16WordOp) `App` e) ] - Word32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word32NarrowOp primop_id - return (Var (mkPrimOpId Narrow32WordOp) `App` e) ] - Word8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word16ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord8Lit + , subsumedByPrimOp Word8NarrowOp , narrowSubsumesAnd AndOp Word8NarrowOp 8 ] - Word16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord16Lit + , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , narrowSubsumesAnd AndOp Word16NarrowOp 16 ] - Word32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord32Lit + , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , subsumedByPrimOp Word32NarrowOp , narrowSubsumesAnd AndOp Word32NarrowOp 32 ] ===================================== compiler/GHC/StgToCmm/DataCon.hs ===================================== @@ -102,6 +102,21 @@ cgTopRhsCon dflags id con args nv_args_w_offsets) = mkVirtHeapOffsetsWithPadding profile StdHeader (addArgReps args) + ; let + -- Decompose padding into units of length 8, 4, 2, or 1 bytes to + -- allow the implementation of mk_payload to use widthFromBytes, + -- which only handles these cases. + fix_padding (x@(Padding n off) : rest) + | n == 0 = fix_padding rest + | n `elem` [1,2,4,8] = x : fix_padding rest + | n > 8 = add_pad 8 + | n > 4 = add_pad 4 + | n > 2 = add_pad 2 + | otherwise = add_pad 1 + where add_pad m = Padding m off : fix_padding (Padding (n-m) (off+m) : rest) + fix_padding (x : rest) = x : fix_padding rest + fix_padding [] = [] + mk_payload (Padding len _) = return (CmmInt 0 (widthFromBytes len)) mk_payload (FieldOff arg _) = do amode <- getArgAmode arg @@ -117,7 +132,7 @@ cgTopRhsCon dflags id con args info_tbl = mkDataConInfoTable profile con True ptr_wds nonptr_wds - ; payload <- mapM mk_payload nv_args_w_offsets + ; payload <- mapM mk_payload (fix_padding nv_args_w_offsets) -- NB1: nv_args_w_offsets is sorted into ptrs then non-ptrs -- NB2: all the amodes should be Lits! -- TODO (osa): Why? ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -46,9 +46,11 @@ module GHC.Types.Literal -- ** Coercions , wordToIntLit, intToWordLit - , narrowLit , narrow8IntLit, narrow16IntLit, narrow32IntLit , narrow8WordLit, narrow16WordLit, narrow32WordLit + , narrowInt8Lit, narrowInt16Lit, narrowInt32Lit + , narrowWord8Lit, narrowWord16Lit, narrowWord32Lit + , extendIntLit, extendWordLit , int8Lit, int16Lit, int32Lit , word8Lit, word16Lit, word32Lit , charToIntLit, intToCharLit @@ -614,16 +616,33 @@ intToWordLit platform (LitNumber LitNumInt i) intToWordLit _ l = pprPanic "intToWordLit" (ppr l) -- | Narrow a literal number (unchecked result range) -narrowLit :: forall a. Integral a => Proxy a -> Literal -> Literal -narrowLit _ (LitNumber nt i) = LitNumber nt (toInteger (fromInteger i :: a)) -narrowLit _ l = pprPanic "narrowLit" (ppr l) - -narrow8IntLit = narrowLit (Proxy :: Proxy Int8) -narrow16IntLit = narrowLit (Proxy :: Proxy Int16) -narrow32IntLit = narrowLit (Proxy :: Proxy Int32) -narrow8WordLit = narrowLit (Proxy :: Proxy Word8) -narrow16WordLit = narrowLit (Proxy :: Proxy Word16) -narrow32WordLit = narrowLit (Proxy :: Proxy Word32) +narrowLit' :: forall a. Integral a => Proxy a -> LitNumType -> Literal -> Literal +narrowLit' _ nt' (LitNumber _ i) = LitNumber nt' (toInteger (fromInteger i :: a)) +narrowLit' _ _ l = pprPanic "narrowLit" (ppr l) + +narrow8IntLit = narrowLit' (Proxy :: Proxy Int8) LitNumInt +narrow16IntLit = narrowLit' (Proxy :: Proxy Int16) LitNumInt +narrow32IntLit = narrowLit' (Proxy :: Proxy Int32) LitNumInt +narrow8WordLit = narrowLit' (Proxy :: Proxy Word8) LitNumWord +narrow16WordLit = narrowLit' (Proxy :: Proxy Word16) LitNumWord +narrow32WordLit = narrowLit' (Proxy :: Proxy Word32) LitNumWord + +narrowInt8Lit, narrowInt16Lit, narrowInt32Lit, + narrowWord8Lit, narrowWord16Lit, narrowWord32Lit :: Literal -> Literal +narrowInt8Lit = narrowLit' (Proxy :: Proxy Int8) LitNumInt8 +narrowInt16Lit = narrowLit' (Proxy :: Proxy Int16) LitNumInt16 +narrowInt32Lit = narrowLit' (Proxy :: Proxy Int32) LitNumInt32 +narrowWord8Lit = narrowLit' (Proxy :: Proxy Word8) LitNumWord8 +narrowWord16Lit = narrowLit' (Proxy :: Proxy Word16) LitNumWord16 +narrowWord32Lit = narrowLit' (Proxy :: Proxy Word32) LitNumWord32 + +-- | Extend a fixed-width literal (e.g. 'Int16#') to a word-sized literal (e.g. +-- 'Int#'). +extendWordLit, extendIntLit :: Platform -> Literal -> Literal +extendWordLit platform (LitNumber _nt i) = mkLitWord platform i +extendWordLit _platform l = pprPanic "extendWordLit" (ppr l) +extendIntLit platform (LitNumber _nt i) = mkLitInt platform i +extendIntLit _platform l = pprPanic "extendIntLit" (ppr l) int8Lit (LitNumber _ i) = mkLitInt8 i int8Lit l = pprPanic "int8Lit" (ppr l) ===================================== testsuite/tests/simplCore/should_compile/T8832.stdout ===================================== @@ -1,11 +1,11 @@ i = GHC.Types.I# 0# -i8 = GHC.Int.I8# (GHC.Prim.narrowInt8# 0#) -i16 = GHC.Int.I16# (GHC.Prim.narrowInt16# 0#) -i32 = GHC.Int.I32# (GHC.Prim.narrowInt32# 0#) +i8 = GHC.Int.I8# 0#8 +i16 = GHC.Int.I16# 0#16 +i32 = GHC.Int.I32# 0#32 i64 = GHC.Int.I64# 0# w = GHC.Types.W# 0## -w8 = GHC.Word.W8# (GHC.Prim.narrowWord8# 0##) -w16 = GHC.Word.W16# (GHC.Prim.narrowWord16# 0##) -w32 = GHC.Word.W32# (GHC.Prim.narrowWord32# 0##) +w8 = GHC.Word.W8# 0##8 +w16 = GHC.Word.W16# 0##16 +w32 = GHC.Word.W32# 0##32 w64 = GHC.Word.W64# 0## z = 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92c9c27937704e8e1aea19a12ae01b4eeb268964...41ee3db93a80125162d66a756d43c6f4854d1613 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92c9c27937704e8e1aea19a12ae01b4eeb268964...41ee3db93a80125162d66a756d43c6f4854d1613 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 Tue Nov 3 01:49:40 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 20:49:40 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 4 commits: CodeToByteCode: Fix handling of narrow datacon fields Message-ID: <5fa0b7345b0f8_7853fb642f51c4c559916@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 7a15e68f by Ben Gamari at 2020-11-02T16:03:55-05:00 CodeToByteCode: Fix handling of narrow datacon fields Handle the non-word-size cases specifically and emit the appropriate bytecode instructions. - - - - - f6fb87a1 by Ben Gamari at 2020-11-02T19:39:00-05:00 Constant folding for extend/narrow - - - - - 41ee3db9 by Ben Gamari at 2020-11-02T19:39:00-05:00 StgToCmm: Normalize padding - - - - - 0c51530e by Moritz Angermann at 2020-11-03T01:49:08+00:00 Merge remote-tracking branch 'origin/wip/bgamari/sized' into wip/angerman/sized - - - - - 5 changed files: - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/Types/Literal.hs - testsuite/tests/simplCore/should_compile/T8832.stdout Changes: ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -199,40 +199,34 @@ primOpRules nm = \case -- coercions - Int8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int8NarrowOp primop_id - return (Var (mkPrimOpId Narrow8IntOp) `App` e) ] - Int16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int16NarrowOp primop_id - return (Var (mkPrimOpId Narrow16IntOp) `App` e) ] - Int32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Int32NarrowOp primop_id - return (Var (mkPrimOpId Narrow32IntOp) `App` e) ] - Int8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int16ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] + Int8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt8Lit + , subsumedByPrimOp Int8NarrowOp , narrowSubsumesAnd AndIOp Int8NarrowOp 8 ] - Int16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt16Lit + , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , narrowSubsumesAnd AndIOp Int16NarrowOp 16 ] - Int32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Int8NarrowOp + Int32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt32Lit + , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , subsumedByPrimOp Int32NarrowOp , narrowSubsumesAnd AndIOp Int32NarrowOp 32 ] - Word8ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word8NarrowOp primop_id - return (Var (mkPrimOpId Narrow8WordOp) `App` e) ] - Word16ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word16NarrowOp primop_id - return (Var (mkPrimOpId Narrow16WordOp) `App` e) ] - Word32ExtendOp -> mkPrimOpRule nm 1 [ do [Var primop_id `App` e] <- getArgs - matchPrimOpId Word32NarrowOp primop_id - return (Var (mkPrimOpId Narrow32WordOp) `App` e) ] - Word8NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word16ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit ] + Word8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord8Lit + , subsumedByPrimOp Word8NarrowOp , narrowSubsumesAnd AndOp Word8NarrowOp 8 ] - Word16NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord16Lit + , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , narrowSubsumesAnd AndOp Word16NarrowOp 16 ] - Word32NarrowOp -> mkPrimOpRule nm 1 [ subsumedByPrimOp Word8NarrowOp + Word32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord32Lit + , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , subsumedByPrimOp Word32NarrowOp , narrowSubsumesAnd AndOp Word32NarrowOp 32 ] ===================================== compiler/GHC/CoreToByteCode.hs ===================================== @@ -1633,30 +1633,39 @@ pushAtom d p (AnnVar var) pushAtom _ _ (AnnLit lit) = do platform <- targetPlatform <$> getDynFlags - let code rep - = let size_words = WordOff (argRepSizeW platform rep) - in return (unitOL (PUSH_UBX lit (trunc16W size_words)), - wordsToBytes platform size_words) + let code :: PrimRep -> BcM (BCInstrList, ByteOff) + code rep = + return (unitOL instr, size_bytes) + where + size_bytes = ByteOff $ primRepSizeB platform rep + -- Here we handle the non-word-width cases specifically since we + -- must emit different bytecode for them. + instr = + case size_bytes of + 1 -> PUSH_UBX8 lit + 2 -> PUSH_UBX16 lit + 4 -> PUSH_UBX32 lit + _ -> PUSH_UBX lit (trunc16W $ bytesToWords platform size_bytes) case lit of - LitLabel _ _ _ -> code N - LitFloat _ -> code F - LitDouble _ -> code D - LitChar _ -> code N - LitNullAddr -> code N - LitString _ -> code N - LitRubbish -> code N + LitLabel _ _ _ -> code AddrRep + LitFloat _ -> code FloatRep + LitDouble _ -> code DoubleRep + LitChar _ -> code WordRep + LitNullAddr -> code AddrRep + LitString _ -> code AddrRep + LitRubbish -> code WordRep LitNumber nt _ -> case nt of - LitNumInt -> code N - LitNumWord -> code N - LitNumInt8 -> code (toArgRep Int8Rep) - LitNumWord8 -> code (toArgRep Word8Rep) - LitNumInt16 -> code (toArgRep Int16Rep) - LitNumWord16 -> code (toArgRep Word16Rep) - LitNumInt32 -> code (toArgRep Int32Rep) - LitNumWord32 -> code (toArgRep Word32Rep) - LitNumInt64 -> code L - LitNumWord64 -> code L + LitNumInt -> code IntRep + LitNumWord -> code WordRep + LitNumInt8 -> code Int8Rep + LitNumWord8 -> code Word8Rep + LitNumInt16 -> code Int16Rep + LitNumWord16 -> code Word16Rep + LitNumInt32 -> code Int32Rep + LitNumWord32 -> code Word32Rep + LitNumInt64 -> code Int64Rep + LitNumWord64 -> code Word64Rep -- No LitInteger's or LitNatural's should be left by the time this is -- called. CorePrep should have converted them all to a real core -- representation. ===================================== compiler/GHC/StgToCmm/DataCon.hs ===================================== @@ -102,6 +102,21 @@ cgTopRhsCon dflags id con args nv_args_w_offsets) = mkVirtHeapOffsetsWithPadding profile StdHeader (addArgReps args) + ; let + -- Decompose padding into units of length 8, 4, 2, or 1 bytes to + -- allow the implementation of mk_payload to use widthFromBytes, + -- which only handles these cases. + fix_padding (x@(Padding n off) : rest) + | n == 0 = fix_padding rest + | n `elem` [1,2,4,8] = x : fix_padding rest + | n > 8 = add_pad 8 + | n > 4 = add_pad 4 + | n > 2 = add_pad 2 + | otherwise = add_pad 1 + where add_pad m = Padding m off : fix_padding (Padding (n-m) (off+m) : rest) + fix_padding (x : rest) = x : fix_padding rest + fix_padding [] = [] + mk_payload (Padding len _) = return (CmmInt 0 (widthFromBytes len)) mk_payload (FieldOff arg _) = do amode <- getArgAmode arg @@ -117,7 +132,7 @@ cgTopRhsCon dflags id con args info_tbl = mkDataConInfoTable profile con True ptr_wds nonptr_wds - ; payload <- mapM mk_payload nv_args_w_offsets + ; payload <- mapM mk_payload (fix_padding nv_args_w_offsets) -- NB1: nv_args_w_offsets is sorted into ptrs then non-ptrs -- NB2: all the amodes should be Lits! -- TODO (osa): Why? ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -46,9 +46,11 @@ module GHC.Types.Literal -- ** Coercions , wordToIntLit, intToWordLit - , narrowLit , narrow8IntLit, narrow16IntLit, narrow32IntLit , narrow8WordLit, narrow16WordLit, narrow32WordLit + , narrowInt8Lit, narrowInt16Lit, narrowInt32Lit + , narrowWord8Lit, narrowWord16Lit, narrowWord32Lit + , extendIntLit, extendWordLit , int8Lit, int16Lit, int32Lit , word8Lit, word16Lit, word32Lit , charToIntLit, intToCharLit @@ -614,16 +616,33 @@ intToWordLit platform (LitNumber LitNumInt i) intToWordLit _ l = pprPanic "intToWordLit" (ppr l) -- | Narrow a literal number (unchecked result range) -narrowLit :: forall a. Integral a => Proxy a -> Literal -> Literal -narrowLit _ (LitNumber nt i) = LitNumber nt (toInteger (fromInteger i :: a)) -narrowLit _ l = pprPanic "narrowLit" (ppr l) - -narrow8IntLit = narrowLit (Proxy :: Proxy Int8) -narrow16IntLit = narrowLit (Proxy :: Proxy Int16) -narrow32IntLit = narrowLit (Proxy :: Proxy Int32) -narrow8WordLit = narrowLit (Proxy :: Proxy Word8) -narrow16WordLit = narrowLit (Proxy :: Proxy Word16) -narrow32WordLit = narrowLit (Proxy :: Proxy Word32) +narrowLit' :: forall a. Integral a => Proxy a -> LitNumType -> Literal -> Literal +narrowLit' _ nt' (LitNumber _ i) = LitNumber nt' (toInteger (fromInteger i :: a)) +narrowLit' _ _ l = pprPanic "narrowLit" (ppr l) + +narrow8IntLit = narrowLit' (Proxy :: Proxy Int8) LitNumInt +narrow16IntLit = narrowLit' (Proxy :: Proxy Int16) LitNumInt +narrow32IntLit = narrowLit' (Proxy :: Proxy Int32) LitNumInt +narrow8WordLit = narrowLit' (Proxy :: Proxy Word8) LitNumWord +narrow16WordLit = narrowLit' (Proxy :: Proxy Word16) LitNumWord +narrow32WordLit = narrowLit' (Proxy :: Proxy Word32) LitNumWord + +narrowInt8Lit, narrowInt16Lit, narrowInt32Lit, + narrowWord8Lit, narrowWord16Lit, narrowWord32Lit :: Literal -> Literal +narrowInt8Lit = narrowLit' (Proxy :: Proxy Int8) LitNumInt8 +narrowInt16Lit = narrowLit' (Proxy :: Proxy Int16) LitNumInt16 +narrowInt32Lit = narrowLit' (Proxy :: Proxy Int32) LitNumInt32 +narrowWord8Lit = narrowLit' (Proxy :: Proxy Word8) LitNumWord8 +narrowWord16Lit = narrowLit' (Proxy :: Proxy Word16) LitNumWord16 +narrowWord32Lit = narrowLit' (Proxy :: Proxy Word32) LitNumWord32 + +-- | Extend a fixed-width literal (e.g. 'Int16#') to a word-sized literal (e.g. +-- 'Int#'). +extendWordLit, extendIntLit :: Platform -> Literal -> Literal +extendWordLit platform (LitNumber _nt i) = mkLitWord platform i +extendWordLit _platform l = pprPanic "extendWordLit" (ppr l) +extendIntLit platform (LitNumber _nt i) = mkLitInt platform i +extendIntLit _platform l = pprPanic "extendIntLit" (ppr l) int8Lit (LitNumber _ i) = mkLitInt8 i int8Lit l = pprPanic "int8Lit" (ppr l) ===================================== testsuite/tests/simplCore/should_compile/T8832.stdout ===================================== @@ -1,11 +1,11 @@ i = GHC.Types.I# 0# -i8 = GHC.Int.I8# (GHC.Prim.narrowInt8# 0#) -i16 = GHC.Int.I16# (GHC.Prim.narrowInt16# 0#) -i32 = GHC.Int.I32# (GHC.Prim.narrowInt32# 0#) +i8 = GHC.Int.I8# 0#8 +i16 = GHC.Int.I16# 0#16 +i32 = GHC.Int.I32# 0#32 i64 = GHC.Int.I64# 0# w = GHC.Types.W# 0## -w8 = GHC.Word.W8# (GHC.Prim.narrowWord8# 0##) -w16 = GHC.Word.W16# (GHC.Prim.narrowWord16# 0##) -w32 = GHC.Word.W32# (GHC.Prim.narrowWord32# 0##) +w8 = GHC.Word.W8# 0##8 +w16 = GHC.Word.W16# 0##16 +w32 = GHC.Word.W32# 0##32 w64 = GHC.Word.W64# 0## z = 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f42424ad9b7daacce022c5d0d46553afae45e361...0c51530e2b951a97d2fb4fd93daa7af94e9b3604 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f42424ad9b7daacce022c5d0d46553afae45e361...0c51530e2b951a97d2fb4fd93daa7af94e9b3604 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 Tue Nov 3 03:24:58 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 02 Nov 2020 22:24:58 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 2 commits: Bump submodules Message-ID: <5fa0cd8ac5025_7853fb5eabea994573884@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: a5bb848b by Moritz Angermann at 2020-11-03T03:24:07+00:00 Bump submodules - - - - - 87db2edf by Moritz Angermann at 2020-11-03T03:24:22+00:00 Make Libdw.c -Werror safe - - - - - 3 changed files: - libraries/binary - libraries/bytestring - rts/Libdw.c Changes: ===================================== libraries/binary ===================================== @@ -1 +1 @@ -Subproject commit 6462b2f024d18fa6f47da180825bcd765a440f6c +Subproject commit 79a8ada34cda3339043f315235e702144116f6e7 ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit fe4e14486e9b7125e41af5ad344b031685bdeaf8 +Subproject commit 8b5d8d0da24aefdc4d950174bf396b32335d7e0f ===================================== rts/Libdw.c ===================================== @@ -133,8 +133,14 @@ int libdwLookupLocation(LibdwSession *session, Location *frame, Dwfl_Module *mod = dwfl_addrmodule(session->dwfl, addr); if (mod == NULL) return 1; + // avoid unaligned pointer value + // Using &frame->object_file as argument to dwfl_module_info leads to + // + // error: taking address of packed member of ‘struct Location_’ may result in an unaligned pointer value [-Werror=address-of-packed-member] + // + void *object_file = &frame->object_file; dwfl_module_info(mod, NULL, NULL, NULL, NULL, NULL, - &frame->object_file, NULL); + object_file, NULL); // Find function name frame->function = dwfl_module_addrname(mod, addr); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c51530e2b951a97d2fb4fd93daa7af94e9b3604...87db2edf15b51c0ca3454e6dd93b40bb70edf14e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0c51530e2b951a97d2fb4fd93daa7af94e9b3604...87db2edf15b51c0ca3454e6dd93b40bb70edf14e 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 Tue Nov 3 04:45:12 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 23:45:12 -0500 Subject: [Git][ghc/ghc][master] testsuite: Add --top flag to driver Message-ID: <5fa0e05837b1e_7853fb61c172ad4583418@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 5 changed files: - hadrian/src/Settings/Builders/RunTest.hs - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk Changes: ===================================== hadrian/src/Settings/Builders/RunTest.hs ===================================== @@ -102,6 +102,7 @@ runTestBuilderArgs = builder RunTest ? do -- TODO: set CABAL_MINIMAL_BUILD/CABAL_PLUGIN_BUILD mconcat [ arg $ "testsuite/driver/runtests.py" , pure [ "--rootdir=" ++ testdir | testdir <- rootdirs ] + , arg "--top", arg (top -/- "testsuite") , arg "-e", arg $ "windows=" ++ show windowsHost , arg "-e", arg $ "darwin=" ++ show osxHost , arg "-e", arg $ "config.local=False" @@ -129,7 +130,6 @@ runTestBuilderArgs = builder RunTest ? do , arg "-e", arg $ "config.ghc_dynamic_by_default=" ++ show hasDynamicByDefault , arg "-e", arg $ "config.ghc_dynamic=" ++ show hasDynamic - , arg "-e", arg $ "config.top=" ++ show (top -/- "testsuite") , arg "-e", arg $ "config.wordsize=" ++ show wordsize , arg "-e", arg $ "config.os=" ++ show os , arg "-e", arg $ "config.arch=" ++ show arch ===================================== testsuite/driver/runtests.py ===================================== @@ -14,6 +14,7 @@ import tempfile import time import re import traceback +from pathlib import Path # We don't actually need subprocess in runtests.py, but: # * We do need it in testlibs.py @@ -56,6 +57,7 @@ parser = argparse.ArgumentParser(description="GHC's testsuite driver") perf_group = parser.add_mutually_exclusive_group() parser.add_argument("-e", action='append', help="A string to execute from the command line.") +parser.add_argument("--top", type=Path, help="path to top of testsuite/ tree") parser.add_argument("--config-file", action="append", help="config file") parser.add_argument("--config", action='append', help="config field") parser.add_argument("--rootdir", action='append', help="root of tree containing tests (default: .)") @@ -104,6 +106,9 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +if args.top: + config.top = args.top + if args.only: config.only = args.only config.run_only_some_tests = True @@ -277,7 +282,7 @@ testopts_local.x = TestOptions() # if timeout == -1 then we try to calculate a sensible value if config.timeout == -1: - config.timeout = int(read_no_crs(config.top + '/timeout/calibrate.out')) + config.timeout = int(read_no_crs(config.top / 'timeout' / 'calibrate.out')) print('Timeout is ' + str(config.timeout)) print('Known ways: ' + ', '.join(config.other_ways)) ===================================== testsuite/driver/testglobals.py ===================================== @@ -22,7 +22,7 @@ class TestConfig: def __init__(self): # Where the testsuite root is - self.top = '' + self.top = Path('.') # Directories below which to look for test description files (foo.T) self.rootdirs = [] ===================================== testsuite/driver/testlib.py ===================================== @@ -1110,7 +1110,7 @@ def do_test(name: TestName, dst_makefile = in_testdir('Makefile') if src_makefile.exists(): makefile = src_makefile.read_text(encoding='UTF-8') - makefile = re.sub('TOP=.*', 'TOP=' + config.top, makefile, 1) + makefile = re.sub('TOP=.*', 'TOP=%s' % config.top, makefile, 1) dst_makefile.write_text(makefile, encoding='UTF-8') if opts.pre_cmd: ===================================== testsuite/mk/test.mk ===================================== @@ -256,13 +256,13 @@ endif RUNTEST_OPTS += \ --rootdir=. \ --config-file=$(CONFIG) \ + --top="$(TOP_ABS)" \ -e 'config.platform="$(TARGETPLATFORM)"' \ -e 'config.os="$(TargetOS_CPP)"' \ -e 'config.arch="$(TargetARCH_CPP)"' \ -e 'config.wordsize="$(WORDSIZE)"' \ -e 'config.timeout=int($(TIMEOUT)) or config.timeout' \ - -e 'config.exeext="$(exeext)"' \ - -e 'config.top="$(TOP_ABS)"' + -e 'config.exeext="$(exeext)"' # Wrap non-empty program paths in quotes, because they may contain spaces. Do # it here, so we don't have to (and don't forget to do it) in the .T test View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ce2f7d6e6a516173750b1d740f345e90992ffce -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ce2f7d6e6a516173750b1d740f345e90992ffce 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 Tue Nov 3 04:45:50 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 23:45:50 -0500 Subject: [Git][ghc/ghc][master] Document that ccall convention doesn't support varargs Message-ID: <5fa0e07ea1f66_7853fb61c300e645900c6@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 5 changed files: - docs/users_guide/exts/ffi.rst - testsuite/tests/rts/T5423.hs - testsuite/tests/rts/T5423.stdout - testsuite/tests/rts/T5423_c.c - testsuite/tests/rts/T5423_cmm.cmm Changes: ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -83,6 +83,21 @@ For more details on the implementation see the Paper: Last known to be accessible `here `_. +Varargs not supported by ``ccall`` calling convention +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +Note that functions requiring varargs arguments are unsupported by the ``ccall`` +calling convention. Foreign imports needing to call such functions should rather +use the ``capi`` convention, giving an explicit signature for the needed +call-pattern. For instance, one could write: :: + + foreign import "capi" "printf" + my_printf :: Ptr CChar -> CInt -> IO () + + printInt :: CInt -> IO () + printInt n = my_printf "printed number %d" n + + .. _ffi-ghcexts: GHC extensions to the FFI Chapter ===================================== testsuite/tests/rts/T5423.hs ===================================== @@ -1,3 +1,5 @@ +-- | Verify that @foreign import prim@ calls with more than 10 arguments +-- are lowered correctly. {-# LANGUAGE MagicHash, GHCForeignImportPrim, UnliftedFFITypes #-} ===================================== testsuite/tests/rts/T5423.stdout ===================================== @@ -1,2 +1,2 @@ -111 112 113 114 115 116 117 118 119 120 +111 112 113 114 115 116 117 118 119 120 120 ===================================== testsuite/tests/rts/T5423_c.c ===================================== @@ -1,6 +1,34 @@ +#include #include void flush_stdout(void) { fflush(stdout); } + +void print_it( + StgWord r1, + StgWord r2, + StgWord r3, + StgWord r4, + StgWord r5, + StgWord r6, + StgWord r7, + StgWord r8, + StgWord r9, + StgWord r10 + ) +{ + printf("%" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word + " %" FMT_Word "\n", + r1, r2, r3, r4, r5, + r6, r7, r8, r9, r10); +} ===================================== testsuite/tests/rts/T5423_cmm.cmm ===================================== @@ -10,7 +10,6 @@ test (W_ r1, W_ r9, W_ r10) { - foreign "C" printf("%d %d %d %d %d %d %d %d %d %d\n", - r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); + foreign "C" print_it(r1, r2, r3, r4, r5, r6, r7, r8, r9, r10); return (r10); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b7722219ffdb109c3a8b034a8e112d18e6e4336 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b7722219ffdb109c3a8b034a8e112d18e6e4336 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 Tue Nov 3 04:46:29 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 23:46:29 -0500 Subject: [Git][ghc/ghc][master] RtsAPI: pause and resume the RTS Message-ID: <5fa0e0a518b29_78573c8258592798@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 30 changed files: - includes/RtsAPI.h - includes/rts/Threads.h - rts/Capability.c - rts/RtsAPI.c - rts/Schedule.c - rts/Task.c - rts/Task.h - rts/sm/NonMoving.c - + testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/pause_and_use_rts_api.hs - + testsuite/tests/rts/pause-resume/pause_and_use_rts_api.stdout - + testsuite/tests/rts/pause-resume/pause_resume.c - + testsuite/tests/rts/pause-resume/pause_resume.h - + testsuite/tests/rts/pause-resume/pause_resume_via_pthread.hs - + testsuite/tests/rts/pause-resume/pause_resume_via_safe_ffi.hs - + testsuite/tests/rts/pause-resume/pause_resume_via_safe_ffi_concurrent.hs - + testsuite/tests/rts/pause-resume/pause_resume_via_safe_ffi_concurrent.stdout - + testsuite/tests/rts/pause-resume/shouldfail/all.T - + testsuite/tests/rts/pause-resume/shouldfail/rts_double_pause.hs - + testsuite/tests/rts/pause-resume/shouldfail/rts_double_pause.stderr - + testsuite/tests/rts/pause-resume/shouldfail/rts_double_pause.stdout - + testsuite/tests/rts/pause-resume/shouldfail/rts_lock_when_paused.hs - + testsuite/tests/rts/pause-resume/shouldfail/rts_lock_when_paused.stderr - + testsuite/tests/rts/pause-resume/shouldfail/rts_lock_when_paused.stdout - + testsuite/tests/rts/pause-resume/shouldfail/rts_pause_lock.c - + testsuite/tests/rts/pause-resume/shouldfail/rts_pause_lock.h - + testsuite/tests/rts/pause-resume/shouldfail/rts_pause_when_locked.hs - + testsuite/tests/rts/pause-resume/shouldfail/rts_pause_when_locked.stderr - + testsuite/tests/rts/pause-resume/shouldfail/rts_pause_when_locked.stdout - + testsuite/tests/rts/pause-resume/shouldfail/unsafe_rts_pause.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81006a06736c7300626f9d692a118b493b585cd5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81006a06736c7300626f9d692a118b493b585cd5 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 Tue Nov 3 04:47:05 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 23:47:05 -0500 Subject: [Git][ghc/ghc][master] Display results of GHC.Core.Lint.lint* functions consistently Message-ID: <5fa0e0c9837fb_785721f2305966d8@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - 6 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - testsuite/tests/callarity/unittest/CallArity1.hs Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -19,8 +19,8 @@ module GHC.Core.Lint ( -- ** Debug output endPass, endPassIO, - dumpPassResult, - GHC.Core.Lint.dumpIfSet, + displayLintResults, dumpPassResult, + dumpIfSet, ) where #include "HsVersions.h" @@ -65,7 +65,8 @@ import GHC.Core.TyCon as TyCon import GHC.Core.Coercion.Axiom import GHC.Core.Unify import GHC.Types.Basic -import GHC.Utils.Error as Err +import GHC.Utils.Error hiding ( dumpIfSet ) +import qualified GHC.Utils.Error as Err import GHC.Data.List.SetOps import GHC.Builtin.Names import GHC.Utils.Outputable as Outputable @@ -372,33 +373,38 @@ lintPassResult hsc_env pass binds | not (gopt Opt_DoCoreLinting dflags) = return () | otherwise - = do { let (warns, errs) = lintCoreBindings dflags pass (interactiveInScope hsc_env) binds + = do { let warns_and_errs = lintCoreBindings dflags pass (interactiveInScope hsc_env) binds ; Err.showPass dflags ("Core Linted result of " ++ showPpr dflags pass) - ; displayLintResults dflags pass warns errs binds } + ; displayLintResults dflags (showLintWarnings pass) (ppr pass) + (pprCoreBindings binds) warns_and_errs } where dflags = hsc_dflags hsc_env -displayLintResults :: DynFlags -> CoreToDo - -> Bag Err.MsgDoc -> Bag Err.MsgDoc -> CoreProgram +displayLintResults :: DynFlags + -> Bool -- ^ If 'True', display linter warnings. + -- If 'False', ignore linter warnings. + -> SDoc -- ^ The source of the linted program + -> SDoc -- ^ The linted program, pretty-printed + -> WarnsAndErrs -> IO () -displayLintResults dflags pass warns errs binds +displayLintResults dflags display_warnings pp_what pp_pgm (warns, errs) | not (isEmptyBag errs) = do { putLogMsg dflags NoReason Err.SevDump noSrcSpan $ withPprStyle defaultDumpStyle - (vcat [ lint_banner "errors" (ppr pass), Err.pprMessageBag errs + (vcat [ lint_banner "errors" pp_what, Err.pprMessageBag errs , text "*** Offending Program ***" - , pprCoreBindings binds + , pp_pgm , text "*** End of Offense ***" ]) ; Err.ghcExit dflags 1 } | not (isEmptyBag warns) , not (hasNoDebugOutput dflags) - , showLintWarnings pass + , display_warnings -- If the Core linter encounters an error, output to stderr instead of -- stdout (#13342) = putLogMsg dflags NoReason Err.SevInfo noSrcSpan $ withPprStyle defaultDumpStyle - (lint_banner "warnings" (ppr pass) $$ Err.pprMessageBag (mapBag ($$ blankLine) warns)) + (lint_banner "warnings" pp_what $$ Err.pprMessageBag (mapBag ($$ blankLine) warns)) | otherwise = return () @@ -413,29 +419,18 @@ showLintWarnings :: CoreToDo -> Bool showLintWarnings (CoreDoSimplify _ (SimplMode { sm_phase = InitialPhase })) = False showLintWarnings _ = True -lintInteractiveExpr :: String -> HscEnv -> CoreExpr -> IO () +lintInteractiveExpr :: SDoc -- ^ The source of the linted expression + -> HscEnv -> CoreExpr -> IO () lintInteractiveExpr what hsc_env expr | not (gopt Opt_DoCoreLinting dflags) = return () | Just err <- lintExpr dflags (interactiveInScope hsc_env) expr - = do { display_lint_err err - ; Err.ghcExit dflags 1 } + = displayLintResults dflags False what (pprCoreExpr expr) (emptyBag, err) | otherwise = return () where dflags = hsc_dflags hsc_env - display_lint_err err - = do { putLogMsg dflags NoReason Err.SevDump - noSrcSpan - $ withPprStyle defaultDumpStyle - (vcat [ lint_banner "errors" (text what) - , err - , text "*** Offending Program ***" - , pprCoreExpr expr - , text "*** End of Offense ***" ]) - ; Err.ghcExit dflags 1 } - interactiveInScope :: HscEnv -> [Var] -- In GHCi we may lint expressions, or bindings arising from 'deriving' -- clauses, that mention variables bound in the interactive context. @@ -464,7 +459,7 @@ interactiveInScope hsc_env -- where t is a RuntimeUnk (see TcType) -- | Type-check a 'CoreProgram'. See Note [Core Lint guarantee]. -lintCoreBindings :: DynFlags -> CoreToDo -> [Var] -> CoreProgram -> (Bag MsgDoc, Bag MsgDoc) +lintCoreBindings :: DynFlags -> CoreToDo -> [Var] -> CoreProgram -> WarnsAndErrs -- Returns (warnings, errors) -- If you edit this function, you may need to update the GHC formalism -- See Note [GHC Formalism] @@ -540,16 +535,16 @@ hence the `TopLevelFlag` on `tcPragExpr` in GHC.IfaceToCore. -} -lintUnfolding :: Bool -- True <=> is a compulsory unfolding +lintUnfolding :: Bool -- True <=> is a compulsory unfolding -> DynFlags -> SrcLoc - -> VarSet -- Treat these as in scope + -> VarSet -- Treat these as in scope -> CoreExpr - -> Maybe MsgDoc -- Nothing => OK + -> Maybe (Bag MsgDoc) -- Nothing => OK lintUnfolding is_compulsory dflags locn var_set expr | isEmptyBag errs = Nothing - | otherwise = Just (pprMessageBag errs) + | otherwise = Just errs where vars = nonDetEltsUniqSet var_set (_warns, errs) = initL dflags (defaultLintFlags dflags) vars $ @@ -563,11 +558,11 @@ lintUnfolding is_compulsory dflags locn var_set expr lintExpr :: DynFlags -> [Var] -- Treat these as in scope -> CoreExpr - -> Maybe MsgDoc -- Nothing => OK + -> Maybe (Bag MsgDoc) -- Nothing => OK lintExpr dflags vars expr | isEmptyBag errs = Nothing - | otherwise = Just (pprMessageBag errs) + | otherwise = Just errs where (_warns, errs) = initL dflags (defaultLintFlags dflags) vars linter linter = addLoc TopLevelBindings $ @@ -2326,13 +2321,15 @@ lintCoercion (HoleCo h) -} lintAxioms :: DynFlags + -> SDoc -- ^ The source of the linted axioms -> [CoAxiom Branched] - -> WarnsAndErrs -lintAxioms dflags axioms - = initL dflags (defaultLintFlags dflags) [] $ - do { mapM_ lint_axiom axioms - ; let axiom_groups = groupWith coAxiomTyCon axioms - ; mapM_ lint_axiom_group axiom_groups } + -> IO () +lintAxioms dflags what axioms = + displayLintResults dflags True what (vcat $ map pprCoAxiom axioms) $ + initL dflags (defaultLintFlags dflags) [] $ + do { mapM_ lint_axiom axioms + ; let axiom_groups = groupWith coAxiomTyCon axioms + ; mapM_ lint_axiom_group axiom_groups } lint_axiom :: CoAxiom Branched -> LintM () lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -1713,7 +1713,7 @@ hscParsedStmt hsc_env stmt = runInteractiveHsc hsc_env $ do -- Desugar it ds_expr <- ioMsgMaybe $ deSugarExpr hsc_env tc_expr - liftIO (lintInteractiveExpr "desugar expression" hsc_env ds_expr) + liftIO (lintInteractiveExpr (text "desugar expression") hsc_env ds_expr) handleWarnings -- Then code-gen, and link it @@ -1955,7 +1955,7 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr ; prepd_expr <- corePrepExpr hsc_env tidy_expr {- Lint if necessary -} - ; lintInteractiveExpr "hscCompileExpr" hsc_env prepd_expr + ; lintInteractiveExpr (text "hscCompileExpr") hsc_env prepd_expr {- Convert to BCOs -} ; bcos <- coreExprToBCOs hsc_env ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -62,6 +62,7 @@ import GHC.Core.TyCon import GHC.Core.ConLike import GHC.Core.DataCon import GHC.Core.Opt.OccurAnal ( occurAnalyseExpr ) +import GHC.Core.Ppr import GHC.Unit.External import GHC.Unit.Module @@ -73,6 +74,7 @@ import GHC.Utils.Outputable import GHC.Utils.Misc import GHC.Utils.Panic +import GHC.Data.Bag import GHC.Data.Maybe import GHC.Data.FastString import GHC.Data.List.SetOps @@ -1199,13 +1201,11 @@ tcIfaceRule (IfaceRule {ifRuleName = name, ifActivation = act, ifRuleBndrs = bnd bndrs' ++ exprsFreeIdsList args') ; case lintExpr dflags in_scope rhs' of - Nothing -> return () - Just fail_msg -> do { mod <- getIfModule - ; pprPanic "Iface Lint failure" - (vcat [ text "In interface for" <+> ppr mod - , hang doc 2 fail_msg - , ppr name <+> equals <+> ppr rhs' - , text "Iface expr =" <+> ppr rhs ]) } } + Nothing -> return () + Just errs -> liftIO $ + displayLintResults dflags False doc + (pprCoreExpr rhs') + (emptyBag, errs) } ; return (bndrs', args', rhs') } ; let mb_tcs = map ifTopFreeName args ; this_mod <- getIfModule @@ -1724,13 +1724,10 @@ tcPragExpr is_compulsory toplvl name expr in_scope <- get_in_scope dflags <- getDynFlags case lintUnfolding is_compulsory dflags noSrcLoc in_scope core_expr' of - Nothing -> return () - Just fail_msg -> do { mod <- getIfModule - ; pprPanic "Iface Lint failure" - (vcat [ text "In interface for" <+> ppr mod - , hang doc 2 fail_msg - , ppr name <+> equals <+> ppr core_expr' - , text "Iface expr =" <+> ppr expr ]) } + Nothing -> return () + Just errs -> liftIO $ + displayLintResults dflags False doc + (pprCoreExpr core_expr') (emptyBag, errs) return core_expr' where doc = ppWhen is_compulsory (text "Compulsory") <+> ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -296,11 +296,7 @@ tcRnModuleTcRnM hsc_env mod_sum tcRnSrcDecls explicit_mod_hdr local_decls export_ies ; whenM (goptM Opt_DoCoreLinting) $ - do { let (warns, errs) = lintGblEnv (hsc_dflags hsc_env) tcg_env - ; mapBagM_ (addWarn NoReason) warns - ; mapBagM_ addErr errs - ; failIfErrsM } -- if we have a lint error, we're only - -- going to get in deeper trouble by proceeding + lintGblEnv (hsc_dflags hsc_env) tcg_env ; setGblEnv tcg_env $ do { -- Process the export list ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -1712,7 +1712,8 @@ getRoleAnnots bndrs role_env -- | Check the 'TcGblEnv' for consistency. Currently, only checks -- axioms, but should check other aspects, too. -lintGblEnv :: DynFlags -> TcGblEnv -> (Bag SDoc, Bag SDoc) -lintGblEnv dflags tcg_env = lintAxioms dflags axioms +lintGblEnv :: DynFlags -> TcGblEnv -> TcM () +lintGblEnv dflags tcg_env = + liftIO $ lintAxioms dflags (text "TcGblEnv axioms") axioms where axioms = typeEnvCoAxioms (tcg_type_env tcg_env) ===================================== testsuite/tests/callarity/unittest/CallArity1.hs ===================================== @@ -172,7 +172,7 @@ main = do dflags <- getSessionDynFlags liftIO $ forM_ exprs $ \(n,e) -> do case lintExpr dflags [f,scrutf,scruta] e of - Just msg -> putMsg dflags (msg $$ text "in" <+> text n) + Just errs -> putMsg dflags (pprMessageBag errs $$ text "in" <+> text n) Nothing -> return () putMsg dflags (text n Outputable.<> char ':') -- liftIO $ putMsg dflags (ppr e) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bfb1e272950169c17963adaf423890e47b908f4d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bfb1e272950169c17963adaf423890e47b908f4d 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 Tue Nov 3 04:48:15 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 23:48:15 -0500 Subject: [Git][ghc/ghc][master] hadrian: Don't capture RunTest output Message-ID: <5fa0e10f1fba4_7853fb595cff67c605277@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 1 changed file: - hadrian/src/Builder.hs Changes: ===================================== hadrian/src/Builder.hs ===================================== @@ -304,6 +304,11 @@ instance H.Builder Builder where Makeindex -> unit $ cmd' [Cwd output] [path] (buildArgs ++ [input]) Tar _ -> cmd' buildOptions echo [path] buildArgs + + -- RunTest produces a very large amount of (colorised) output; + -- Don't attempt to capture it. + RunTest -> cmd echo [path] buildArgs + _ -> cmd' echo [path] buildArgs -- TODO: Some builders are required only on certain platforms. For example, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1370eda7a53f5dfc88afe705b2ffecb1d5544ec7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1370eda7a53f5dfc88afe705b2ffecb1d5544ec7 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 Tue Nov 3 04:47:40 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 02 Nov 2020 23:47:40 -0500 Subject: [Git][ghc/ghc][master] Expand type synonyms with :kind! Message-ID: <5fa0e0ec14ce9_7853fb640178d206025a5@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 8 changed files: - compiler/GHC/Tc/Module.hs - docs/users_guide/9.2.1-notes.rst - + testsuite/tests/ghci/scripts/T13795.script - + testsuite/tests/ghci/scripts/T13795.stdout - + testsuite/tests/ghci/scripts/T18828.hs - + testsuite/tests/ghci/scripts/T18828.script - + testsuite/tests/ghci/scripts/T18828.stdout - testsuite/tests/ghci/scripts/all.T Changes: ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -2625,12 +2625,13 @@ tcRnType hsc_env flexi normalise rdr_type -- Do validity checking on type ; checkValidType (GhciCtxt True) ty - ; ty' <- if normalise - then do { fam_envs <- tcGetFamInstEnvs - ; let (_, ty') - = normaliseType fam_envs Nominal ty - ; return ty' } - else return ty ; + -- Optionally (:k vs :k!) normalise the type. Does two things: + -- normaliseType: expand type-family applications + -- expandTypeSynonyms: expand type synonyms (#18828) + ; fam_envs <- tcGetFamInstEnvs + ; let ty' | normalise = expandTypeSynonyms $ snd $ + normaliseType fam_envs Nominal ty + | otherwise = ty ; return (ty', mkInfForAllTys kvs (tcTypeKind ty')) } ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -37,6 +37,9 @@ Compiler - Type checker plugins which work with the natural numbers now should use ``naturalTy`` kind instead of ``typeNatKind``, which has been removed. +- GHCi's ``:kind!`` command now expands through type synonyms in addition to type + families. See :ghci-cmd:`:kind`. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== testsuite/tests/ghci/scripts/T13795.script ===================================== @@ -0,0 +1,2 @@ +type A = () +:kind! A ===================================== testsuite/tests/ghci/scripts/T13795.stdout ===================================== @@ -0,0 +1,2 @@ +A :: * += () ===================================== testsuite/tests/ghci/scripts/T18828.hs ===================================== @@ -0,0 +1,31 @@ +{-# Language ConstraintKinds #-} +{-# Language DataKinds #-} +{-# Language GADTs #-} +{-# Language PolyKinds #-} +{-# Language RankNTypes #-} +{-# Language StandaloneKindSignatures #-} +{-# Language TypeFamilies #-} +{-# Language TypeOperators #-} +module T18828 where + +import Data.Kind + +type Cat :: Type -> Type +type Cat ob = ob -> ob -> Type + +type Dict :: Constraint -> Type +data Dict cls where + Dict :: cls => Dict cls + +type (:-) :: Cat Constraint +newtype cls1 :- cls2 where + Sub :: (cls1 => Dict cls2) -> (cls1 :- cls2) + +type ObjectSyn :: Cat ob -> Type +type ObjectSyn (cat :: ob -> ob -> Type) = ob + +type + ObjectFam :: Cat ob -> Type +type family + ObjectFam cat where + ObjectFam @ob cat = ob ===================================== testsuite/tests/ghci/scripts/T18828.script ===================================== @@ -0,0 +1,9 @@ +:load T18828 +:set -XDataKinds -XKindSignatures -XRankNTypes +import Data.Type.Equality +:k! ObjectSyn (->) +:k! forall ob. ObjectSyn ((:~:) :: Cat ob) +:k! ObjectSyn (:-) +:k! ObjectFam (->) +:k! forall ob. ObjectFam ((:~:) :: Cat ob) +:k! ObjectFam (:-) ===================================== testsuite/tests/ghci/scripts/T18828.stdout ===================================== @@ -0,0 +1,12 @@ +ObjectSyn (->) :: * += * +forall ob. ObjectSyn ((:~:) :: Cat ob) :: * += ob +ObjectSyn (:-) :: * += Constraint +ObjectFam (->) :: * += * +forall ob. ObjectFam ((:~:) :: Cat ob) :: * += ob +ObjectFam (:-) :: * += Constraint ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -279,6 +279,7 @@ test('T13591', expect_broken(13591), ghci_script, ['T13591.script']) test('T13699', normal, ghci_script, ['T13699.script']) test('T13988', normal, ghci_script, ['T13988.script']) test('T13407', normal, ghci_script, ['T13407.script']) +test('T13795', normal, ghci_script, ['T13795.script']) test('T13963', normal, ghci_script, ['T13963.script']) test('T14342', [extra_hc_opts("-XOverloadedStrings -XRebindableSyntax")], ghci_script, ['T14342.script']) @@ -322,3 +323,4 @@ test('T17669', [extra_run_opts('-fexternal-interpreter -fobject-code'), expect_b test('T18501', normal, ghci_script, ['T18501.script']) test('T18644', normal, ghci_script, ['T18644.script']) test('T18755', normal, ghci_script, ['T18755.script']) +test('T18828', normal, ghci_script, ['T18828.script']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9e5f52c571ae3dfd4826e10a256d1a265f7e058 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9e5f52c571ae3dfd4826e10a256d1a265f7e058 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 Tue Nov 3 05:19:08 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 00:19:08 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: testsuite: Add --top flag to driver Message-ID: <5fa0e84ca708d_785e6af3ac61284e@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 6b7070e6 by Ben Gamari at 2020-11-03T00:18:53-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - fff03b4c by Matthew Pickering at 2020-11-03T00:18:54-05:00 Update inlining flags documentation - - - - - b4dd47c4 by Alan Zimmerman at 2020-11-03T00:18:54-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - adea95f6 by Sylvain Henry at 2020-11-03T00:18:59-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/exts/ffi.rst - docs/users_guide/using-optimisation.rst - hadrian/src/Builder.hs - hadrian/src/Rules/Clean.hs - hadrian/src/Settings/Builders/RunTest.hs - includes/RtsAPI.h - includes/rts/EventLogWriter.h - includes/rts/Threads.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/RtsAPI.c - rts/RtsSymbols.c - rts/Schedule.c - rts/Task.c - rts/Task.h - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/sm/NonMoving.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2dc835801c5bb0eba9fb8e55874e2cb1876a8f4c...adea95f6e7f4f369325eef133040517e902c3362 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2dc835801c5bb0eba9fb8e55874e2cb1876a8f4c...adea95f6e7f4f369325eef133040517e902c3362 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 Tue Nov 3 06:38:46 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 03 Nov 2020 01:38:46 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-always-pic] 11 commits: testsuite: Add --top flag to driver Message-ID: <5fa0faf625cc_7853fb6435ae2e8624439@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC Commits: 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 45af76cd by Moritz Angermann at 2020-11-03T06:31:57+00:00 [AArch64] Aarch64 Always PIC - - - - - 4ba1c796 by Moritz Angermann at 2020-11-03T06:31:57+00:00 Fix spelling - - - - - 7f94591b by Moritz Angermann at 2020-11-03T06:31:57+00:00 Drop mmap_next (not needed with forced PIC anymore) - - - - - 0326390a by Moritz Angermann at 2020-11-03T06:31:57+00:00 Meh, AArch64 is ARM64 in master. - - - - - 50e81b8d by Moritz Angermann at 2020-11-03T06:31:57+00:00 Fix libdw with -Werror - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/ffi.rst - hadrian/src/Builder.hs - hadrian/src/Settings/Builders/RunTest.hs - includes/RtsAPI.h - includes/rts/Flags.h - includes/rts/Threads.h - rts/Capability.c - rts/Libdw.c - rts/Linker.c - rts/LinkerInternals.h - rts/RtsAPI.c - rts/Schedule.c - rts/Task.c - rts/Task.h - rts/sm/NonMoving.c - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - testsuite/tests/callarity/unittest/CallArity1.hs - + testsuite/tests/ghci/scripts/T13795.script - + testsuite/tests/ghci/scripts/T13795.stdout - + testsuite/tests/ghci/scripts/T18828.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7d441e1849a3be17265cbd1a1db5a4085e4c63ef...50e81b8d20e9aac634760f03bd7e9dbdb0293fb0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7d441e1849a3be17265cbd1a1db5a4085e4c63ef...50e81b8d20e9aac634760f03bd7e9dbdb0293fb0 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 Tue Nov 3 08:40:23 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 03 Nov 2020 03:40:23 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 28 commits: testsuite: Add --top flag to driver Message-ID: <5fa11777ded63_7853fb6402bf094632227@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 2adffe1b by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Ints] I8/I16/I32 with unpacked ints now. (cherry picked from commit acb5ce792806bc3c1e1730c6bdae853d2755de16) - - - - - 1b368955 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Int] unpacked ints, part 2 (cherry picked from commit 872b3b35e269eaea771d0f98a9bce6ce9ff8f084) - - - - - 3c4fffc1 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Int] unpacked ints, part 3 (cherry picked from commit 39b8861cf728ffeeb1d1f4abff073b8e4956d853) - - - - - 02c3b439 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Int] T8832 fix test stdout. (cherry picked from commit a6e59c84ace4a4f3cb1aa95ffaec3bb5b675d66a) - - - - - 6a3be476 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Int] fix haddock (cherry picked from commit 5764bca329c18619598fbe99433f581a119a5898) - - - - - f47e4c1f by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Int] move Int32# section. (cherry picked from commit beba345453f368b7f76bf55161fe10f26b9b2110) - - - - - af751f6c by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Word] W8/W16/W32 (cherry picked from commit 8aef9557ae8a2a446090af4124d22d1d27a4a10d) - - - - - 1fecf13f by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSize Word] pt 2 (cherry picked from commit 88764dd4d4cf744a02bde4c91c0ee1e510b88298) - - - - - 59c6f380 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSize Word] pt 3 (cherry picked from commit dade52f58bc677040146362d8e49d7a42b82ae83) - - - - - 0a76fb47 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Word] Constant Fold (cherry picked from commit fe9a02930e2596660fd1bdb7c9dbd63d43085e05) - - - - - 70ef6c92 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Word] Fix testsuite (cherry picked from commit a0903f8eb626fa3444bcc880ac515d1fb6e52140) - - - - - e51b9f83 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized Word] More constant folds (cherry picked from commit 13a7028bd83f33b0647cd924830f3ad228e9ee24) - - - - - 78d575e0 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [SizedCmm Word] Trying to fix TH Quotes (cherry picked from commit e98e3d124a92cdf48108d918e501a132eaaee53a) - - - - - 7590b715 by Moritz Angermann at 2020-11-03T08:23:05+00:00 Fix superfluous import - - - - - 0f9e1936 by Moritz Angermann at 2020-11-03T08:23:05+00:00 [CmmSized] bump submodules - - - - - ed4b2e64 by Moritz Angermann at 2020-11-03T08:23:05+00:00 Fix T8832 - - - - - 58262896 by Ben Gamari at 2020-11-03T08:23:05+00:00 CodeToByteCode: Fix handling of narrow datacon fields Handle the non-word-size cases specifically and emit the appropriate bytecode instructions. - - - - - cbadeb8d by Ben Gamari at 2020-11-03T08:23:05+00:00 Constant folding for extend/narrow - - - - - 235464b1 by Ben Gamari at 2020-11-03T08:23:05+00:00 StgToCmm: Normalize padding - - - - - 0d45991b by Moritz Angermann at 2020-11-03T08:23:05+00:00 Bump submodules - - - - - 3332dc26 by Moritz Angermann at 2020-11-03T08:23:05+00:00 Make Libdw.c -Werror safe - - - - - dfecf8f7 by Moritz Angermann at 2020-11-03T08:38:42+00:00 bump text - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - + compiler/GHC/HsToCore/PmCheck/Oracle.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/ffi.rst - ghc/ghc-bin.cabal.in - hadrian/src/Builder.hs - hadrian/src/Settings/Builders/RunTest.hs - includes/RtsAPI.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/87db2edf15b51c0ca3454e6dd93b40bb70edf14e...dfecf8f7553b02736bee8ad638e07d0be5dc9d01 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/87db2edf15b51c0ca3454e6dd93b40bb70edf14e...dfecf8f7553b02736bee8ad638e07d0be5dc9d01 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 Tue Nov 3 09:21:30 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 04:21:30 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Add whereFrom# primop Message-ID: <5fa1211a83e45_7853fb65480d7946429e7@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 0d8d3cd7 by Matthew Pickering at 2020-11-03T08:49:51+00:00 Add whereFrom# primop - - - - - e92f46d9 by Matthew Pickering at 2020-11-03T09:11:24+00:00 Add simple test for whereFrom primop - - - - - d98f44c8 by Matthew Pickering at 2020-11-03T09:21:14+00:00 Fix warnings - - - - - 16 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Heap.hs - compiler/GHC/StgToCmm/Prim.hs - includes/rts/Profiling.h - includes/stg/MiscClosures.h - libraries/base/GHC/Stack/CCS.hsc - rts/PrimOps.cmm - rts/Profiling.c - rts/RtsSymbols.c - testsuite/tests/profiling/should_run/all.T - + testsuite/tests/profiling/should_run/staticcallstack001.hs - + testsuite/tests/profiling/should_run/staticcallstack001.stdout Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3004,6 +3004,15 @@ primop ClearCCSOp "clearCCS#" GenPrimOp with out_of_line = True +------------------------------------------------------------------------ +section "Info Table Origin" +------------------------------------------------------------------------ +primop WhereFromOp "whereFrom#" GenPrimOp + a -> State# s -> (# State# s, Addr# #) + { TODO } + with + out_of_line = True + ------------------------------------------------------------------------ section "Etc" {Miscellaneous built-ins} ===================================== compiler/GHC/CoreToStg.hs ===================================== @@ -47,16 +47,12 @@ import GHC.Platform.Ways import GHC.Driver.Ppr import GHC.Types.ForeignCall import GHC.Types.Demand ( isUsedOnce ) -import GHC.Types.SrcLoc ( mkGeneralSrcSpan ) -import GHC.Builtin.PrimOps ( PrimCall(..), primOpWrapperId ) +import GHC.Builtin.PrimOps ( PrimCall(..) ) import GHC.Builtin.Names ( unsafeEqualityProofName ) import GHC.Data.Maybe import Data.List.NonEmpty (nonEmpty, toList) import Control.Monad (ap) -import Data.List.NonEmpty (nonEmpty, toList) -import Data.Maybe (fromMaybe) -import Data.Tuple (swap) import qualified Data.Set as Set import Control.Monad.Trans.RWS import GHC.Types.Unique.Map ===================================== compiler/GHC/Driver/Hooks.hs ===================================== @@ -67,7 +67,6 @@ import GHCi.RemoteTypes import GHC.Data.Stream import GHC.Data.Bag -import GHC.Hs.Extension import Data.IORef import Data.Maybe ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -163,7 +163,6 @@ import GHC.Cmm.Info.Build import GHC.Cmm.Pipeline import GHC.Cmm.Info -import GHC.Driver.Session import GHC.Utils.Error import Data.IORef @@ -187,7 +186,6 @@ import GHC.Types.HpcInfo import GHC.Utils.Fingerprint ( Fingerprint ) import GHC.Utils.Panic -import GHC.Utils.Error import GHC.Utils.Outputable import GHC.Utils.Exception import GHC.Utils.Misc ===================================== compiler/GHC/StgToCmm.hs ===================================== @@ -59,7 +59,6 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.SysTools.FileCleanup -import GHC.Types.Unique.FM import GHC.Data.Stream import GHC.Data.OrdList @@ -70,7 +69,6 @@ import GHC.Utils.Misc import System.IO.Unsafe import qualified Data.ByteString as BS import GHC.Types.Unique.Map -import GHC.Driver.Ppr codeGen :: DynFlags @@ -246,8 +244,7 @@ cgDataCon :: Maybe (Module, Int) -> DataCon -> FCode () cgDataCon _ data_con | isUnboxedTupleDataCon data_con = return () cgDataCon _ data_con | isUnboxedSumDataCon data_con = return () cgDataCon mn data_con - = do { dflags <- getDynFlags - ; profile <- getProfile + = do { profile <- getProfile ; platform <- getPlatform ; let (tot_wds, -- #ptr_wds + #nonptr_wds ===================================== compiler/GHC/StgToCmm/Heap.hs ===================================== @@ -52,7 +52,6 @@ import GHC.Data.FastString( mkFastString, fsLit ) import Control.Monad (when) import Data.Maybe (isJust) -import GHC.Utils.Outputable import GHC.Utils.Panic( sorry ) ----------------------------------------------------------- ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1515,6 +1515,7 @@ emitPrimOp dflags primop = case primop of NewBCOOp -> alwaysExternal UnpackClosureOp -> alwaysExternal ClosureSizeOp -> alwaysExternal + WhereFromOp -> alwaysExternal GetApStackValOp -> alwaysExternal ClearCCSOp -> alwaysExternal TraceEventOp -> alwaysExternal ===================================== includes/rts/Profiling.h ===================================== @@ -16,3 +16,4 @@ void registerCcList(CostCentre **cc_list); void registerInfoProvList(InfoProvEnt **cc_list); void registerCcsList(CostCentreStack **cc_list); +InfoProvEnt * lookupIPE(StgClosure *info); \ No newline at end of file ===================================== includes/stg/MiscClosures.h ===================================== @@ -479,6 +479,7 @@ RTS_FUN_DECL(stg_writeTVarzh); RTS_FUN_DECL(stg_unpackClosurezh); RTS_FUN_DECL(stg_closureSizzezh); +RTS_FUN_DECL(stg_whereFromzh); RTS_FUN_DECL(stg_getApStackValzh); RTS_FUN_DECL(stg_getSparkzh); RTS_FUN_DECL(stg_numSparkszh); ===================================== libraries/base/GHC/Stack/CCS.hsc ===================================== @@ -20,6 +20,7 @@ module GHC.Stack.CCS ( -- * Call stacks currentCallStack, whoCreated, + whereFrom, -- * Internals CostCentreStack, @@ -44,6 +45,7 @@ import GHC.Ptr import GHC.Foreign as GHC import GHC.IO.Encoding import GHC.List ( concatMap, reverse ) +import Prelude (putStrLn, print) #define PROFILING #include "Rts.h" @@ -135,3 +137,47 @@ whoCreated obj = do renderStack :: [String] -> String renderStack strs = "CallStack (from -prof):" ++ concatMap ("\n "++) (reverse strs) + +-- Static Closure Information + +data InfoProv +data InfoProvEnt + +-- | Get the 'InfoProvEnv' associated with the given value. +getIPE :: a -> IO (Ptr InfoProvEnt) +getIPE obj = IO $ \s -> + case whereFrom## obj s of + (## s', addr ##) -> (## s', Ptr addr ##) + +ipeProv :: Ptr InfoProvEnt -> Ptr InfoProv +ipeProv p = p `plusPtr` 8 --(#offsetof InfoProvEnt, prov) -- TODO, offset is to the "prov" field but not sure how to express this + -- (# sizeOf * StgInfoTable) + +ipName, ipDesc, ipLabel, ipModule, ipSrcLoc :: Ptr InfoProv -> IO CString +ipName p = (# peek InfoProv, table_name) p +ipDesc p = (# peek InfoProv, closure_desc) p +ipLabel p = (# peek InfoProv, label) p +ipModule p = (# peek InfoProv, module) p +ipSrcLoc p = (# peek InfoProv, srcloc) p + +infoProvToStrings :: Ptr InfoProv -> IO [String] +infoProvToStrings ip = do + name <- GHC.peekCString utf8 =<< ipName ip + desc <- GHC.peekCString utf8 =<< ipDesc ip + label <- GHC.peekCString utf8 =<< ipLabel ip + mod <- GHC.peekCString utf8 =<< ipModule ip + loc <- GHC.peekCString utf8 =<< ipSrcLoc ip + return [name, desc, label, mod, loc] + +-- TODO: Add structured output of whereFrom + +whereFrom :: a -> IO [String] +whereFrom obj = do + ipe <- getIPE obj + -- The primop returns the null pointer in two situations at the moment + -- 1. The lookup fails for whatever reason + -- 2. Profiling is not enabled. + -- It would be good to distinguish between these two cases somehow. + if ipe == nullPtr + then return [] + else infoProvToStrings (ipeProv ipe) ===================================== rts/PrimOps.cmm ===================================== @@ -2409,6 +2409,13 @@ stg_closureSizzezh (P_ clos) return (len); } +stg_whereFromzh (P_ clos) +{ + P_ ipe; + (ipe) = foreign "C" lookupIPE(UNTAG(clos) "ptr"); + return (ipe); +} + /* ----------------------------------------------------------------------------- Thread I/O blocking primitives -------------------------------------------------------------------------- */ ===================================== rts/Profiling.c ===================================== @@ -6,7 +6,6 @@ * * ---------------------------------------------------------------------------*/ -#if defined(PROFILING) #include "PosixSource.h" #include "Rts.h" @@ -24,6 +23,9 @@ #include #include +// TODO: These above includes are only used for lookupIPE when profiling is +// not enabled. +#if defined(PROFILING) #if defined(DEBUG) || defined(PROFILING) #include "Trace.h" @@ -1054,3 +1056,28 @@ debugCCS( CostCentreStack *ccs ) #endif /* DEBUG */ #endif /* PROFILING */ + +// MP: TODO: This should not be a linear search, need to improve +// the IPE_LIST structure +#if defined(PROFILING) +InfoProvEnt * lookupIPE(StgClosure *clos) +{ + StgInfoTable * info; + info = GET_INFO(clos); + InfoProvEnt *ip, *next; + //printf("%p\n", info); + //printf("%p\n\n", clos); + for (ip = IPE_LIST; ip != NULL; ip = next) { + if (ip->info == info) { + //printf("Found %p\n", ip->info); + return ip; + } + next = ip->link; + } +} +#else +InfoProvEnt * lookupIPE(StgClosure *info STG_UNUSED) +{ + return ; +} +#endif \ No newline at end of file ===================================== rts/RtsSymbols.c ===================================== @@ -546,6 +546,7 @@ SymI_HasProto(registerCcList) \ SymI_HasProto(registerInfoProvList) \ SymI_HasProto(registerCcsList) \ + SymI_HasProto(lookupIPE) \ SymI_HasProto(era) #else #define RTS_PROF_SYMBOLS /* empty */ @@ -680,6 +681,7 @@ SymI_HasProto(initLinker_) \ SymI_HasProto(stg_unpackClosurezh) \ SymI_HasProto(stg_closureSizzezh) \ + SymI_HasProto(stg_whereFromzh) \ SymI_HasProto(stg_getApStackValzh) \ SymI_HasProto(stg_getSparkzh) \ SymI_HasProto(stg_numSparkszh) \ ===================================== testsuite/tests/profiling/should_run/all.T ===================================== @@ -150,3 +150,9 @@ test('T15897', makefile_test, ['T15897']) test('T17572', [], compile_and_run, ['']) + +test('staticcallstack001', + # unoptimised results are different w.r.t. CAF attribution + [ omit_ways(['ghci-ext-prof']), # produces a different stack + ], compile_and_run, + ['-O0 -g3']) ===================================== testsuite/tests/profiling/should_run/staticcallstack001.hs ===================================== @@ -0,0 +1,19 @@ +module Main where + +import GHC.Stack.CCS + +data D = D Int deriving Show + +ff = id (D 5) +{-# NOINLINE ff #-} +{-# NOINLINE qq #-} + +qq x = D x + +caf = D 5 + +main = do + print =<< whereFrom (D 5) + print =<< whereFrom caf + print =<< whereFrom (id (D 5)) + ===================================== testsuite/tests/profiling/should_run/staticcallstack001.stdout ===================================== @@ -0,0 +1,3 @@ +["D_Main_4_con_info","0","main","Main","staticcallstack001.hs:16:13-27"] +["caf_info","21","caf","Main","staticcallstack001.hs:13:1-3"] +["sat_sYR_info","15","main","Main","staticcallstack001.hs:18:13-32"] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1ba64ae7d3536b2e09fa1f2aca8e8ce1aec2af6d...d98f44c87c7b566e6ba2d499b30f8fbc8bbc9feb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1ba64ae7d3536b2e09fa1f2aca8e8ce1aec2af6d...d98f44c87c7b566e6ba2d499b30f8fbc8bbc9feb 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 Tue Nov 3 10:49:27 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 05:49:27 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fa135b7c2bf9_7853fb61d9724a466017b@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 44780e10 by Ben Gamari at 2020-11-03T05:49:14-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - f9888c86 by Matthew Pickering at 2020-11-03T05:49:15-05:00 Update inlining flags documentation - - - - - 31974f3c by Sylvain Henry at 2020-11-03T05:49:17-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - a333b650 by Alan Zimmerman at 2020-11-03T05:49:17-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - e2f46a26 by Sylvain Henry at 2020-11-03T05:49:19-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - d4d5c04f by Sylvain Henry at 2020-11-03T05:49:21-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - + compiler/GHC/Linker.hs - + compiler/GHC/Linker/Dynamic.hs - compiler/GHC/SysTools/ExtraObj.hs → compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Runtime/Linker.hs → compiler/GHC/Linker/Loader.hs - + compiler/GHC/Linker/MacOS.hs - + compiler/GHC/Linker/Static.hs - compiler/GHC/Runtime/Linker/Types.hs → compiler/GHC/Linker/Types.hs - + compiler/GHC/Linker/Unit.hs - + compiler/GHC/Linker/Windows.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/SysTools.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Unit/Finder.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/adea95f6e7f4f369325eef133040517e902c3362...d4d5c04fc59ec24d52ebf778ba59381caec78c62 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/adea95f6e7f4f369325eef133040517e902c3362...d4d5c04fc59ec24d52ebf778ba59381caec78c62 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 Tue Nov 3 11:25:39 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 06:25:39 -0500 Subject: [Git][ghc/ghc][wip/con-info] 4 commits: Add a flag to control distinct constructor tables Message-ID: <5fa13e33c9903_7853fb640dd11bc6711c8@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: ec3c5fa0 by Matthew Pickering at 2020-11-03T11:24:18+00:00 Add a flag to control distinct constructor tables - - - - - 4c01d7e5 by Matthew Pickering at 2020-11-03T11:25:05+00:00 small fixes to diff - - - - - 9f4e3ea3 by Matthew Pickering at 2020-11-03T11:25:14+00:00 Start of note - - - - - 343040a9 by Matthew Pickering at 2020-11-03T11:25:22+00:00 More clear name in eventlog - - - - - 7 changed files: - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/StgToCmm/Types.hs - rts/eventlog/EventLog.c Changes: ===================================== compiler/GHC/CoreToStg.hs ===================================== @@ -925,7 +925,7 @@ lookupBinding env v = case lookupVarEnv env v of incDc :: DataCon -> CtsM (Maybe Int) incDc dc | isUnboxedTupleDataCon dc = return Nothing -incDc dc = CtsM $ \_ _ -> do +incDc dc = CtsM $ \dflags _ -> if not (gopt Opt_DistinctConstructorTables dflags) then return Nothing else do env <- get cc <- ask let dcMap' = alterUniqMap (maybe (Just [(0, cc)]) (\xs@((k, _):_) -> Just ((k + 1, cc) : xs))) (provDC env) dc ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -111,10 +111,10 @@ codeOutput dflags this_mod filenm location foreign_fps pkg_deps genForeignStubs ; a <- case backend dflags of NCG -> outputAsm dflags this_mod location filenm linted_cmm_stream - ViaC -> outputC dflags filenm linted_cmm_stream pkg_deps + ViaC -> outputC dflags filenm linted_cmm_stream pkg_deps LLVM -> outputLlvm dflags filenm linted_cmm_stream - Interpreter -> panic "codeOutput: HscInterpreted" - NoBackend -> panic "codeOutput: HscNothing" + Interpreter -> panic "codeOutput: Interpreter" + NoBackend -> panic "codeOutput: NoBackend" ; stubs <- genForeignStubs ; stubs_exist <- outputForeignStubs dflags this_mod location stubs ; return (filenm, stubs_exist, foreign_fps, a) @@ -311,6 +311,7 @@ profilingInitCode platform this_mod (local_CCs, singleton_CCSs) -- | Generate code to initialise info pointer origin +-- See note [Mapping Info Tables to Source Positions] ipInitCode :: [CmmInfoTable] -> DynFlags -> Module -> InfoTableProvMap -> SDoc ipInitCode used_info dflags this_mod (InfoTableProvMap dcmap closure_map) = if not (sccProfilingEnabled dflags) @@ -342,4 +343,50 @@ ipInitCode used_info dflags this_mod (InfoTableProvMap dcmap closure_map) <> semi +{- +Note [Mapping Info Tables to Source Positions] + +When debugging memory issues it is very useful to be able to map a specific closure +to a position in the source. The prime example is being able to map a THUNK to +a specific place in the source program, the mapping is usually quite precise because +a fresh info table is created for each distinct THUNK. + +There are two parts to the implementation + +1. The SourceNote information is used in order to give a source location to +some specific closures. +2. During code generation, a mapping from the info table to the statically +determined location is emitted which can then be queried at runtime by +various tools. + +-- Giving Source Locations to Closures + +### Thunks +### Constructors + + + + +-- Code Generation + +After the mapping has been collected during compilation, a C stub is generated which +creates the static map from info table pointer to the information about where that +info table was created from. + +This information can be consumed in two ways. + +1. The complete mapping is emitted into the eventlog so that external tools such +as eventlog2html can use the information with the heap profile by info table mode. +2. The `lookupIPE` function can be used via the `whereFrom#` primop to introspect +information about a closure in a running Haskell program. + +Note [Distinct Info Tables for Constructors] + +In the old times, each usage of a data constructor used the same info table. +This made it impossible to distinguish which actual usuage of a data constructor was +contributing primarily to the allocation in a program. Using the TODO flag you +can cause code generation to generate a distinct info table for each usage of +a constructor. Then, when inspecting the heap you can see precisely which usage of a constructor +was responsible for each allocation. +-} \ No newline at end of file ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -130,6 +130,8 @@ data GeneralFlag | Opt_FastLlvm -- hidden flag | Opt_NoTypeableBinds + | Opt_DistinctConstructorTables + | Opt_WarnIsError -- -Werror; makes warnings fatal | Opt_ShowWarnGroups -- Show the group a warning belongs to | Opt_HideSourcePaths -- Hide module source/object paths ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -218,7 +218,6 @@ import GHC.Unit.Module.Status import GHC.Unit.Module.Imported import GHC.Unit.Module.Graph import GHC.Unit.Home.ModInfo -import GHC.Types.Name.Set import GHC.Unit.Home import GHC.Unit.State import GHC.Unit.Module.Deps @@ -1643,7 +1642,7 @@ doCodeGen hsc_env this_mod denv data_tycons Stream.mapAccumL_ (cmmPipeline hsc_env) (emptySRT this_mod) ppr_stream1 <&> first (srtMapNonCAFs . moduleSRTMap) - return CgInfos{ cgNonCafs = non_cafs, cgLFInfos = lf_infos, cgNameSet = emptyNameSet } + return CgInfos{ cgNonCafs = non_cafs, cgLFInfos = lf_infos } dump2 a = do unless (null a) $ ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2914,6 +2914,8 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + , make_ord_flag defGhcFlag "fdistinct-constructor-tables" + (NoArg (setGeneralFlag Opt_DistinctConstructorTables)) ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) ===================================== compiler/GHC/StgToCmm/Types.hs ===================================== @@ -86,7 +86,6 @@ data CgInfos = CgInfos -- either not exported of CAFFY. , cgLFInfos :: !ModuleLFInfos -- ^ LambdaFormInfos of exported closures in the current module. - , cgNameSet :: !NameSet } -------------------------------------------------------------------------------- ===================================== rts/eventlog/EventLog.c ===================================== @@ -104,7 +104,7 @@ char *EventDesc[] = { [EVENT_HACK_BUG_T9003] = "Empty event for bug #9003", [EVENT_HEAP_PROF_BEGIN] = "Start of heap profile", [EVENT_HEAP_PROF_COST_CENTRE] = "Cost center definition", - [EVENT_IPE] = "ITE", + [EVENT_IPE] = "Info Table Source Position", [EVENT_HEAP_PROF_SAMPLE_BEGIN] = "Start of heap profile sample", [EVENT_HEAP_BIO_PROF_SAMPLE_BEGIN] = "Start of heap profile (biographical) sample", [EVENT_HEAP_PROF_SAMPLE_END] = "End of heap profile sample", View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d98f44c87c7b566e6ba2d499b30f8fbc8bbc9feb...343040a911599fc6096ac8bcc98f591360da1a9a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d98f44c87c7b566e6ba2d499b30f8fbc8bbc9feb...343040a911599fc6096ac8bcc98f591360da1a9a 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 Tue Nov 3 12:06:14 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 03 Nov 2020 07:06:14 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] Fix isWeakDmd, hopefully fixing an arduous performance regression in code generation Message-ID: <5fa147b6b38c2_785100b024c68380@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 901e38d7 by Sebastian Graf at 2020-11-03T13:06:08+01:00 Fix isWeakDmd, hopefully fixing an arduous performance regression in code generation - - - - - 1 changed file: - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -712,7 +712,7 @@ isScaleInvariantCleanDmd (Call n _) = isScaleInvariantCard n -- See Note [Scalin -- was incomplete. -- See Note [Lazy and unleashable free variables] in "GHC.Core.Opt.DmdAnal". isWeakDmd :: Demand -> Bool -isWeakDmd (n :* cd) = not (isStrict n) && isScaleInvariantCleanDmd cd +isWeakDmd dmd@(n :* _) = not (isStrict n) && isScaleInvariantDmd dmd -- | @keepAliveDmdType dt vs@ makes sure that the Ids in @vs@ have -- /some/ usage in the returned demand types -- they are not Absent. @@ -1201,9 +1201,6 @@ multDmdEnv n env -- match multDmd (see #13977). | n == C_11 = env | otherwise = mapVarEnv (multDmd n) env - -- For the Absent case just discard alC_ sage information - -- We only processed the thing at all to analyse the body - -- See Note [Always analyse in virgin pass] -- | See Note [Scaling demands] reuseEnv :: DmdEnv -> DmdEnv View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/901e38d7bf3bbe96dc252e05a2aa43a912f9f59c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/901e38d7bf3bbe96dc252e05a2aa43a912f9f59c 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 Tue Nov 3 13:28:34 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 03 Nov 2020 08:28:34 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-always-pic] [AArch64] Aarch64 Always PIC Message-ID: <5fa15b0271769_7856ff89707101a@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC Commits: c788de1a by Moritz Angermann at 2020-11-03T13:27:27+00:00 [AArch64] Aarch64 Always PIC - - - - - 6 changed files: - compiler/GHC/Driver/Session.hs - docs/users_guide/runtime_control.rst - includes/rts/Flags.h - rts/Libdw.c - rts/Linker.c - rts/LinkerInternals.h Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3796,8 +3796,21 @@ validHoleFitsImpliedGFlags default_PIC :: Platform -> [GeneralFlag] default_PIC platform = case (platformOS platform, platformArch platform) of - (OSDarwin, ArchX86_64) -> [Opt_PIC] - (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in + -- Darwin always requires PIC. Especially on more recent macOS releases + -- there will be a 4GB __ZEROPAGE that prevents us from using 32bit addresses + -- while we could work around this on x86_64 (like WINE does), we won't be + -- able on aarch64, where this is enforced. + (OSDarwin, ArchX86_64) -> [Opt_PIC] + -- For AArch64, we need to always have PIC enabled. The relocation model + -- on AArch64 does not permit arbitrary relocations. Under ASLR, we can't + -- control much how far apart symbols are in memory for our in-memory static + -- linker; and thus need to ensure we get sufficiently capable relocations. + -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top + -- of that. Subsequently we expect all code on aarch64/linux (and macOS) to + -- be built with -fPIC. + (OSDarwin, ArchARM64) -> [Opt_PIC] + (OSLinux, ArchARM64) -> [Opt_PIC, Opt_ExternalDynamicRefs] + (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release -- (1 May 2013) we need to -- always generate PIC. See ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -327,8 +327,10 @@ Miscellaneous RTS options an object, the linker will probably fail with an error message when the problem is detected. - On some platforms where PIC is always the case, e.g. x86_64 MacOS X, this - flag is enabled by default. + On some platforms where PIC is always the case, e.g. macOS and openBSD on + x86_64, and macOS and Linux on aarch64 this flag is enabled by default. + One repercussion of this is that referenced system libraries also need to be + compiled with ``-fPIC`` if we need to load them in the runtime linker. .. rts-flag:: -xm ⟨address⟩ ===================================== includes/rts/Flags.h ===================================== @@ -200,7 +200,7 @@ typedef struct _CONCURRENT_FLAGS { * files were compiled with -fPIC -fexternal-dynamic-refs and load them * anywhere in the address space. */ -#if defined(x86_64_HOST_ARCH) && defined(darwin_HOST_OS) +#if defined(darwin_HOST_OS) || defined(aarch64_HOST_ARCH) #define DEFAULT_LINKER_ALWAYS_PIC true #else #define DEFAULT_LINKER_ALWAYS_PIC false ===================================== rts/Libdw.c ===================================== @@ -133,8 +133,9 @@ int libdwLookupLocation(LibdwSession *session, Location *frame, Dwfl_Module *mod = dwfl_addrmodule(session->dwfl, addr); if (mod == NULL) return 1; + void *object_file = &frame->object_file; dwfl_module_info(mod, NULL, NULL, NULL, NULL, NULL, - &frame->object_file, NULL); + object_file, NULL); // Find function name frame->function = dwfl_module_addrname(mod, addr); ===================================== rts/Linker.c ===================================== @@ -1022,42 +1022,6 @@ resolveSymbolAddr (pathchar* buffer, int size, } #if RTS_LINKER_USE_MMAP - -/* ----------------------------------------------------------------------------- - Occationally we depend on mmap'd region being close to already mmap'd regions. - - Our static in-memory linker may be restricted by the architectures relocation - range. E.g. aarch64 has a +-4GB range for PIC code, thus we'd preferrably - get memory for the linker close to existing mappings. mmap on it's own is - free to return any memory location, independent of what the preferred - location argument indicates. - - For example mmap (via qemu) might give you addresses all over the available - memory range if the requested location is already occupied. - - mmap_next will do a linear search from the start page upwards to find a - suitable location that is as close as possible to the locations (proivded - via the first argument). - -------------------------------------------------------------------------- */ - -void* -mmap_next(void *addr, size_t length, int prot, int flags, int fd, off_t offset) { - if(addr == NULL) return mmap(addr, length, prot, flags, fd, offset); - // we are going to look for up to pageSize * 1024 * 1024 (4GB) from the - // address. - size_t pageSize = getPageSize(); - for(int i = (uintptr_t)addr & (pageSize-1) ? 1 : 0; i < 1024*1024; i++) { - void *target = (void*)(((uintptr_t)addr & ~(pageSize-1))+(i*pageSize)); - void *mem = mmap(target, length, prot, flags, fd, offset); - if(mem == NULL) return mem; - if(mem == target) return mem; - munmap(mem, length); - IF_DEBUG(linker && (i % 1024 == 0), - debugBelch("mmap_next failed to find suitable space in %p - %p\n", addr, target)); - } - return NULL; -} - // // Returns NULL on failure. // @@ -1089,8 +1053,8 @@ mmap_again: debugBelch("mmapForLinker: \tflags %#0x\n", MAP_PRIVATE | tryMap32Bit | fixed | flags)); - result = mmap_next(map_addr, size, prot, - MAP_PRIVATE|tryMap32Bit|fixed|flags, fd, offset); + result = mmap(map_addr, size, prot, + MAP_PRIVATE|tryMap32Bit|fixed|flags, fd, offset); if (result == MAP_FAILED) { sysErrorBelch("mmap %" FMT_Word " bytes at %p",(W_)size,map_addr); ===================================== rts/LinkerInternals.h ===================================== @@ -14,7 +14,6 @@ #if RTS_LINKER_USE_MMAP #include -void* mmap_next(void *addr, size_t length, int prot, int flags, int fd, off_t offset); #endif void printLoadedObjects(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c788de1a35c525f0efc26d90912581f89971501c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c788de1a35c525f0efc26d90912581f89971501c 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 Tue Nov 3 13:39:18 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Tue, 03 Nov 2020 08:39:18 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18920 Message-ID: <5fa15d8688e6f_7853fb643dfcd64715042@gitlab.haskell.org.mail> Ryan Scott pushed new branch wip/T18920 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18920 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 Tue Nov 3 14:10:06 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 03 Nov 2020 09:10:06 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] Bump text again :facepalm: Message-ID: <5fa164be19321_7853fb657cdefa4721686@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 70d20e24 by Moritz Angermann at 2020-11-03T14:09:51+00:00 Bump text again :facepalm: - - - - - 1 changed file: - libraries/text Changes: ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit 2c4f7bb2a69a3cd13b55253c1aa71326530c4dec +Subproject commit b655cd33155d7e2572a224cc898899bc180e63ef View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/70d20e24088fe6a36dfd800e4f56796e5b98a60c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/70d20e24088fe6a36dfd800e4f56796e5b98a60c 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 Tue Nov 3 14:10:08 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 03 Nov 2020 09:10:08 -0500 Subject: [Git][ghc/ghc][wip/andreask/32bit_cmp_fix] 2 commits: NCG: Fix 64bit int comparisons on 32bit x86 Message-ID: <5fa164c0d8ba9_7858488034721895@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/32bit_cmp_fix at Glasgow Haskell Compiler / GHC Commits: fb46315a by Andreas Klebinger at 2020-11-03T14:26:37+01:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b970d083 by Andreas Klebinger at 2020-11-03T15:09:46+01:00 Test NCG 64bit comparisons - - - - - 6 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1823,6 +1823,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1840,22 +1869,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] == ![x >= y] + GTT -> intComparison GE false true r1_lo r2_lo + GU -> intComparison GEU false true r1_lo r2_lo + -- [x <= y] == [y >= x] + LE -> intComparison GE false true r2_lo r1_lo + LEU -> intComparison GEU false true r2_lo r1_lo + -- [x < y] == ![x >= x] + LTT -> intComparison GE true false r1_lo r2_lo + LU -> intComparison GEU true false r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/GHC/CmmToAsm/X86/Cond.hs ===================================== @@ -11,22 +11,22 @@ import GHC.Prelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condToUnsigned :: Cond -> Cond ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#ifdef __GLASGOW_HASKELL__ +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/092d1eeafe6f24b5fab1ff7c4aff622331677717...b970d08312f7aa5b5c2552ae30881783ef319a68 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/092d1eeafe6f24b5fab1ff7c4aff622331677717...b970d08312f7aa5b5c2552ae30881783ef319a68 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 Tue Nov 3 14:11:29 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 03 Nov 2020 09:11:29 -0500 Subject: [Git][ghc/ghc][wip/andreask/32bit_cmp_fix] Test NCG 64bit comparisons Message-ID: <5fa165116a75a_7853fb5ebcb169c7231f5@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/32bit_cmp_fix at Glasgow Haskell Compiler / GHC Commits: db555fe7 by Andreas Klebinger at 2020-11-03T15:11:11+01:00 Test NCG 64bit comparisons - - - - - 4 changed files: - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm Changes: ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/db555fe7b256e2728f914cc654338ed8e84121e2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/db555fe7b256e2728f914cc654338ed8e84121e2 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 Tue Nov 3 14:54:22 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 03 Nov 2020 09:54:22 -0500 Subject: [Git][ghc/ghc][wip/andreask/test_pkg_db] Testsuite: Support for user supplied package dbs Message-ID: <5fa16f1e71967_78589f98b07348d6@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/test_pkg_db at Glasgow Haskell Compiler / GHC Commits: de3fc83b by Andreas Klebinger at 2020-11-03T15:54:07+01:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 4 changed files: - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk Changes: ===================================== testsuite/driver/runtests.py ===================================== @@ -71,6 +71,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -104,6 +105,8 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testglobals.py ===================================== @@ -169,6 +169,9 @@ class TestConfig: # Baseline commit for performane metric comparisons. self.baseline_commit = None # type: Optional[GitRef] + # Additional package dbs to inspect for test dependencies. + self.test_package_db = [] # type: [PathToPackageDb] + # Should we skip performance tests self.skip_perf_tests = False ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de3fc83bef356d6bca6d659f0ce4b27734ac6f06 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de3fc83bef356d6bca6d659f0ce4b27734ac6f06 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 Tue Nov 3 15:01:36 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 03 Nov 2020 10:01:36 -0500 Subject: [Git][ghc/ghc][wip/andreask/test_pkg_db] Testsuite: Support for user supplied package dbs Message-ID: <5fa170d098ec1_78589f98b073692f@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/test_pkg_db at Glasgow Haskell Compiler / GHC Commits: 45bc1b4a by Andreas Klebinger at 2020-11-03T16:01:21+01:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 4 changed files: - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk Changes: ===================================== testsuite/driver/runtests.py ===================================== @@ -71,6 +71,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -104,6 +105,9 @@ config.summary_file = args.summary_file config.no_print_summary = args.no_print_summary config.baseline_commit = args.perf_baseline +if args.test_package_db: + config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testglobals.py ===================================== @@ -169,6 +169,9 @@ class TestConfig: # Baseline commit for performane metric comparisons. self.baseline_commit = None # type: Optional[GitRef] + # Additional package dbs to inspect for test dependencies. + self.test_package_db = [] # type: [PathToPackageDb] + # Should we skip performance tests self.skip_perf_tests = False ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/45bc1b4ae27d08c27c67ee7a33a77cd153acd54d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/45bc1b4ae27d08c27c67ee7a33a77cd153acd54d 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 Tue Nov 3 16:01:42 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 03 Nov 2020 11:01:42 -0500 Subject: [Git][ghc/ghc][wip/andreask/32bit_cmp_fix] NCG: Fix 64bit int comparisons on 32bit x86 Message-ID: <5fa17ee68f849_7853fb65da0a4f87573fa@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/32bit_cmp_fix at Glasgow Haskell Compiler / GHC Commits: 9d18b750 by Andreas Klebinger at 2020-11-03T17:01:16+01:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - 6 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1823,6 +1823,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1840,22 +1869,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/GHC/CmmToAsm/X86/Cond.hs ===================================== @@ -11,22 +11,22 @@ import GHC.Prelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condToUnsigned :: Cond -> Cond ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d18b750c25350ab2e50bcef40231033cdbc29d6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d18b750c25350ab2e50bcef40231033cdbc29d6 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 Tue Nov 3 16:03:10 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 11:03:10 -0500 Subject: [Git][ghc/ghc][wip/con-info] Split IPE stuff into separate file - separate from profiling Message-ID: <5fa17f3ee9cba_7853fb5948524907595cc@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 3bc500f5 by Matthew Pickering at 2020-11-03T16:02:54+00:00 Split IPE stuff into separate file - separate from profiling - - - - - 12 changed files: - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - includes/Rts.h - includes/rts/Profiling.h - libraries/base/GHC/Stack/CCS.hsc - + rts/IPE.c - + rts/IPE.h - rts/Profiling.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/rts.cabal.in Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -314,7 +314,7 @@ profilingInitCode platform this_mod (local_CCs, singleton_CCSs) -- See note [Mapping Info Tables to Source Positions] ipInitCode :: [CmmInfoTable] -> DynFlags -> Module -> InfoTableProvMap -> SDoc ipInitCode used_info dflags this_mod (InfoTableProvMap dcmap closure_map) - = if not (sccProfilingEnabled dflags) + = if not (gopt Opt_InfoTableMap dflags) then empty else withPprStyle (PprCode CStyle) $ pprTraceIt "ipInitCode" $ vcat $ map emit_ipe_decl ents ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -131,6 +131,7 @@ data GeneralFlag | Opt_NoTypeableBinds | Opt_DistinctConstructorTables + | Opt_InfoTableMap | Opt_WarnIsError -- -Werror; makes warnings fatal | Opt_ShowWarnGroups -- Show the group a warning belongs to ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2916,6 +2916,9 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fdistinct-constructor-tables" (NoArg (setGeneralFlag Opt_DistinctConstructorTables)) + + , make_ord_flag defGhcFlag "finfo-table-map" + (NoArg (setGeneralFlag Opt_InfoTableMap)) ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) ===================================== includes/Rts.h ===================================== @@ -235,6 +235,7 @@ void _assertFail(const char *filename, unsigned int linenum) #include "rts/PrimFloat.h" #include "rts/Main.h" #include "rts/Profiling.h" +#include "rts/IPE.h" #include "rts/StaticPtrTable.h" #include "rts/Libdw.h" #include "rts/LibdwPool.h" ===================================== includes/rts/Profiling.h ===================================== @@ -14,6 +14,4 @@ #pragma once void registerCcList(CostCentre **cc_list); -void registerInfoProvList(InfoProvEnt **cc_list); -void registerCcsList(CostCentreStack **cc_list); -InfoProvEnt * lookupIPE(StgClosure *info); \ No newline at end of file +void registerCcsList(CostCentreStack **cc_list); \ No newline at end of file ===================================== libraries/base/GHC/Stack/CCS.hsc ===================================== @@ -45,7 +45,6 @@ import GHC.Ptr import GHC.Foreign as GHC import GHC.IO.Encoding import GHC.List ( concatMap, reverse ) -import Prelude (putStrLn, print) #define PROFILING #include "Rts.h" @@ -161,12 +160,12 @@ ipModule p = (# peek InfoProv, module) p ipSrcLoc p = (# peek InfoProv, srcloc) p infoProvToStrings :: Ptr InfoProv -> IO [String] -infoProvToStrings ip = do - name <- GHC.peekCString utf8 =<< ipName ip - desc <- GHC.peekCString utf8 =<< ipDesc ip - label <- GHC.peekCString utf8 =<< ipLabel ip - mod <- GHC.peekCString utf8 =<< ipModule ip - loc <- GHC.peekCString utf8 =<< ipSrcLoc ip +infoProvToStrings infop = do + name <- GHC.peekCString utf8 =<< ipName infop + desc <- GHC.peekCString utf8 =<< ipDesc infop + label <- GHC.peekCString utf8 =<< ipLabel infop + mod <- GHC.peekCString utf8 =<< ipModule infop + loc <- GHC.peekCString utf8 =<< ipSrcLoc infop return [name, desc, label, mod, loc] -- TODO: Add structured output of whereFrom ===================================== rts/IPE.c ===================================== @@ -0,0 +1,82 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team, 1998-2000 + * + * Support for mapping info table pointers to source locations + * + * ---------------------------------------------------------------------------*/ + + +#include "PosixSource.h" +#include "Rts.h" + +#include "RtsUtils.h" +#include "Profiling.h" +#include "Arena.h" +#include "Printer.h" +#include "Capability.h" + +#include +#include + +#if defined(DEBUG) || defined(PROFILING) +#include "Trace.h" +#endif + +InfoProvEnt *IPE_LIST = NULL; + +static void +dumpIPEToEventLog(void) +{ + InfoProvEnt *ip, *next; + for (ip = IPE_LIST; ip != NULL; ip = next) { + next = ip->link; + traceIPE(ip->info, ip->prov.table_name, ip->prov.closure_desc, ip->prov.label, + ip->prov.module, ip->prov.srcloc); + } +} + +/* ----------------------------------------------------------------------------- + Registering IPEs + + Registering a IPE consists of linking it onto the list of registered IPEs + + IPEs are registered at startup by a C constructor function + generated by the compiler (ProfInit.hs) in the _stub.c file for each module. + -------------------------------------------------------------------------- */ + +static void +registerInfoProvEnt(InfoProvEnt *ipe) +{ + //if (ipe->link == NULL) { + // + ipe->link = IPE_LIST; + IPE_LIST = ipe; + //} +} + +void registerInfoProvList(InfoProvEnt **ent_list) +{ + for (InfoProvEnt **i = ent_list; *i != NULL; i++) { + registerInfoProvEnt(*i); + } +} + + +// MP: TODO: This should not be a linear search, need to improve +// the IPE_LIST structure +InfoProvEnt * lookupIPE(StgClosure *clos) +{ + StgInfoTable * info; + info = GET_INFO(clos); + InfoProvEnt *ip, *next; + //printf("%p\n", info); + //printf("%p\n\n", clos); + for (ip = IPE_LIST; ip != NULL; ip = next) { + if (ip->info == info) { + //printf("Found %p\n", ip->info); + return ip; + } + next = ip->link; + } +} \ No newline at end of file ===================================== rts/IPE.h ===================================== @@ -0,0 +1,12 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team, 1998-2005 + * + * Support for IPE + * + * ---------------------------------------------------------------------------*/ + +#pragma once + +#include + ===================================== rts/Profiling.c ===================================== @@ -7,6 +7,7 @@ * ---------------------------------------------------------------------------*/ +#if defined(PROFILING) #include "PosixSource.h" #include "Rts.h" @@ -23,9 +24,6 @@ #include #include -// TODO: These above includes are only used for lookupIPE when profiling is -// not enabled. -#if defined(PROFILING) #if defined(DEBUG) || defined(PROFILING) #include "Trace.h" @@ -59,7 +57,6 @@ CostCentre *CC_LIST = NULL; // parent of all cost centres stacks (done in initProfiling2()). static CostCentreStack *CCS_LIST = NULL; -InfoProvEnt *IPE_LIST = NULL; #if defined(THREADED_RTS) static Mutex ccs_mutex; @@ -149,18 +146,6 @@ dumpCostCentresToEventLog(void) #endif } -static void -dumpIPEToEventLog(void) -{ -#if defined(PROFILING) - InfoProvEnt *ip, *next; - for (ip = IPE_LIST; ip != NULL; ip = next) { - next = ip->link; - traceIPE(ip->info, ip->prov.table_name, ip->prov.closure_desc, ip->prov.label, - ip->prov.module, ip->prov.srcloc); - } -#endif -} void initProfiling (void) { @@ -219,7 +204,6 @@ void initProfiling (void) } dumpCostCentresToEventLog(); - dumpIPEToEventLog(); } @@ -356,16 +340,6 @@ static void registerCCS(CostCentreStack *ccs) } } -static void -registerInfoProvEnt(InfoProvEnt *ipe) -{ - //if (ipe->link == NULL) { - // - ipe->link = IPE_LIST; - IPE_LIST = ipe; - //} -} - void registerCcList(CostCentre **cc_list) { for (CostCentre **i = cc_list; *i != NULL; i++) { @@ -380,13 +354,6 @@ void registerCcsList(CostCentreStack **cc_list) } } -void registerInfoProvList(InfoProvEnt **ent_list) -{ - for (InfoProvEnt **i = ent_list; *i != NULL; i++) { - registerInfoProvEnt(*i); - } -} - /* ----------------------------------------------------------------------------- Set CCCS when entering a function. @@ -1056,28 +1023,3 @@ debugCCS( CostCentreStack *ccs ) #endif /* DEBUG */ #endif /* PROFILING */ - -// MP: TODO: This should not be a linear search, need to improve -// the IPE_LIST structure -#if defined(PROFILING) -InfoProvEnt * lookupIPE(StgClosure *clos) -{ - StgInfoTable * info; - info = GET_INFO(clos); - InfoProvEnt *ip, *next; - //printf("%p\n", info); - //printf("%p\n\n", clos); - for (ip = IPE_LIST; ip != NULL; ip = next) { - if (ip->info == info) { - //printf("Found %p\n", ip->info); - return ip; - } - next = ip->link; - } -} -#else -InfoProvEnt * lookupIPE(StgClosure *info STG_UNUSED) -{ - return ; -} -#endif \ No newline at end of file ===================================== rts/RtsStartup.c ===================================== @@ -32,6 +32,7 @@ #include "StaticPtrTable.h" #include "Hash.h" #include "Profiling.h" +#include "IPE.h" #include "ProfHeap.h" #include "Timer.h" #include "Globals.h" ===================================== rts/RtsSymbols.c ===================================== @@ -544,9 +544,7 @@ SymI_HasProto(pushCostCentre) \ SymI_HasProto(mkCostCentre) \ SymI_HasProto(registerCcList) \ - SymI_HasProto(registerInfoProvList) \ SymI_HasProto(registerCcsList) \ - SymI_HasProto(lookupIPE) \ SymI_HasProto(era) #else #define RTS_PROF_SYMBOLS /* empty */ @@ -1002,6 +1000,8 @@ SymI_HasProto(cas) \ SymI_HasProto(_assertFail) \ SymI_HasProto(keepCAFs) \ + SymI_HasProto(registerInfoProvList) \ + SymI_HasProto(lookupIPE) \ RTS_USER_SIGNALS_SYMBOLS \ RTS_INTCHAR_SYMBOLS ===================================== rts/rts.cabal.in ===================================== @@ -155,6 +155,7 @@ library rts/Parallel.h rts/PrimFloat.h rts/Profiling.h + rts/IPE.h rts/Signals.h rts/SpinLock.h rts/StableName.h @@ -434,6 +435,7 @@ library ProfilerReport.c ProfilerReportJson.c Profiling.c + IPE.c Proftimer.c RaiseAsync.c RetainerProfile.c View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3bc500f5bc4e8cba0dad6efcf258fa4955cd10bc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3bc500f5bc4e8cba0dad6efcf258fa4955cd10bc 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 Tue Nov 3 16:13:11 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Tue, 03 Nov 2020 11:13:11 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_gc_roots] 28 commits: hadrian: Don't quote metric baseline argument Message-ID: <5fa1819759591_7853fb61c3198887658c5@gitlab.haskell.org.mail> David Eichmann pushed to branch wip/ghc-debug_gc_roots at Glasgow Haskell Compiler / GHC Commits: 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 1b7cbcf5 by David Eichmann at 2020-11-03T15:45:29+00:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f36684e6e5d3dcf972dba64c4716f097cfc6f012...1b7cbcf53377caa9cbd6dea75e77fa10ba1fba35 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f36684e6e5d3dcf972dba64c4716f097cfc6f012...1b7cbcf53377caa9cbd6dea75e77fa10ba1fba35 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 Tue Nov 3 16:17:53 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 11:17:53 -0500 Subject: [Git][ghc/ghc][wip/con-info] Fix diff Message-ID: <5fa182b1d6861_7853fb5f345e258770113@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 0c9c403e by Matthew Pickering at 2020-11-03T16:17:37+00:00 Fix diff - - - - - 6 changed files: - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/Heap.hs - compiler/GHC/StgToCmm/Monad.hs - rts/Profiling.c Changes: ===================================== compiler/GHC/StgToCmm.hs ===================================== @@ -263,6 +263,7 @@ cgDataCon mn data_con | ty <- dataConRepArgTys data_con , rep_ty <- typePrimRep (scaledThing ty) , not (isVoidRep rep_ty) ] + ; emitClosureAndInfoTable platform dyn_info_tbl NativeDirectCall [] $ -- NB: the closure pointer is assumed *untagged* on -- entry to a constructor. If the pointer is tagged, ===================================== compiler/GHC/StgToCmm/Bind.hs ===================================== @@ -95,8 +95,8 @@ cgTopRhsClosure platform rec id ccs upd_flag args body = gen_code _ closure_label | StgApp f [] <- body, null args, isNonRec rec = do - cg_info <- getCgIdInfo f - emitDataCon closure_label indStaticInfoTable ccs [unLit (idInfoToAmode cg_info)] + cg_info <- getCgIdInfo f + emitDataCon closure_label indStaticInfoTable ccs [unLit (idInfoToAmode cg_info)] gen_code lf_info _closure_label = do { profile <- getProfile @@ -136,7 +136,7 @@ cgBind (StgNonRec name rhs) -- init cannot be used in body, so slightly better to sink it eagerly cgBind (StgRec pairs) - = do { r <- sequence $ unzipWith cgRhs pairs + = do { r <- sequence $ unzipWith cgRhs pairs ; let (id_infos, fcodes) = unzip r ; addBindsC id_infos ; (inits, body) <- getCodeR $ sequence fcodes ===================================== compiler/GHC/StgToCmm/Closure.hs ===================================== @@ -924,7 +924,7 @@ mkDataConInfoTable profile data_con mn is_static ptr_wds nonptr_wds | otherwise = ProfilingInfo ty_descr val_descr ty_descr = BS8.pack $ occNameString $ getOccName $ dataConTyCon data_con - val_descr = BS8.pack $ (occNameString $ getOccName data_con) + val_descr = BS8.pack $ occNameString $ getOccName data_con -- We need a black-hole closure info to pass to @allocDynClosure@ when we -- want to allocate the black hole on entry to a CAF. ===================================== compiler/GHC/StgToCmm/Heap.hs ===================================== @@ -49,10 +49,10 @@ import GHC.Driver.Session import GHC.Platform import GHC.Platform.Profile import GHC.Data.FastString( mkFastString, fsLit ) +import GHC.Utils.Panic( sorry ) import Control.Monad (when) import Data.Maybe (isJust) -import GHC.Utils.Panic( sorry ) ----------------------------------------------------------- -- Initialise dynamic heap objects ===================================== compiler/GHC/StgToCmm/Monad.hs ===================================== @@ -472,6 +472,7 @@ newUnique = do setState $ state { cgs_uniqs = us' } return u +------------------ getInfoDown :: FCode CgInfoDownwards getInfoDown = FCode $ \info_down state -> (info_down,state) ===================================== rts/Profiling.c ===================================== @@ -6,8 +6,8 @@ * * ---------------------------------------------------------------------------*/ - #if defined(PROFILING) + #include "PosixSource.h" #include "Rts.h" @@ -57,7 +57,6 @@ CostCentre *CC_LIST = NULL; // parent of all cost centres stacks (done in initProfiling2()). static CostCentreStack *CCS_LIST = NULL; - #if defined(THREADED_RTS) static Mutex ccs_mutex; #endif @@ -146,7 +145,6 @@ dumpCostCentresToEventLog(void) #endif } - void initProfiling (void) { // initialise our arena View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0c9c403e36795cabb32ad821d13d59b5c1993564 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0c9c403e36795cabb32ad821d13d59b5c1993564 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 Tue Nov 3 16:19:54 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 11:19:54 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Update inlining flags documentation Message-ID: <5fa1832ad8508_7853fb643facfc47786e8@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 91d990cf by Matthew Pickering at 2020-11-03T11:19:36-05:00 Update inlining flags documentation - - - - - 105a5f18 by Sylvain Henry at 2020-11-03T11:19:41-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - f8833e29 by Alan Zimmerman at 2020-11-03T11:19:41-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 9efcebe1 by Sylvain Henry at 2020-11-03T11:19:43-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 5ab50acd by Sylvain Henry at 2020-11-03T11:19:44-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - e5665bee by Sylvain Henry at 2020-11-03T11:19:46-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - + compiler/GHC/Linker.hs - + compiler/GHC/Linker/Dynamic.hs - compiler/GHC/SysTools/ExtraObj.hs → compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Runtime/Linker.hs → compiler/GHC/Linker/Loader.hs - + compiler/GHC/Linker/MacOS.hs - + compiler/GHC/Linker/Static.hs - compiler/GHC/Runtime/Linker/Types.hs → compiler/GHC/Linker/Types.hs - + compiler/GHC/Linker/Unit.hs - + compiler/GHC/Linker/Windows.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/SysTools.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Unit/Finder.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4d5c04fc59ec24d52ebf778ba59381caec78c62...e5665bee887415fcdcaa1631e032d643deb8942c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4d5c04fc59ec24d52ebf778ba59381caec78c62...e5665bee887415fcdcaa1631e032d643deb8942c 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 Tue Nov 3 16:21:06 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 03 Nov 2020 11:21:06 -0500 Subject: [Git][ghc/ghc][wip/andreask/test_pkg_db] 50 commits: Implement -Woperator-whitespace (#18834) Message-ID: <5fa183723723a_7853fb58221d71c7831d0@gitlab.haskell.org.mail> Andreas Klebinger pushed to branch wip/andreask/test_pkg_db at Glasgow Haskell Compiler / GHC Commits: b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 09b9f2ea by Andreas Klebinger at 2020-11-03T17:20:28+01:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Regs.hs - compiler/GHC/Core.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/45bc1b4ae27d08c27c67ee7a33a77cd153acd54d...09b9f2ea42b121ec55f14b9231d6896a9191baf5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/45bc1b4ae27d08c27c67ee7a33a77cd153acd54d...09b9f2ea42b121ec55f14b9231d6896a9191baf5 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 Tue Nov 3 16:23:06 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Tue, 03 Nov 2020 11:23:06 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_gc_roots] Add rts_listThreads and rts_listMiscRoots to RtsAPI.h Message-ID: <5fa183eaf414_7853fb5a7eb55f47850a@gitlab.haskell.org.mail> David Eichmann pushed to branch wip/ghc-debug_gc_roots at Glasgow Haskell Compiler / GHC Commits: 601bf072 by David Eichmann at 2020-11-03T16:22:55+00:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 6 changed files: - includes/RtsAPI.h - rts/RtsAPI.c - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -17,6 +17,7 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" +#include "rts/Types.h" #include "rts/EventLogWriter.h" /* @@ -566,6 +567,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== rts/RtsAPI.c ===================================== @@ -809,6 +809,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +873,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/601bf072e52a92d3e4f21126abe83a93e6d089e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/601bf072e52a92d3e4f21126abe83a93e6d089e4 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 Tue Nov 3 16:47:55 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 11:47:55 -0500 Subject: [Git][ghc/ghc][wip/con-info] add back dumping to eventlog Message-ID: <5fa189bbf1b81_7853fb5e248ce5c788160@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: b71305a2 by Matthew Pickering at 2020-11-03T16:47:43+00:00 add back dumping to eventlog - - - - - 3 changed files: - rts/IPE.c - rts/IPE.h - rts/RtsStartup.c Changes: ===================================== rts/IPE.c ===================================== @@ -15,17 +15,15 @@ #include "Arena.h" #include "Printer.h" #include "Capability.h" +#include "Trace.h" #include #include -#if defined(DEBUG) || defined(PROFILING) -#include "Trace.h" -#endif InfoProvEnt *IPE_LIST = NULL; -static void +void dumpIPEToEventLog(void) { InfoProvEnt *ip, *next; ===================================== rts/IPE.h ===================================== @@ -10,3 +10,4 @@ #include +void dumpIPEToEventlog(void); ===================================== rts/RtsStartup.c ===================================== @@ -364,6 +364,7 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) #if defined(PROFILING) initProfiling(); #endif + //dumpIPEToEventlog(); initHeapProfiling(); /* start the virtual timer 'subsystem'. */ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b71305a26451fe26196627d4dccd9a7af87b690f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b71305a26451fe26196627d4dccd9a7af87b690f 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 Tue Nov 3 16:55:40 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 11:55:40 -0500 Subject: [Git][ghc/ghc][wip/con-info] Run test in all ways Message-ID: <5fa18b8c8fe87_7853fb6429cc9c0789446@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 5e13439a by Matthew Pickering at 2020-11-03T16:55:25+00:00 Run test in all ways - - - - - 1 changed file: - testsuite/tests/profiling/should_run/all.T Changes: ===================================== testsuite/tests/profiling/should_run/all.T ===================================== @@ -8,6 +8,12 @@ test('heapprof002', test('T11489', [req_profiling], makefile_test, ['T11489']) +test('staticcallstack001', + # unoptimised results are different w.r.t. CAF attribution + [ omit_ways(['ghci-ext-prof']), # produces a different stack + ], compile_and_run, + ['-O0 -g3 -fdistinct-constructor-tables -finfo-table-map']) + # Below this line, run tests only with profiling ways. setTestOpts(req_profiling) setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) @@ -151,8 +157,3 @@ test('T15897', test('T17572', [], compile_and_run, ['']) -test('staticcallstack001', - # unoptimised results are different w.r.t. CAF attribution - [ omit_ways(['ghci-ext-prof']), # produces a different stack - ], compile_and_run, - ['-O0 -g3']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e13439ae474312e5a0febc1290b5f99e92af7b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e13439ae474312e5a0febc1290b5f99e92af7b2 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 Tue Nov 3 17:01:44 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 03 Nov 2020 12:01:44 -0500 Subject: [Git][ghc/ghc][wip/con-info] Add missing file Message-ID: <5fa18cf84b9ac_785103c3510790361@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 655f9d55 by Matthew Pickering at 2020-11-03T17:01:28+00:00 Add missing file - - - - - 1 changed file: - + includes/rts/IPE.h Changes: ===================================== includes/rts/IPE.h ===================================== @@ -0,0 +1,17 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team, 2017-2018 + * + * IPE API + * + * Do not #include this file directly: #include "Rts.h" instead. + * + * To understand the structure of the RTS headers, see the wiki: + * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/source-tree/includes + * + * -------------------------------------------------------------------------- */ + +#pragma once + +void registerInfoProvList(InfoProvEnt **cc_list); +InfoProvEnt * lookupIPE(StgClosure *info); \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/655f9d557c8aeb7eabfc8c735732f0e6b137a3e8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/655f9d557c8aeb7eabfc8c735732f0e6b137a3e8 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 Tue Nov 3 18:32:26 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 03 Nov 2020 13:32:26 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 5 commits: More ppr Message-ID: <5fa1a23a8c119_785100e0d848058a8@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 5e5f9c5f by Sebastian Graf at 2020-11-03T13:09:35+01:00 More ppr - - - - - d13e36f3 by Sebastian Graf at 2020-11-03T15:27:45+01:00 trailing whitespace - - - - - c56373ec by Sebastian Graf at 2020-11-03T18:28:29+01:00 Accept testsuite changes - - - - - 7bdef557 by Sebastian Graf at 2020-11-03T18:28:49+01:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - faaba016 by Sebastian Graf at 2020-11-03T19:32:14+01:00 Fix isStrictDmd, rename it to isStrUsedDmd - - - - - 24 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr - testsuite/tests/arityanal/should_compile/Arity16.stderr - testsuite/tests/arityanal/should_compile/T18793.stderr - testsuite/tests/stranal/should_compile/T13031.stdout - testsuite/tests/stranal/should_compile/T18903.stderr - testsuite/tests/stranal/should_compile/all.T Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3450,8 +3450,7 @@ primop PrefetchAddrOp3 "prefetchAddr3#" GenPrimOp primop PrefetchValueOp3 "prefetchValue3#" GenPrimOp a -> State# s -> State# s - with strictness = { \ _arity -> mkClosedStrictSig [botDmd, topDmd] topDiv } - has_side_effects = True + with has_side_effects = True ---- primop PrefetchByteArrayOp2 "prefetchByteArray2#" GenPrimOp @@ -3468,8 +3467,7 @@ primop PrefetchAddrOp2 "prefetchAddr2#" GenPrimOp primop PrefetchValueOp2 "prefetchValue2#" GenPrimOp a -> State# s -> State# s - with strictness = { \ _arity -> mkClosedStrictSig [botDmd, topDmd] topDiv } - has_side_effects = True + with has_side_effects = True ---- primop PrefetchByteArrayOp1 "prefetchByteArray1#" GenPrimOp @@ -3486,8 +3484,7 @@ primop PrefetchAddrOp1 "prefetchAddr1#" GenPrimOp primop PrefetchValueOp1 "prefetchValue1#" GenPrimOp a -> State# s -> State# s - with strictness = { \ _arity -> mkClosedStrictSig [botDmd, topDmd] topDiv } - has_side_effects = True + with has_side_effects = True ---- primop PrefetchByteArrayOp0 "prefetchByteArray0#" GenPrimOp @@ -3504,8 +3501,7 @@ primop PrefetchAddrOp0 "prefetchAddr0#" GenPrimOp primop PrefetchValueOp0 "prefetchValue0#" GenPrimOp a -> State# s -> State# s - with strictness = { \ _arity -> mkClosedStrictSig [botDmd, topDmd] topDiv } - has_side_effects = True + with has_side_effects = True ------------------------------------------------------------------------ --- --- ===================================== compiler/GHC/Core/Opt/CprAnal.hs ===================================== @@ -319,7 +319,7 @@ cprAnalBind top_lvl env id rhs -- See Note [CPR for thunks] stays_thunk = is_thunk && not_strict is_thunk = not (exprIsHNF rhs) && not (isJoinId id) - not_strict = not (isStrictDmd (idDemandInfo id)) + not_strict = not (isStrUsedDmd (idDemandInfo id)) -- See Note [CPR for sum types] (_, ret_ty) = splitPiTys (idType id) not_a_prod = isNothing (deepSplitProductType_maybe (ae_fam_envs env) ret_ty) ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -550,7 +550,8 @@ dmdAnalRhsLetDown -- to the Id, and augment the environment with the signature as well. -- See Note [NOINLINE and strictness] dmdAnalRhsLetDown rec_flag env let_dmd id rhs - = (lazy_fv, sig, rhs') + = -- pprTrace "dmdAnalRhsLetDown" (ppr id $$ ppr let_dmd $$ ppr sig $$ ppr lazy_fv) $ + (lazy_fv, sig, rhs') where rhs_arity = idArity id rhs_dmd -- See Note [Demand analysis for join points] ===================================== compiler/GHC/Core/Opt/SetLevels.hs ===================================== @@ -103,7 +103,7 @@ import GHC.Types.Unique.Set ( nonDetStrictFoldUniqSet ) import GHC.Types.Unique.DSet ( getUniqDSet ) import GHC.Types.Var.Env import GHC.Types.Literal ( litIsTrivial ) -import GHC.Types.Demand ( StrictSig, Demand, isStrictDmd, splitStrictSig, prependArgsStrictSig ) +import GHC.Types.Demand ( StrictSig, Demand, isStrUsedDmd, splitStrictSig, prependArgsStrictSig ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Types.Name ( getOccName, mkSystemVarName ) import GHC.Types.Name.Occurrence ( occNameString ) @@ -469,7 +469,7 @@ lvlApp env orig_expr ((_,AnnVar fn), args) lvl_arg :: [Demand] -> CoreExprWithFVs -> LvlM ([Demand], LevelledExpr) lvl_arg strs arg | (str1 : strs') <- strs , is_val_arg arg - = do { arg' <- lvlMFE env (isStrictDmd str1) arg + = do { arg' <- lvlMFE env (isStrUsedDmd str1) arg ; return (strs', arg') } | otherwise = do { arg' <- lvlMFE env False arg ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -41,7 +41,7 @@ import GHC.Core.Opt.Monad ( Tick(..), SimplMode(..) ) import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) -import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd +import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrUsedDmd , mkClosedStrictSig, topDmd, seqDmd, botDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) @@ -2481,7 +2481,7 @@ There have been various earlier versions of this patch: scrut_is_demanded_var :: CoreExpr -> Bool scrut_is_demanded_var (Cast s _) = scrut_is_demanded_var s - scrut_is_demanded_var (Var _) = isStrictDmd (idDemandInfo case_bndr) + scrut_is_demanded_var (Var _) = isStrUsedDmd (idDemandInfo case_bndr) scrut_is_demanded_var _ = False This only fired if the scrutinee was a /variable/, which seems @@ -2709,7 +2709,7 @@ doCaseToLet scrut case_bndr | otherwise -- Scrut has a lifted type = exprIsHNF scrut - || isStrictDmd (idDemandInfo case_bndr) + || isStrUsedDmd (idDemandInfo case_bndr) -- See Note [Case-to-let for strictly-used binders] -------------------------------------------------- ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -329,7 +329,7 @@ addCastTo ai co = ai { ai_args = CastBy co : ai_args ai } isStrictArgInfo :: ArgInfo -> Bool -- True if the function is strict in the next argument isStrictArgInfo (ArgInfo { ai_dmds = dmds }) - | dmd:_ <- dmds = isStrictDmd dmd + | dmd:_ <- dmds = isStrUsedDmd dmd | otherwise = False argInfoAppArgs :: [ArgSpec] -> [OutExpr] ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -610,7 +610,7 @@ wantToUnbox :: FamInstEnvs -> Bool -> Type -> Demand -> Maybe ([Demand], DataCon wantToUnbox fam_envs has_inlineable_prag ty dmd = case deepSplitProductType_maybe fam_envs ty of Just dcac at DataConAppContext{ dcac_arg_tys = con_arg_tys } - | isStrictDmd dmd + | isStrUsedDmd dmd -- See Note [Unpacking arguments with product and polymorphic demands] , Just cs <- split_prod_dmd_arity dmd (length con_arg_tys) -- See Note [Do not unpack class dictionaries] ===================================== compiler/GHC/CoreToStg/Prep.hs ===================================== @@ -1359,7 +1359,7 @@ mkFloat dmd is_unlifted bndr rhs -- See Note [Pin demand info on floats] where is_hnf = exprIsHNF rhs - is_strict = isStrictDmd dmd + is_strict = isStrUsedDmd dmd emptyFloats :: Floats emptyFloats = Floats OkToSpec nilOL @@ -1446,7 +1446,7 @@ canFloat (Floats ok_to_spec fs) rhs wantFloatNested :: RecFlag -> Demand -> Bool -> Floats -> CpeRhs -> Bool wantFloatNested is_rec dmd is_unlifted floats rhs = isEmptyFloats floats - || isStrictDmd dmd + || isStrUsedDmd dmd || is_unlifted || (allLazyNested is_rec floats && exprIsHNF rhs) -- Why the test for allLazyNested? ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -19,7 +19,7 @@ module GHC.Types.Demand ( plusCard, plusDmd, plusCleanDmd, multCard, multDmd, multCleanDmd, lazyApply1Dmd, lazyApply2Dmd, strictApply1Dmd, - isAbs, isUsedOnce, isStrict, isAbsDmd, isUsedOnceDmd, isStrictDmd, + isAbs, isUsedOnce, isStrict, isAbsDmd, isUsedOnceDmd, isStrUsedDmd, isTopDmd, isSeqDmd, strictenDmd, addCaseBndrDmd, @@ -80,28 +80,6 @@ import GHC.Utils.Outputable import GHC.Utils.Panic {- -************************************************************************ -* * - Joint domain for Strictness and Absence -* * -************************************************************************ --} - -{- -************************************************************************ -* * - Strictness domain -* * -************************************************************************ - - Lazy - | - HeadStr - / \ - SCall SProd - \ / - HyperStr - Note [Exceptions and strictness] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We used to smart about catching exceptions, but we aren't anymore. @@ -173,24 +151,6 @@ See Note [Precise exceptions and strictness analysis]. -} -{- -************************************************************************ -* * - Absence domain -* * -************************************************************************ - - Used - / \ - UCall UProd - \ / - UHead - | - Count x - - | - Abs --} - addCaseBndrDmd :: Demand -- On the case binder -> [Demand] -- On the components of the constructor -> [Demand] -- Final demands for the components of the constructor @@ -285,28 +245,6 @@ Compare with: (C) making Used win for plus, but UProd win for lub * * ************************************************************************ -This domain differst from JointDemand in the sense that pure absence -is taken away, i.e., we deal *only* with non-absent demands. - -Note [Strict demands] -~~~~~~~~~~~~~~~~~~~~~ -isStrictDmd returns true only of demands that are - both strict - and used -In particular, it is False for , which can and does -arise in, say (#7319) - f x = raise# -Then 'x' is not used, so f gets strictness -> . -Now the w/w generates - fx = let x = absentError "unused" - in raise -At this point we really don't want to convert to - fx = case absentError "unused" of x -> raise -Since the program is going to diverge, this swaps one error for another, -but it's really a bad idea to *ever* evaluate an absent argument. -In #7319 we get - T7319.exe: Oops! Entered absent arg w_s1Hd{v} [lid] [base:GHC.Base.String{tc 36u}] - Note [Dealing with call demands] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Call demands are constructed and deconstructed coherently for @@ -585,9 +523,9 @@ isTopDmd dmd = dmd == topDmd isAbsDmd :: Demand -> Bool isAbsDmd (n :* _) = isAbs n -isStrictDmd :: Demand -> Bool --- See Note [Strict demands] -isStrictDmd (n :* _) = isStrict n +-- | Not absent and used strictly. See Note [Strict demands] +isStrUsedDmd :: Demand -> Bool +isStrUsedDmd (n :* _) = isStrict n && not (isAbs n) isSeqDmd :: Demand -> Bool isSeqDmd (C_11 :* cd) = cd == seqCleanDmd @@ -605,13 +543,32 @@ seqDemand (_ :* cd) = seqCleanDemand cd seqCleanDemand :: CleanDemand -> () seqCleanDemand (Prod ds) = seqDemandList ds seqCleanDemand (Call _ cd) = seqCleanDemand cd -seqCleanDemand (Poly _) = () +seqCleanDemand (Poly _) = () seqDemandList :: [Demand] -> () seqDemandList = foldr (seq . seqDemand) () -{- Note [Call demands are relative] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [Strict demands] +~~~~~~~~~~~~~~~~~~~~~~~~ +'isStrUsedDmd' returns true only of demands that are + both strict + and used +In particular, it is False for , which can and does +arise in, say (#7319) + f x = raise# +Then 'x' is not used, so f gets strictness -> . +Now the w/w generates + fx = let x = absentError "unused" + in raise +At this point we really don't want to convert to + fx = case absentError "unused" of x -> raise +Since the program is going to diverge, this swaps one error for another, +but it's really a bad idea to *ever* evaluate an absent argument. +In #7319 we get + T7319.exe: Oops! Entered absent arg w_s1Hd{v} [lid] [base:GHC.Base.String{tc 36u}] + +Note [Call demands are relative] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The expression @if b then 0 else f 1 2 + f 3 4@ uses @f@ according to the demand @UCU(CS(S(U)))@, meaning ===================================== compiler/GHC/Types/Id.hs ===================================== @@ -704,7 +704,7 @@ isStrictId id not (isJoinId id) && ( (isStrictType (idType id)) || -- Take the best of both strictnesses - old and new - (isStrictDmd (idDemandInfo id)) + (isStrUsedDmd (idDemandInfo id)) ) --------------------------------- ===================================== compiler/GHC/Types/Id/Info.hs ===================================== @@ -636,7 +636,7 @@ zapLamInfo info@(IdInfo {occInfo = occ, demandInfo = demand}) -> occ { occ_tail = NoTailCallInfo } _other -> occ - is_safe_dmd dmd = not (isStrictDmd dmd) + is_safe_dmd dmd = not (isStrUsedDmd dmd) -- | Remove all demand info on the 'IdInfo' zapDemandInfo :: IdInfo -> Maybe IdInfo ===================================== testsuite/tests/arityanal/should_compile/Arity01.stderr ===================================== @@ -10,7 +10,7 @@ F1.f2 = 1 Rec { -- RHS size: {terms: 18, types: 4, coercions: 0, joins: 0/0} F1.f1_h1 [Occ=LoopBreaker] :: Integer -> Integer -> Integer -> Integer -[GblId, Arity=3, Str=, Unf=OtherCon []] +[GblId, Arity=3, Str=, Unf=OtherCon []] F1.f1_h1 = \ (n :: Integer) (x :: Integer) (eta :: Integer) -> case GHC.Num.Integer.integerCompare x n of { @@ -33,7 +33,7 @@ f1 = F1.f1_h1 F1.f3 F1.f2 F1.f3 g :: Integer -> Integer -> Integer -> Integer -> Integer -> Integer [GblId, Arity=5, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=5,unsat_ok=True,boring_ok=False) Tmpl= \ (x1 [Occ=Once1] :: Integer) (x2 [Occ=Once1] :: Integer) (x3 [Occ=Once1] :: Integer) (x4 [Occ=Once1] :: Integer) (x5 [Occ=Once1] :: Integer) -> GHC.Num.Integer.integerAdd (GHC.Num.Integer.integerAdd (GHC.Num.Integer.integerAdd (GHC.Num.Integer.integerAdd x1 x2) x3) x4) x5}] g = \ (x1 :: Integer) (x2 :: Integer) (x3 :: Integer) (x4 :: Integer) (x5 :: Integer) -> GHC.Num.Integer.integerAdd (GHC.Num.Integer.integerAdd (GHC.Num.Integer.integerAdd (GHC.Num.Integer.integerAdd x1 x2) x3) x4) x5 @@ -47,7 +47,7 @@ F1.s1 = 3 s :: forall {t1} {t2}. Num t1 => (t1 -> t2) -> t2 [GblId, Arity=2, - Str=, + Str=<1(A,A,A,A,A,A,1C1(U))>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (@t) (@t1) ($dNum [Occ=Once1] :: Num t) (f [Occ=Once1!] :: t -> t1) -> f (fromInteger @t $dNum F1.s1)}] s = \ (@t) (@t1) ($dNum :: Num t) (f :: t -> t1) -> f (fromInteger @t $dNum F1.s1) @@ -61,7 +61,7 @@ F1.h1 = 24 h :: Integer -> Integer [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (x5 [Occ=Once1] :: Integer) -> GHC.Num.Integer.integerAdd F1.h1 x5}] h = \ (x5 :: Integer) -> GHC.Num.Integer.integerAdd F1.h1 x5 ===================================== testsuite/tests/arityanal/should_compile/Arity02.stderr ===================================== @@ -11,7 +11,7 @@ F2.f1 = 0 f2f :: forall {t1} {t2}. (t1 -> Integer -> t2) -> t1 -> t2 [GblId, Arity=2, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True) Tmpl= \ (@t) (@t1) (h [Occ=Once1!] :: t -> Integer -> t1) (x [Occ=Once1] :: t) -> h x F2.f1}] f2f = \ (@t) (@t1) (h :: t -> Integer -> t1) (x :: t) -> h x F2.f1 @@ -24,7 +24,7 @@ lvl = 1 Rec { -- RHS size: {terms: 16, types: 3, coercions: 0, joins: 0/0} F2.f2_g [Occ=LoopBreaker] :: Integer -> Integer -> Integer -[GblId, Arity=2, Str=, Unf=OtherCon []] +[GblId, Arity=2, Str=, Unf=OtherCon []] F2.f2_g = \ (x :: Integer) (y :: Integer) -> case GHC.Num.Integer.integerCompare x F2.f1 of { ===================================== testsuite/tests/arityanal/should_compile/Arity03.stderr ===================================== @@ -4,8 +4,8 @@ Result size of Tidy Core = {terms: 29, types: 13, coercions: 0, joins: 0/0} Rec { -- RHS size: {terms: 15, types: 3, coercions: 0, joins: 0/0} -F3.$wfac [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -[GblId, Arity=1, Str=, Unf=OtherCon []] +F3.$wfac [InlPrag=[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# +[GblId, Arity=1, Str=, Unf=OtherCon []] F3.$wfac = \ (ww :: GHC.Prim.Int#) -> case ww of wild { @@ -15,10 +15,10 @@ F3.$wfac end Rec } -- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0} -fac [InlPrag=NOUSERINLINE[2]] :: Int -> Int +fac [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1!] :: Int) -> case w of { GHC.Types.I# ww1 [Occ=Once1] -> case F3.$wfac ww1 of ww2 [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww2 } }}] @@ -28,7 +28,7 @@ fac = \ (w :: Int) -> case w of { GHC.Types.I# ww1 -> case F3.$wfac ww1 of ww2 { f3 :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True) Tmpl= fac}] ===================================== testsuite/tests/arityanal/should_compile/Arity04.stderr ===================================== @@ -6,7 +6,7 @@ Result size of Tidy Core = {terms: 39, types: 24, coercions: 0, joins: 0/0} f4g :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (y [Occ=Once1!] :: Int) -> case y of { GHC.Types.I# x [Occ=Once1] -> GHC.Types.I# (GHC.Prim.+# x 1#) }}] @@ -19,8 +19,8 @@ lvl = GHC.Types.I# 0# Rec { -- RHS size: {terms: 13, types: 4, coercions: 0, joins: 0/0} -F4.$wf4h [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: (Int -> Int) -> GHC.Prim.Int# -> Int -[GblId, Arity=2, Str=, Unf=OtherCon []] +F4.$wf4h [InlPrag=[2], Occ=LoopBreaker] :: (Int -> Int) -> GHC.Prim.Int# -> Int +[GblId, Arity=2, Str=, Unf=OtherCon []] F4.$wf4h = \ (w :: Int -> Int) (ww :: GHC.Prim.Int#) -> case ww of wild { @@ -30,10 +30,10 @@ F4.$wf4h end Rec } -- RHS size: {terms: 8, types: 5, coercions: 0, joins: 0/0} -f4h [InlPrag=NOUSERINLINE[2]] :: (Int -> Int) -> Int -> Int +f4h [InlPrag=[2]] :: (Int -> Int) -> Int -> Int [GblId, Arity=2, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1] :: Int -> Int) (w1 [Occ=Once1!] :: Int) -> case w1 of { GHC.Types.I# ww1 [Occ=Once1] -> F4.$wf4h w ww1 }}] f4h = \ (w :: Int -> Int) (w1 :: Int) -> case w1 of { GHC.Types.I# ww1 -> F4.$wf4h w ww1 } ===================================== testsuite/tests/arityanal/should_compile/Arity05.stderr ===================================== @@ -11,21 +11,21 @@ F5.f5g1 = 1 f5g :: forall {a} {t}. Num a => (t -> a) -> t -> a [GblId, Arity=3, - Str=, + Str=<1C1(U)>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=3,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@t) ($dNum :: Num a) (h [Occ=Once1!] :: t -> a) (z [Occ=Once1] :: t) -> + @a $dNum (h z) (fromInteger @a $dNum F5.f5g1)}] f5g = \ (@a) (@t) ($dNum :: Num a) (h :: t -> a) (z :: t) -> + @a $dNum (h z) (fromInteger @a $dNum F5.f5g1) -- RHS size: {terms: 15, types: 14, coercions: 0, joins: 0/0} -F5.$wf5h [InlPrag=NOUSERINLINE[2]] :: forall {a} {t}. (a -> a -> a) -> (Integer -> a) -> (t -> a) -> t -> (t -> a) -> a -[GblId, Arity=5, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 60 60 0 60] 120 0}] +F5.$wf5h [InlPrag=[2]] :: forall {a} {t}. (a -> a -> a) -> (Integer -> a) -> (t -> a) -> t -> (t -> a) -> a +[GblId, Arity=5, Str=<1C1(U)><1C1(U)><1C1(U)>, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 60 60 0 60] 120 0}] F5.$wf5h = \ (@a) (@t) (ww :: a -> a -> a) (ww1 :: Integer -> a) (w :: t -> a) (w1 :: t) (w2 :: t -> a) -> ww (w w1) (ww (w2 w1) (ww1 F5.f5g1)) -- RHS size: {terms: 15, types: 32, coercions: 0, joins: 0/0} -f5h [InlPrag=NOUSERINLINE[2]] :: forall {a} {t}. Num a => (t -> a) -> t -> (t -> a) -> a +f5h [InlPrag=[2]] :: forall {a} {t}. Num a => (t -> a) -> t -> (t -> a) -> a [GblId, Arity=4, - Str=, + Str=<1C1(U)><1C1(U)>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@t) (w [Occ=Once1!] :: Num a) (w1 [Occ=Once1] :: t -> a) (w2 [Occ=Once1] :: t) (w3 [Occ=Once1] :: t -> a) -> case w of { GHC.Num.C:Num ww1 [Occ=Once1] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] ww7 [Occ=Once1] -> F5.$wf5h @a @t ww1 ww7 w1 w2 w3 }}] f5h = \ (@a) (@t) (w :: Num a) (w1 :: t -> a) (w2 :: t) (w3 :: t -> a) -> case w of { GHC.Num.C:Num ww1 ww2 ww3 ww4 ww5 ww6 ww7 -> F5.$wf5h @a @t ww1 ww7 w1 w2 w3 } @@ -34,7 +34,7 @@ f5h = \ (@a) (@t) (w :: Num a) (w1 :: t -> a) (w2 :: t) (w3 :: t -> a) -> case w f5y :: Integer -> Integer [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (y [Occ=Once1] :: Integer) -> GHC.Num.Integer.integerAdd y F5.f5g1}] f5y = \ (y :: Integer) -> GHC.Num.Integer.integerAdd y F5.f5g1 ===================================== testsuite/tests/arityanal/should_compile/Arity09.stderr ===================================== @@ -20,7 +20,7 @@ F9.f1 = 10 Rec { -- RHS size: {terms: 15, types: 2, coercions: 0, joins: 0/0} F9.f91_f [Occ=LoopBreaker] :: Integer -> Integer -[GblId, Arity=1, Str=, Unf=OtherCon []] +[GblId, Arity=1, Str=, Unf=OtherCon []] F9.f91_f = \ (n :: Integer) -> case GHC.Num.Integer.integerCompare n lvl of { ===================================== testsuite/tests/arityanal/should_compile/Arity11.stderr ===================================== @@ -20,7 +20,7 @@ F11.fib2 = 2 Rec { -- RHS size: {terms: 24, types: 3, coercions: 0, joins: 0/0} F11.f11_fib [Occ=LoopBreaker] :: Integer -> Integer -[GblId, Arity=1, Str=, Unf=OtherCon []] +[GblId, Arity=1, Str=, Unf=OtherCon []] F11.f11_fib = \ (ds :: Integer) -> case GHC.Num.Integer.integerEq# ds F11.fib1 of { @@ -34,8 +34,8 @@ F11.f11_fib end Rec } -- RHS size: {terms: 52, types: 28, coercions: 0, joins: 0/5} -F11.$wfib [InlPrag=NOUSERINLINE[2]] :: forall {a} {p}. (a -> a -> Bool) -> (Num a, Num p) => a -> p -[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 460 0}] +F11.$wfib [InlPrag=[2]] :: forall {a} {p}. (a -> a -> Bool) -> (Num a, Num p) => a -> p +[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 460 0}] F11.$wfib = \ (@a) (@p) (ww :: a -> a -> Bool) (w :: Num a) (w1 :: Num p) (w2 :: a) -> let { @@ -56,7 +56,7 @@ F11.$wfib lvl3 = fromInteger @a w F11.fib1 } in letrec { fib4 [Occ=LoopBreaker] :: a -> p - [LclId, Arity=1, Str=, Unf=OtherCon []] + [LclId, Arity=1, Str=, Unf=OtherCon []] fib4 = \ (ds :: a) -> case ww ds lvl3 of { @@ -70,10 +70,10 @@ F11.$wfib fib4 w2 -- RHS size: {terms: 14, types: 21, coercions: 0, joins: 0/0} -fib [InlPrag=NOUSERINLINE[2]] :: forall {a} {p}. (Eq a, Num a, Num p) => a -> p +fib [InlPrag=[2]] :: forall {a} {p}. (Eq a, Num a, Num p) => a -> p [GblId, Arity=4, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@p) (w [Occ=Once1!] :: Eq a) (w1 [Occ=Once1] :: Num a) (w2 [Occ=Once1] :: Num p) (w3 [Occ=Once1] :: a) -> case w of { GHC.Classes.C:Eq ww1 [Occ=Once1] _ [Occ=Dead] -> F11.$wfib @a @p ww1 w1 w2 w3 }}] fib = \ (@a) (@p) (w :: Eq a) (w1 :: Num a) (w2 :: Num p) (w3 :: a) -> case w of { GHC.Classes.C:Eq ww1 ww2 -> F11.$wfib @a @p ww1 w1 w2 w3 } @@ -92,7 +92,7 @@ F11.f11_x = F11.f11_fib F11.f3 F11.f11f1 :: Integer -> Integer [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (y [Occ=Once1] :: Integer) -> GHC.Num.Integer.integerAdd F11.f11_x y}] F11.f11f1 = \ (y :: Integer) -> GHC.Num.Integer.integerAdd F11.f11_x y @@ -101,7 +101,7 @@ F11.f11f1 = \ (y :: Integer) -> GHC.Num.Integer.integerAdd F11.f11_x y f11f :: forall {p}. p -> Integer -> Integer [GblId, Arity=2, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True) Tmpl= \ (@p) _ [Occ=Dead] (eta [Occ=Once1] :: Integer) -> F11.f11f1 eta}] f11f = \ (@p) _ [Occ=Dead] -> F11.f11f1 ===================================== testsuite/tests/arityanal/should_compile/Arity14.stderr ===================================== @@ -6,7 +6,7 @@ Result size of Tidy Core = {terms: 56, types: 87, coercions: 0, joins: 0/3} F14.f1 :: forall {t}. t -> t [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True) Tmpl= \ (@t) (y [Occ=Once1] :: t) -> y}] F14.f1 = \ (@t) (y :: t) -> y @@ -17,8 +17,8 @@ F14.f2 :: Integer F14.f2 = 1 -- RHS size: {terms: 35, types: 24, coercions: 0, joins: 0/3} -F14.$wf14 [InlPrag=NOUSERINLINE[2]] :: forall {t}. (t -> t -> Bool) -> Num t => t -> t -> t -> t -[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 90 0 0] 300 0}] +F14.$wf14 [InlPrag=[2]] :: forall {t}. (t -> t -> Bool) -> Num t => t -> t -> t -> t +[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 90 0 0] 300 0}] F14.$wf14 = \ (@t) (ww :: t -> t -> Bool) (w :: Num t) (w1 :: t) (w2 :: t) -> let { @@ -27,14 +27,14 @@ F14.$wf14 lvl = fromInteger @t w F14.f2 } in letrec { f3 [Occ=LoopBreaker] :: t -> t -> t -> t - [LclId, Arity=2, Str=, Unf=OtherCon []] + [LclId, Arity=2, Str=, Unf=OtherCon []] f3 = \ (n :: t) (x :: t) -> case ww x n of { False -> F14.f1 @t; True -> let { - v [Dmd=] :: t -> t + v [Dmd=UCU(U)] :: t -> t [LclId] v = f3 n (+ @t w x lvl) } in \ (y :: t) -> v (+ @t w x y) @@ -42,10 +42,10 @@ F14.$wf14 f3 w1 w2 -- RHS size: {terms: 13, types: 34, coercions: 0, joins: 0/0} -f14 [InlPrag=NOUSERINLINE[2]] :: forall {t}. (Ord t, Num t) => t -> t -> t -> t +f14 [InlPrag=[2]] :: forall {t}. (Ord t, Num t) => t -> t -> t -> t [GblId, Arity=4, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@t) (w [Occ=Once1!] :: Ord t) (w1 [Occ=Once1] :: Num t) (w2 [Occ=Once1] :: t) (w3 [Occ=Once1] :: t) -> case w of { GHC.Classes.C:Ord _ [Occ=Dead] _ [Occ=Dead] ww3 [Occ=Once1] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] -> F14.$wf14 @t ww3 w1 w2 w3 }}] f14 = \ (@t) (w :: Ord t) (w1 :: Num t) (w2 :: t) (w3 :: t) -> case w of { GHC.Classes.C:Ord ww1 ww2 ww3 ww4 ww5 ww6 ww7 ww8 -> F14.$wf14 @t ww3 w1 w2 w3 } ===================================== testsuite/tests/arityanal/should_compile/Arity16.stderr ===================================== @@ -5,7 +5,7 @@ Result size of Tidy Core = {terms: 52, types: 87, coercions: 0, joins: 0/0} Rec { -- RHS size: {terms: 15, types: 17, coercions: 0, joins: 0/0} map2 [Occ=LoopBreaker] :: forall {t} {a}. (t -> a) -> [t] -> [a] -[GblId, Arity=2, Str=, Unf=OtherCon []] +[GblId, Arity=2, Str=, Unf=OtherCon []] map2 = \ (@t) (@a) (f :: t -> a) (ds :: [t]) -> case ds of { @@ -27,7 +27,7 @@ lvl1 = \ (@a) -> Control.Exception.Base.patError @'GHC.Types.LiftedRep @[a] lvl Rec { -- RHS size: {terms: 29, types: 35, coercions: 0, joins: 0/0} zipWith2 [Occ=LoopBreaker] :: forall {t1} {t2} {a}. (t1 -> t2 -> a) -> [t1] -> [t2] -> [a] -[GblId, Arity=3, Str=, Unf=OtherCon []] +[GblId, Arity=3, Str=, Unf=OtherCon []] zipWith2 = \ (@t) (@t1) (@a) (f :: t -> t1 -> a) (ds :: [t]) (ds1 :: [t1]) -> case ds of { ===================================== testsuite/tests/arityanal/should_compile/T18793.stderr ===================================== @@ -4,14 +4,14 @@ Result size of Tidy Core = {terms: 81, types: 74, coercions: 0, joins: 0/0} -- RHS size: {terms: 20, types: 13, coercions: 0, joins: 0/0} T18793.$wstuff [InlPrag=NOINLINE] :: Int -> (# Int, [Int] #) -[GblId, Arity=1, Str=, Unf=OtherCon []] +[GblId, Arity=1, Str=, Unf=OtherCon []] T18793.$wstuff = \ (w :: Int) -> (# w, GHC.Types.: @Int (case w of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 1#) }) (GHC.Types.: @Int (case w of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 2#) }) (GHC.Types.[] @Int)) #) -- RHS size: {terms: 8, types: 11, coercions: 0, joins: 0/0} -stuff [InlPrag=NOUSERINLINE[final]] :: Int -> [Int] +stuff [InlPrag=[final]] :: Int -> [Int] [GblId, Arity=1, - Str=, + Str=, Cpr=m2, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1] :: Int) -> case T18793.$wstuff w of { (# ww1 [Occ=Once1], ww2 [Occ=Once1] #) -> GHC.Types.: @Int ww1 ww2 }}] @@ -19,8 +19,8 @@ stuff = \ (w :: Int) -> case T18793.$wstuff w of { (# ww1, ww2 #) -> GHC.Types.: Rec { -- RHS size: {terms: 23, types: 11, coercions: 0, joins: 0/0} -T18793.$wgo1 [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: [Int] -> GHC.Prim.Int# -> GHC.Prim.Int# -[GblId, Arity=2, Str=, Unf=OtherCon []] +T18793.$wgo1 [InlPrag=[2], Occ=LoopBreaker] :: [Int] -> GHC.Prim.Int# -> GHC.Prim.Int# +[GblId, Arity=2, Str=, Unf=OtherCon []] T18793.$wgo1 = \ (w :: [Int]) (ww :: GHC.Prim.Int#) -> case w of { @@ -36,10 +36,10 @@ T18793.$wgo1 end Rec } -- RHS size: {terms: 12, types: 6, coercions: 0, joins: 0/0} -T18793.f_go1 [InlPrag=NOUSERINLINE[2]] :: [Int] -> Int -> Int +T18793.f_go1 [InlPrag=[2]] :: [Int] -> Int -> Int [GblId, Arity=2, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1] :: [Int]) (w1 [Occ=Once1!] :: Int) -> case w1 of { GHC.Types.I# ww1 [Occ=Once1] -> case T18793.$wgo1 w ww1 of ww2 [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww2 } }}] @@ -59,7 +59,7 @@ T18793.f1 = case T18793.$wstuff T18793.f2 of { (# ww1, ww2 #) -> GHC.Types.: @In f :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=False) Tmpl= \ (eta [Occ=Once1] :: Int) -> T18793.f_go1 T18793.f1 eta}] ===================================== testsuite/tests/stranal/should_compile/T13031.stdout ===================================== @@ -1,2 +1,2 @@ hello -[GblId, Arity=3, Str=b, Cpr=b, Unf=OtherCon []] +[GblId, Arity=3, Str=b, Cpr=b, Unf=OtherCon []] ===================================== testsuite/tests/stranal/should_compile/T18903.stderr ===================================== @@ -61,37 +61,35 @@ T18903.$wh [InlPrag=[2]] :: GHC.Prim.Int# -> Int Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [70] 262 10}] T18903.$wh - = \ (ww_s11L :: GHC.Prim.Int#) -> + = \ (ww :: GHC.Prim.Int#) -> let { - $wg_s11H [InlPrag=NOINLINE, Dmd=1C1((1(U),S(U)))] + $wg [InlPrag=NOINLINE, Dmd=1C1((1(U),S(U)))] :: GHC.Prim.Int# -> (# Int, Int #) [LclId, Arity=1, Str=, Unf=OtherCon []] - $wg_s11H - = \ (ww1_s11C [OS=OneShot] :: GHC.Prim.Int#) -> - case ww1_s11C of ds_X3 { + $wg + = \ (ww1 [OS=OneShot] :: GHC.Prim.Int#) -> + case ww1 of ds { __DEFAULT -> - (# GHC.Types.I# (GHC.Prim.*# 2# ds_X3), - case ds_X3 of { + (# GHC.Types.I# (GHC.Prim.*# 2# ds), + case ds of { __DEFAULT -> - case GHC.Classes.divInt# 2# ds_X3 of ww4_aZI { __DEFAULT -> - GHC.Types.I# ww4_aZI + case GHC.Classes.divInt# 2# ds of ww4 { __DEFAULT -> + GHC.Types.I# ww4 }; -1# -> T18903.h2; - 0# -> case GHC.Real.divZeroError of wild1_00 { } + 0# -> case GHC.Real.divZeroError of wild1 { } } #); - 1# -> (# GHC.Types.I# ww_s11L, T18903.h1 #) + 1# -> (# GHC.Types.I# ww, T18903.h1 #) } } in - case ww_s11L of ds_X2 { + case ww of ds { __DEFAULT -> - case $wg_s11H ds_X2 of { (# ww2_s11O, ww3_s11P #) -> - case ww2_s11O of { GHC.Types.I# x_aZS -> - case ww3_s11P of { GHC.Types.I# y_aZV -> - GHC.Types.I# (GHC.Prim.+# x_aZS y_aZV) - } + case $wg ds of { (# ww2, ww3 #) -> + case ww2 of { GHC.Types.I# x -> + case ww3 of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } } }; 1# -> T18903.h1; - 2# -> case $wg_s11H 2# of { (# ww2_s11O, ww3_s11P #) -> ww3_s11P } + 2# -> case $wg 2# of { (# ww2, ww3 #) -> ww3 } } -- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0} @@ -102,12 +100,10 @@ h [InlPrag=[2]] :: Int -> Int Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) - Tmpl= \ (w_s11I [Occ=Once1!] :: Int) -> - case w_s11I of { GHC.Types.I# ww1_s11L [Occ=Once1] -> - T18903.$wh ww1_s11L - }}] -h = \ (w_s11I :: Int) -> - case w_s11I of { GHC.Types.I# ww1_s11L -> T18903.$wh ww1_s11L } + Tmpl= \ (w [Occ=Once1!] :: Int) -> + case w of { GHC.Types.I# ww1 [Occ=Once1] -> T18903.$wh ww1 }}] +h = \ (w :: Int) -> + case w of { GHC.Types.I# ww1 -> T18903.$wh ww1 } ===================================== testsuite/tests/stranal/should_compile/all.T ===================================== @@ -57,4 +57,4 @@ test('T13380b', [ grep_errmsg('bigDeadAction') ], compile, ['-dppr-cols=200 -dd test('T18122', [ grep_errmsg(r'wfoo =') ], compile, ['-ddump-simpl']) # We care about the call demand on $wg -test('T18903', [ grep_errmsg(r'Dmd=\S+C\S+') ], compile, ['-ddump-simpl']) +test('T18903', [ grep_errmsg(r'Dmd=\S+C\S+') ], compile, ['-ddump-simpl -dsuppress-uniques']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/901e38d7bf3bbe96dc252e05a2aa43a912f9f59c...faaba016b53494042748e04229f5cc3bf9281f7c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/901e38d7bf3bbe96dc252e05a2aa43a912f9f59c...faaba016b53494042748e04229f5cc3bf9281f7c 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 Tue Nov 3 22:39:58 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 17:39:58 -0500 Subject: [Git][ghc/ghc][master] Update inlining flags documentation Message-ID: <5fa1dc3e962a8_7853fb65dc7323082493b@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 2 changed files: - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/using-optimisation.rst Changes: ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -87,6 +87,7 @@ -fstg-lift-lams-rec-args-any -fth -ftype-function-depth +-funfolding-keeness-factor -fuse-rpaths -fversion-macros -fvia-c ===================================== docs/users_guide/using-optimisation.rst ===================================== @@ -1270,19 +1270,6 @@ by saying ``-fno-wombat``. How eager should the compiler be to inline functions? -.. ghc-flag:: -funfolding-keeness-factor=⟨n⟩ - :shortdesc: *default: 1.5.* Tweak unfolding settings. - :type: dynamic - :category: - - :default: 1.5 - - .. index:: - single: inlining, controlling - single: unfolding, controlling - - How eager should the compiler be to inline functions? - .. ghc-flag:: -funfolding-use-threshold=⟨n⟩ :shortdesc: *default: 80.* Tweak unfolding settings. :type: dynamic View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78f2767d4db5e69a142ac6a408a217b11c35949d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78f2767d4db5e69a142ac6a408a217b11c35949d 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 Tue Nov 3 22:40:41 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 17:40:41 -0500 Subject: [Git][ghc/ghc][master] Linker: reorganize linker related code Message-ID: <5fa1dc6910f5c_7853fb65d7b70d4830284@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - + compiler/GHC/Linker.hs - + compiler/GHC/Linker/Dynamic.hs - compiler/GHC/SysTools/ExtraObj.hs → compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Runtime/Linker.hs → compiler/GHC/Linker/Loader.hs - + compiler/GHC/Linker/MacOS.hs - + compiler/GHC/Linker/Static.hs - compiler/GHC/Runtime/Linker/Types.hs → compiler/GHC/Linker/Types.hs - + compiler/GHC/Linker/Unit.hs - + compiler/GHC/Linker/Windows.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/SysTools.hs - compiler/GHC/SysTools/Tasks.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Home/ModInfo.hs - compiler/GHC/Unit/Module/ModGuts.hs - compiler/GHC/Unit/State.hs - compiler/ghc.cabal.in - ghc/GHCi/Leak.hs - ghc/GHCi/UI.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/14ce454f7294381225b4211dc191a167a386e380 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/14ce454f7294381225b4211dc191a167a386e380 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 Tue Nov 3 22:41:24 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 17:41:24 -0500 Subject: [Git][ghc/ghc][master] Restrict Linear arrow %1 to exactly literal 1 only Message-ID: <5fa1dc941a987_7853fb641b7b6b48348b0@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 7 changed files: - compiler/GHC/Hs/Type.hs - compiler/GHC/Parser/PostProcess.hs - + testsuite/tests/linear/should_fail/T18888.hs - + testsuite/tests/linear/should_fail/T18888.stderr - + testsuite/tests/linear/should_fail/T18888_datakinds.hs - + testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/linear/should_fail/all.T Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1982,8 +1982,8 @@ ppr_fun_ty mult ty1 ty2 -------------------------- ppr_tylit :: HsTyLit -> SDoc -ppr_tylit (HsNumTy _ i) = integer i -ppr_tylit (HsStrTy _ s) = text (show s) +ppr_tylit (HsNumTy source i) = pprWithSourceText source (integer i) +ppr_tylit (HsStrTy source s) = pprWithSourceText source (text (show s)) -- | @'hsTypeNeedsParens' p t@ returns 'True' if the type @t@ needs parentheses ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -2620,7 +2620,8 @@ mkLHsOpTy x op y = in L loc (mkHsOpTy x op y) mkMultTy :: IsUnicodeSyntax -> Located Token -> LHsType GhcPs -> (HsArrow GhcPs, AddAnn) -mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy _ 1))) +mkMultTy u tok t@(L _ (HsTyLit _ (HsNumTy (SourceText "1") 1))) + -- See #18888 for the use of (SourceText "1") above = (HsLinearArrow u, AddAnn AnnPercentOne (combineLocs tok t)) mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok)) ===================================== testsuite/tests/linear/should_fail/T18888.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE LinearTypes #-} +module T18888 where + +f :: a %001 -> b +f x = undefined x ===================================== testsuite/tests/linear/should_fail/T18888.stderr ===================================== @@ -0,0 +1,3 @@ + +T18888.hs:4:9: + Illegal type: ‘001’ Perhaps you intended to use DataKinds ===================================== testsuite/tests/linear/should_fail/T18888_datakinds.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE LinearTypes #-} +{-# LANGUAGE DataKinds #-} +module T18888 where + +f :: a %001 -> b +f x = undefined x ===================================== testsuite/tests/linear/should_fail/T18888_datakinds.stderr ===================================== @@ -0,0 +1,5 @@ + +T18888_datakinds.hs:5:9: + Expected kind ‘GHC.Types.Multiplicity’, + but ‘001’ has kind ‘GHC.Num.Natural.Natural’ + In the type signature: f :: a %001 -> b ===================================== testsuite/tests/linear/should_fail/all.T ===================================== @@ -32,3 +32,5 @@ test('LinearIf', normal, compile_fail, ['']) test('LinearPatternGuardWildcard', normal, compile_fail, ['']) test('LinearFFI', normal, compile_fail, ['']) test('LinearTHFail', normal, compile_fail, ['']) +test('T18888', normal, compile_fail, ['']) +test('T18888_datakinds', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/616bec0dee67ae4841c4e60e9406cc9c63358223 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/616bec0dee67ae4841c4e60e9406cc9c63358223 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 Tue Nov 3 22:41:55 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 17:41:55 -0500 Subject: [Git][ghc/ghc][master] Hadrian: don't fail if ghc-tarballs dir doesn't exist Message-ID: <5fa1dcb3e1879_7853fb61c20850c8373e7@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 1 changed file: - hadrian/src/Rules/Clean.hs Changes: ===================================== hadrian/src/Rules/Clean.hs ===================================== @@ -22,7 +22,7 @@ cleanSourceTree = do cleanMingwTarballs :: Action () cleanMingwTarballs = do - liftIO $ IO.removeDirectoryRecursive "ghc-tarballs" + removeDirectory "ghc-tarballs" -- Clean all temporary fs files copied by configure into the source folder cleanFsUtils :: Action () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3486ebe6f960cc55d52c1e645ee15fdeb277d0ab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3486ebe6f960cc55d52c1e645ee15fdeb277d0ab 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 Tue Nov 3 22:42:34 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 17:42:34 -0500 Subject: [Git][ghc/ghc][master] Constant-folding: don't pass through GHC's Int/Word (fix #11704) Message-ID: <5fa1dcdae0927_7853fb61c20850c841719@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - 4 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/HsToCore/Foreign/Decl.hs Changes: ===================================== compiler/GHC/Core.hs ===================================== @@ -27,8 +27,8 @@ module GHC.Core ( mkLet, mkLets, mkLetNonRec, mkLetRec, mkLams, mkApps, mkTyApps, mkCoApps, mkVarApps, mkTyArg, - mkIntLit, mkIntLitInt, - mkWordLit, mkWordLitWord, + mkIntLit, mkIntLitWrap, + mkWordLit, mkWordLitWrap, mkWord64LitWord64, mkInt64LitInt64, mkCharLit, mkStringLit, mkFloatLit, mkFloatLitFloat, @@ -1977,23 +1977,25 @@ mkTyArg ty -- | Create a machine integer literal expression of type @Int#@ from an @Integer at . -- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr' -mkIntLit :: Platform -> Integer -> Expr b --- | Create a machine integer literal expression of type @Int#@ from an @Int at . --- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr' -mkIntLitInt :: Platform -> Int -> Expr b +mkIntLit :: Platform -> Integer -> Expr b +mkIntLit platform n = Lit (mkLitInt platform n) -mkIntLit platform n = Lit (mkLitInt platform n) -mkIntLitInt platform n = Lit (mkLitInt platform (toInteger n)) +-- | Create a machine integer literal expression of type @Int#@ from an +-- @Integer@, wrapping if necessary. +-- If you want an expression of type @Int@ use 'GHC.Core.Make.mkIntExpr' +mkIntLitWrap :: Platform -> Integer -> Expr b +mkIntLitWrap platform n = Lit (mkLitIntWrap platform n) -- | Create a machine word literal expression of type @Word#@ from an @Integer at . -- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr' -mkWordLit :: Platform -> Integer -> Expr b --- | Create a machine word literal expression of type @Word#@ from a @Word at . --- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr' -mkWordLitWord :: Platform -> Word -> Expr b +mkWordLit :: Platform -> Integer -> Expr b +mkWordLit platform w = Lit (mkLitWord platform w) -mkWordLit platform w = Lit (mkLitWord platform w) -mkWordLitWord platform w = Lit (mkLitWord platform (toInteger w)) +-- | Create a machine word literal expression of type @Word#@ from an +-- @Integer@, wrapping if necessary. +-- If you want an expression of type @Word@ use 'GHC.Core.Make.mkWordExpr' +mkWordLitWrap :: Platform -> Integer -> Expr b +mkWordLitWrap platform w = Lit (mkLitWordWrap platform w) mkWord64LitWord64 :: Word64 -> Expr b mkWord64LitWord64 w = Lit (mkLitWord64 (toInteger w)) ===================================== compiler/GHC/Core/Make.hs ===================================== @@ -13,7 +13,7 @@ module GHC.Core.Make ( sortQuantVars, castBottomExpr, -- * Constructing boxed literals - mkWordExpr, mkWordExprWord, + mkWordExpr, mkIntExpr, mkIntExprInt, mkUncheckedIntExpr, mkIntegerExpr, mkNaturalExpr, mkFloatExpr, mkDoubleExpr, @@ -263,16 +263,12 @@ mkUncheckedIntExpr i = mkCoreConApps intDataCon [Lit (mkLitIntUnchecked i)] -- | Create a 'CoreExpr' which will evaluate to the given @Int@ mkIntExprInt :: Platform -> Int -> CoreExpr -- Result = I# i :: Int -mkIntExprInt platform i = mkCoreConApps intDataCon [mkIntLitInt platform i] +mkIntExprInt platform i = mkCoreConApps intDataCon [mkIntLit platform (fromIntegral i)] -- | Create a 'CoreExpr' which will evaluate to the a @Word@ with the given value mkWordExpr :: Platform -> Integer -> CoreExpr mkWordExpr platform w = mkCoreConApps wordDataCon [mkWordLit platform w] --- | Create a 'CoreExpr' which will evaluate to the given @Word@ -mkWordExprWord :: Platform -> Word -> CoreExpr -mkWordExprWord platform w = mkCoreConApps wordDataCon [mkWordLitWord platform w] - -- | Create a 'CoreExpr' which will evaluate to the given @Integer@ mkIntegerExpr :: Integer -> CoreExpr -- Result :: Integer mkIntegerExpr i = Lit (mkLitInteger i) ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -1348,10 +1348,10 @@ builtinBignumRules _ = , rule_IntegerFromLitNum "Int64# -> Integer" integerFromInt64Name , rule_IntegerFromLitNum "Word64# -> Integer" integerFromWord64Name , rule_IntegerFromLitNum "Natural -> Integer" integerFromNaturalName - , rule_convert "Integer -> Word#" integerToWordName mkWordLitWord - , rule_convert "Integer -> Int#" integerToIntName mkIntLitInt - , rule_convert "Integer -> Word64#" integerToWord64Name (\_ -> mkWord64LitWord64) - , rule_convert "Integer -> Int64#" integerToInt64Name (\_ -> mkInt64LitInt64) + , rule_convert "Integer -> Word#" integerToWordName mkWordLitWrap + , rule_convert "Integer -> Int#" integerToIntName mkIntLitWrap + , rule_convert "Integer -> Word64#" integerToWord64Name (\_ -> mkWord64LitWord64 . fromInteger) + , rule_convert "Integer -> Int64#" integerToInt64Name (\_ -> mkInt64LitInt64 . fromInteger) , rule_binopi "integerAdd" integerAddName (+) , rule_binopi "integerSub" integerSubName (-) , rule_binopi "integerMul" integerMulName (*) @@ -1366,9 +1366,9 @@ builtinBignumRules _ = , rule_unop "integerSignum" integerSignumName signum , rule_binop_Ordering "integerCompare" integerCompareName compare , rule_encodeFloat "integerEncodeFloat" integerEncodeFloatName mkFloatLitFloat - , rule_convert "integerToFloat" integerToFloatName (\_ -> mkFloatLitFloat) + , rule_convert "integerToFloat" integerToFloatName (\_ -> mkFloatLitFloat . fromInteger) , rule_encodeFloat "integerEncodeDouble" integerEncodeDoubleName mkDoubleLitDouble - , rule_convert "integerToDouble" integerToDoubleName (\_ -> mkDoubleLitDouble) + , rule_convert "integerToDouble" integerToDoubleName (\_ -> mkDoubleLitDouble . fromInteger) , rule_binopi "integerGcd" integerGcdName gcd , rule_binopi "integerLcm" integerLcmName lcm , rule_binopi "integerAnd" integerAndName (.&.) @@ -1659,12 +1659,11 @@ match_integerBit _ _ _ _ = Nothing ------------------------------------------------- -match_Integer_convert :: Num a - => (Platform -> a -> Expr CoreBndr) +match_Integer_convert :: (Platform -> Integer -> Expr CoreBndr) -> RuleFun match_Integer_convert convert env id_unf _ [xl] | Just (LitNumber LitNumInteger x) <- exprIsLiteral_maybe id_unf xl - = Just (convert (roPlatform env) (fromInteger x)) + = Just (convert (roPlatform env) x) match_Integer_convert _ _ _ _ _ = Nothing match_Integer_unop :: (Integer -> Integer) -> RuleFun ===================================== compiler/GHC/HsToCore/Foreign/Decl.hs ===================================== @@ -453,7 +453,7 @@ dsFExportDynamic id co0 cconv = do to be entered using an external calling convention (stdcall, ccall). -} - adj_args = [ mkIntLitInt platform (ccallConvToInt cconv) + adj_args = [ mkIntLit platform (fromIntegral (ccallConvToInt cconv)) , Var stbl_value , Lit (LitLabel fe_nm mb_sz_args IsFunction) , Lit (mkLitString typestring) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/37f0434d65fa0891a961504c8882893fad7609c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/37f0434d65fa0891a961504c8882893fad7609c6 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 Tue Nov 3 22:43:11 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 03 Nov 2020 17:43:11 -0500 Subject: [Git][ghc/ghc][master] Bignum: make GMP's bignat_add not recursive Message-ID: <5fa1dcffc0b20_7853fb58e6a06fc8448e2@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - 1 changed file: - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs Changes: ===================================== libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs ===================================== @@ -70,13 +70,13 @@ bignat_add -> State# RealWorld {-# INLINE bignat_add #-} bignat_add mwa wa wb s - -- weird GMP requirement + -- weird GMP requirement: the biggest comes first | isTrue# (wordArraySize# wb ># wordArraySize# wa) - = bignat_add mwa wb wa s + = case ioWord# (c_mpn_add mwa wb (wordArraySize# wb) wa (wordArraySize# wa)) s of + (# s', c #) -> mwaWriteMostSignificant mwa c s' | True - = do - case ioWord# (c_mpn_add mwa wa (wordArraySize# wa) wb (wordArraySize# wb)) s of + = case ioWord# (c_mpn_add mwa wa (wordArraySize# wa) wb (wordArraySize# wb)) s of (# s', c #) -> mwaWriteMostSignificant mwa c s' bignat_add_word View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bff74de713dac3e62c3bb6f1946e0649549f2215 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bff74de713dac3e62c3bb6f1946e0649549f2215 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 Wed Nov 4 01:38:32 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 03 Nov 2020 20:38:32 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-always-pic] 7 commits: Update inlining flags documentation Message-ID: <5fa20618e2e21_7853fb661dd4260858492@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC Commits: 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - ba4ef2f8 by Moritz Angermann at 2020-11-03T20:38:31-05:00 [AArch64] Aarch64 Always PIC - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - + compiler/GHC/Linker.hs - + compiler/GHC/Linker/Dynamic.hs - compiler/GHC/SysTools/ExtraObj.hs → compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Runtime/Linker.hs → compiler/GHC/Linker/Loader.hs - + compiler/GHC/Linker/MacOS.hs - + compiler/GHC/Linker/Static.hs - compiler/GHC/Runtime/Linker/Types.hs → compiler/GHC/Linker/Types.hs - + compiler/GHC/Linker/Unit.hs - + compiler/GHC/Linker/Windows.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/SysTools.hs - compiler/GHC/SysTools/Tasks.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c788de1a35c525f0efc26d90912581f89971501c...ba4ef2f89dd2306204dbf25f8831d816006a9f88 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c788de1a35c525f0efc26d90912581f89971501c...ba4ef2f89dd2306204dbf25f8831d816006a9f88 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 Wed Nov 4 02:58:24 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 03 Nov 2020 21:58:24 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-always-pic] [AArch64] Aarch64 Always PIC Message-ID: <5fa218d0de4c_785105ab0d087021f@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC Commits: 6cc2b864 by Moritz Angermann at 2020-11-04T02:58:12+00:00 [AArch64] Aarch64 Always PIC - - - - - 6 changed files: - compiler/GHC/Driver/Session.hs - docs/users_guide/runtime_control.rst - includes/rts/Flags.h - rts/Libdw.c - rts/Linker.c - rts/LinkerInternals.h Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3796,8 +3796,21 @@ validHoleFitsImpliedGFlags default_PIC :: Platform -> [GeneralFlag] default_PIC platform = case (platformOS platform, platformArch platform) of - (OSDarwin, ArchX86_64) -> [Opt_PIC] - (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in + -- Darwin always requires PIC. Especially on more recent macOS releases + -- there will be a 4GB __ZEROPAGE that prevents us from using 32bit addresses + -- while we could work around this on x86_64 (like WINE does), we won't be + -- able on aarch64, where this is enforced. + (OSDarwin, ArchX86_64) -> [Opt_PIC] + -- For AArch64, we need to always have PIC enabled. The relocation model + -- on AArch64 does not permit arbitrary relocations. Under ASLR, we can't + -- control much how far apart symbols are in memory for our in-memory static + -- linker; and thus need to ensure we get sufficiently capable relocations. + -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top + -- of that. Subsequently we expect all code on aarch64/linux (and macOS) to + -- be built with -fPIC. + (OSDarwin, ArchARM64) -> [Opt_PIC] + (OSLinux, ArchARM64) -> [Opt_PIC, Opt_ExternalDynamicRefs] + (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release -- (1 May 2013) we need to -- always generate PIC. See ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -327,8 +327,10 @@ Miscellaneous RTS options an object, the linker will probably fail with an error message when the problem is detected. - On some platforms where PIC is always the case, e.g. x86_64 MacOS X, this - flag is enabled by default. + On some platforms where PIC is always the case, e.g. macOS and OpenBSD on + x86_64, and macOS and Linux on aarch64 this flag is enabled by default. + One repercussion of this is that referenced system libraries also need to be + compiled with ``-fPIC`` if we need to load them in the runtime linker. .. rts-flag:: -xm ⟨address⟩ ===================================== includes/rts/Flags.h ===================================== @@ -200,7 +200,7 @@ typedef struct _CONCURRENT_FLAGS { * files were compiled with -fPIC -fexternal-dynamic-refs and load them * anywhere in the address space. */ -#if defined(x86_64_HOST_ARCH) && defined(darwin_HOST_OS) +#if defined(darwin_HOST_OS) || defined(aarch64_HOST_ARCH) #define DEFAULT_LINKER_ALWAYS_PIC true #else #define DEFAULT_LINKER_ALWAYS_PIC false ===================================== rts/Libdw.c ===================================== @@ -133,8 +133,9 @@ int libdwLookupLocation(LibdwSession *session, Location *frame, Dwfl_Module *mod = dwfl_addrmodule(session->dwfl, addr); if (mod == NULL) return 1; + void *object_file = &frame->object_file; dwfl_module_info(mod, NULL, NULL, NULL, NULL, NULL, - &frame->object_file, NULL); + object_file, NULL); // Find function name frame->function = dwfl_module_addrname(mod, addr); ===================================== rts/Linker.c ===================================== @@ -1022,42 +1022,6 @@ resolveSymbolAddr (pathchar* buffer, int size, } #if RTS_LINKER_USE_MMAP - -/* ----------------------------------------------------------------------------- - Occationally we depend on mmap'd region being close to already mmap'd regions. - - Our static in-memory linker may be restricted by the architectures relocation - range. E.g. aarch64 has a +-4GB range for PIC code, thus we'd preferrably - get memory for the linker close to existing mappings. mmap on it's own is - free to return any memory location, independent of what the preferred - location argument indicates. - - For example mmap (via qemu) might give you addresses all over the available - memory range if the requested location is already occupied. - - mmap_next will do a linear search from the start page upwards to find a - suitable location that is as close as possible to the locations (proivded - via the first argument). - -------------------------------------------------------------------------- */ - -void* -mmap_next(void *addr, size_t length, int prot, int flags, int fd, off_t offset) { - if(addr == NULL) return mmap(addr, length, prot, flags, fd, offset); - // we are going to look for up to pageSize * 1024 * 1024 (4GB) from the - // address. - size_t pageSize = getPageSize(); - for(int i = (uintptr_t)addr & (pageSize-1) ? 1 : 0; i < 1024*1024; i++) { - void *target = (void*)(((uintptr_t)addr & ~(pageSize-1))+(i*pageSize)); - void *mem = mmap(target, length, prot, flags, fd, offset); - if(mem == NULL) return mem; - if(mem == target) return mem; - munmap(mem, length); - IF_DEBUG(linker && (i % 1024 == 0), - debugBelch("mmap_next failed to find suitable space in %p - %p\n", addr, target)); - } - return NULL; -} - // // Returns NULL on failure. // @@ -1089,8 +1053,8 @@ mmap_again: debugBelch("mmapForLinker: \tflags %#0x\n", MAP_PRIVATE | tryMap32Bit | fixed | flags)); - result = mmap_next(map_addr, size, prot, - MAP_PRIVATE|tryMap32Bit|fixed|flags, fd, offset); + result = mmap(map_addr, size, prot, + MAP_PRIVATE|tryMap32Bit|fixed|flags, fd, offset); if (result == MAP_FAILED) { sysErrorBelch("mmap %" FMT_Word " bytes at %p",(W_)size,map_addr); ===================================== rts/LinkerInternals.h ===================================== @@ -14,7 +14,6 @@ #if RTS_LINKER_USE_MMAP #include -void* mmap_next(void *addr, size_t length, int prot, int flags, int fd, off_t offset); #endif void printLoadedObjects(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6cc2b8646579e296f49f1029d660c38bb44d979a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6cc2b8646579e296f49f1029d660c38bb44d979a 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 Wed Nov 4 08:22:50 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 04 Nov 2020 03:22:50 -0500 Subject: [Git][ghc/ghc][wip/con-info] Start of documentation Message-ID: <5fa264dac910_7853fb61db3d52c891480@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: fb288e29 by Matthew Pickering at 2020-11-04T08:22:41+00:00 Start of documentation - - - - - 1 changed file: - docs/users_guide/debug-info.rst Changes: ===================================== docs/users_guide/debug-info.rst ===================================== @@ -331,3 +331,54 @@ Further Reading For more information about the debug information produced by GHC see Peter Wortmann's PhD thesis, `*Profiling Optimized Haskell: Causal Analysis and Implementation* `__. + + +Direct Mapping +============== + +In addition to the DWARF debug information, which can be used by many +standard tools, using the ``-finfo-table-map`` flag + + +.. ghc-flag:: -finfo-table-map + :shortdesc: Embed a lookup table in the generated binary which + maps the address of an info table to the source position + the closure originated from. + :type: dynamic + :category: debugging + + :since: 9.2 + + This flag enables the generation of a table which maps the address of + an info table to an approximate source position of where that + info table statically originated from. + +.. ghc-flag:: -fdistinct-constructor-tables + :shortdesc: Generate a fresh info table for each usage + of a data constructor. + :type: dynamic + :category: debugging + + :since: 9.2 + + For every usage of a data constructor in the source program + a new info table will be created. This is useful for debugging + as if each usage has a unique info table then the info table map + and profiling modes can distinguish the allocation sites of + a data constructor. + + + +Querying the Info Table Map +--------------------------- + +If it is generated then the info table map can be used +in two ways. + +1. The ``whereFrom`` function can be used to determine the source + position which we think a specific closure was created. +2. The complete mapping is also dumped into the eventlog. + +If you are using gdb then you can use the ``lookupIPE`` function +directly in order to find any information which is known +about the info table for a specific closure. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fb288e2950e3644cf4978aab6d8a3c7f2722d0ae -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fb288e2950e3644cf4978aab6d8a3c7f2722d0ae 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 Wed Nov 4 10:08:51 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 04 Nov 2020 05:08:51 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Docs Message-ID: <5fa27db3a5b4_7853fb655bd9f989076a7@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 8640e4f0 by Matthew Pickering at 2020-11-04T09:08:27+00:00 Docs - - - - - a9a77b1b by Matthew Pickering at 2020-11-04T09:51:49+00:00 fix evenlog dump - - - - - d92b1623 by Matthew Pickering at 2020-11-04T10:08:18+00:00 Move trace IPE - - - - - 5 changed files: - compiler/GHC/Driver/CodeOutput.hs - docs/users_guide/debug-info.rst - rts/IPE.h - rts/RtsStartup.c - rts/Trace.h Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -346,6 +346,8 @@ ipInitCode used_info dflags this_mod (InfoTableProvMap dcmap closure_map) {- Note [Mapping Info Tables to Source Positions] +This note describes what the `-finfo-table-map` flag achieves. + When debugging memory issues it is very useful to be able to map a specific closure to a position in the source. The prime example is being able to map a THUNK to a specific place in the source program, the mapping is usually quite precise because @@ -361,17 +363,32 @@ various tools. -- Giving Source Locations to Closures -### Thunks -### Constructors +At the moment thunk and constructor closures are added to the map. This information +is collected in the `InfoTableProvMap` which provides a mapping from: + +1. Data constructors to a list of where they are used. +2. `Name`s and where they originate from. + +During the CoreToStg phase, this map is populated whenever something is turned into +a StgRhsClosure or an StgConApp. The current source position is recorded +depending on the location indicated by the surrounding SourceNote. +When the -fdistinct-constructor-tables` flag is turned on then every +usage of a data constructor gets its own distinct info table. This is orchestrated +in `coreToStgExpr` where an incrementing number is used to distinguish each +occurrence of a data constructor. +-- StgToCmm +The info tables which are actually used in the generated program are recorded during the +conversion from STG to Cmm. The used info tables are recorded in the `emitProc` function. -- Code Generation After the mapping has been collected during compilation, a C stub is generated which creates the static map from info table pointer to the information about where that -info table was created from. +info table was created from. This is created by `ipInitCode` in the same manner as a +C stub is generated for cost centres. This information can be consumed in two ways. @@ -384,7 +401,7 @@ Note [Distinct Info Tables for Constructors] In the old times, each usage of a data constructor used the same info table. This made it impossible to distinguish which actual usuage of a data constructor was -contributing primarily to the allocation in a program. Using the TODO flag you +contributing primarily to the allocation in a program. Using the `-fdistinct-info-tables` flag you can cause code generation to generate a distinct info table for each usage of a constructor. Then, when inspecting the heap you can see precisely which usage of a constructor was responsible for each allocation. ===================================== docs/users_guide/debug-info.rst ===================================== @@ -334,10 +334,11 @@ Analysis and Implementation* `__. Direct Mapping -============== +-------------- In addition to the DWARF debug information, which can be used by many -standard tools, using the ``-finfo-table-map`` flag +standard tools, there is also a GHC specific way to map info table pointers +to a source location. This lookup table is generated by using the ``-finfo-table-map`` flag. .. ghc-flag:: -finfo-table-map ===================================== rts/IPE.h ===================================== @@ -9,5 +9,10 @@ #pragma once #include +#include "Rts.h" -void dumpIPEToEventlog(void); +#include "BeginPrivate.h" + +void dumpIPEToEventLog (void); + +#include "EndPrivate.h" ===================================== rts/RtsStartup.c ===================================== @@ -364,7 +364,7 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) #if defined(PROFILING) initProfiling(); #endif - //dumpIPEToEventlog(); + dumpIPEToEventLog(); initHeapProfiling(); /* start the virtual timer 'subsystem'. */ ===================================== rts/Trace.h ===================================== @@ -302,12 +302,6 @@ void traceHeapProfCostCentre(StgWord32 ccID, const char *module, const char *srcloc, StgBool is_caf); -void traceIPE(StgInfoTable *info, - const char *table_name, - const char *closure_desc, - const char *label, - const char *module, - const char *srcloc ); void traceHeapProfSampleCostCentre(StgWord8 profile_id, CostCentreStack *stack, StgWord residency); @@ -326,6 +320,12 @@ void traceConcUpdRemSetFlush(Capability *cap); void traceNonmovingHeapCensus(uint32_t log_blk_size, const struct NonmovingAllocCensus *census); +void traceIPE(StgInfoTable *info, + const char *table_name, + const char *closure_desc, + const char *label, + const char *module, + const char *srcloc ); void flushTrace(void); #else /* !TRACING */ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb288e2950e3644cf4978aab6d8a3c7f2722d0ae...d92b162377ac683780ba565afdc4830d11904e5d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fb288e2950e3644cf4978aab6d8a3c7f2722d0ae...d92b162377ac683780ba565afdc4830d11904e5d 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 Wed Nov 4 10:18:41 2020 From: gitlab at gitlab.haskell.org (Sylvain Henry) Date: Wed, 04 Nov 2020 05:18:41 -0500 Subject: [Git][ghc/ghc][wip/uf-conf-codegen] 46 commits: Fix `instance Bounded a => Bounded (Down a)` (#18716) Message-ID: <5fa28001215b0_785f49fb74910736@gitlab.haskell.org.mail> Sylvain Henry pushed to branch wip/uf-conf-codegen at Glasgow Haskell Compiler / GHC Commits: 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - df5171bd by Ben Gamari at 2020-11-04T11:16:08+01:00 CmmToAsm/X86: Improve code generation for MO_UF_Conv of literal Previously we would call hs_word2float which is incredibly expensive compared to just a MOV. - - - - - 81c87cfb by Ben Gamari at 2020-11-04T11:18:05+01:00 primops: Document semantics of Float/Int conversions Fixes #18840. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1b92bde80e492895ff2be26d673a5f179543a539...81c87cfbed7a0e811d441fcac2853dd5974a99f1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1b92bde80e492895ff2be26d673a5f179543a539...81c87cfbed7a0e811d441fcac2853dd5974a99f1 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 Wed Nov 4 15:12:49 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Wed, 04 Nov 2020 10:12:49 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_gc_roots] Add rts_listThreads and rts_listMiscRoots to RtsAPI.h Message-ID: <5fa2c4f11760_7853fb59438f14c95526f@gitlab.haskell.org.mail> David Eichmann pushed to branch wip/ghc-debug_gc_roots at Glasgow Haskell Compiler / GHC Commits: 2772b6a1 by David Eichmann at 2020-11-04T15:12:38+00:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 6 changed files: - includes/RtsAPI.h - rts/RtsAPI.c - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -17,6 +17,7 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" +#include "rts/Types.h" #include "rts/EventLogWriter.h" /* @@ -566,6 +567,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== rts/RtsAPI.c ===================================== @@ -809,6 +809,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +873,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2772b6a11a4043ee61fe0abd9bd5168dd36437fe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2772b6a11a4043ee61fe0abd9bd5168dd36437fe 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 Wed Nov 4 15:47:26 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 04 Nov 2020 10:47:26 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: Update inlining flags documentation Message-ID: <5fa2cd0e82084_7853fb642c29b3c9664b1@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - 920deca1 by Andreas Klebinger at 2020-11-04T10:47:12-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - cebcd195 by Andreas Klebinger at 2020-11-04T10:47:12-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - f782f586 by Sylvain Henry at 2020-11-04T10:47:16-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - + compiler/GHC/Linker.hs - + compiler/GHC/Linker/Dynamic.hs - compiler/GHC/SysTools/ExtraObj.hs → compiler/GHC/Linker/ExtraObj.hs - compiler/GHC/Runtime/Linker.hs → compiler/GHC/Linker/Loader.hs - + compiler/GHC/Linker/MacOS.hs - + compiler/GHC/Linker/Static.hs - compiler/GHC/Runtime/Linker/Types.hs → compiler/GHC/Linker/Types.hs - + compiler/GHC/Linker/Unit.hs - + compiler/GHC/Linker/Windows.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/SysTools.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e5665bee887415fcdcaa1631e032d643deb8942c...f782f586c353afe0999dbc189af5213ec3bf8817 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e5665bee887415fcdcaa1631e032d643deb8942c...f782f586c353afe0999dbc189af5213ec3bf8817 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 Wed Nov 4 16:29:03 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 04 Nov 2020 11:29:03 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Add missing case for unboxed sum Message-ID: <5fa2d6cfdc38f_7853fb5eaa5389c9776c@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 4f0b7a39 by Matthew Pickering at 2020-11-04T10:44:56+00:00 Add missing case for unboxed sum - - - - - 2dcc8657 by Matthew Pickering at 2020-11-04T10:45:09+00:00 move traceIPE out of profiling block - - - - - 395abf45 by Matthew Pickering at 2020-11-04T16:28:50+00:00 Move postIPE - - - - - 5 changed files: - compiler/GHC/CoreToStg.hs - rts/IPE.c - rts/Trace.c - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h Changes: ===================================== compiler/GHC/CoreToStg.hs ===================================== @@ -925,6 +925,7 @@ lookupBinding env v = case lookupVarEnv env v of incDc :: DataCon -> CtsM (Maybe Int) incDc dc | isUnboxedTupleDataCon dc = return Nothing +incDc dc | isUnboxedSumDataCon dc = return Nothing incDc dc = CtsM $ \dflags _ -> if not (gopt Opt_DistinctConstructorTables dflags) then return Nothing else do env <- get cc <- ask ===================================== rts/IPE.c ===================================== @@ -15,25 +15,31 @@ #include "Arena.h" #include "Printer.h" #include "Capability.h" -#include "Trace.h" #include #include +#if defined(TRACING) +#include "Trace.h" +#endif + InfoProvEnt *IPE_LIST = NULL; void dumpIPEToEventLog(void) { +#if defined(TRACING) InfoProvEnt *ip, *next; for (ip = IPE_LIST; ip != NULL; ip = next) { next = ip->link; traceIPE(ip->info, ip->prov.table_name, ip->prov.closure_desc, ip->prov.label, ip->prov.module, ip->prov.srcloc); } +#endif } + /* ----------------------------------------------------------------------------- Registering IPEs ===================================== rts/Trace.c ===================================== @@ -638,6 +638,18 @@ void traceHeapProfSampleString(StgWord8 profile_id, } } +void traceIPE(StgInfoTable * info, + const char *table_name, + const char *closure_desc, + const char *label, + const char *module, + const char *srcloc ) +{ + if (eventlog_enabled) { + postIPE(INFO_PTR_TO_STRUCT(info), table_name, closure_desc, label, module, srcloc); + } +} + #if defined(PROFILING) void traceHeapProfCostCentre(StgWord32 ccID, const char *label, @@ -650,17 +662,6 @@ void traceHeapProfCostCentre(StgWord32 ccID, } } -void traceIPE(StgInfoTable * info, - const char *table_name, - const char *closure_desc, - const char *label, - const char *module, - const char *srcloc ) -{ - if (eventlog_enabled) { - postIPE(INFO_PTR_TO_STRUCT(info), table_name, closure_desc, label, module, srcloc); - } -} // This one is for .hp samples void traceHeapProfSampleCostCentre(StgWord8 profile_id, ===================================== rts/eventlog/EventLog.c ===================================== @@ -1413,31 +1413,6 @@ void postHeapProfCostCentre(StgWord32 ccID, postWord8(&eventBuf, is_caf); RELEASE_LOCK(&eventBufMutex); } -void postIPE(StgWord64 info, - const char *table_name, - const char *closure_desc, - const char *label, - const char *module, - const char *srcloc) -{ - ACQUIRE_LOCK(&eventBufMutex); - StgWord table_name_len = strlen(table_name); - StgWord closure_desc_len = strlen(closure_desc); - StgWord label_len = strlen(label); - StgWord module_len = strlen(module); - StgWord srcloc_len = strlen(srcloc); - StgWord len = 8+table_name_len+closure_desc_len+label_len+module_len+srcloc_len+3; - ensureRoomForVariableEvent(&eventBuf, len); - postEventHeader(&eventBuf, EVENT_IPE); - postPayloadSize(&eventBuf, len); - postWord64(&eventBuf, info); - postString(&eventBuf, table_name); - postString(&eventBuf, closure_desc); - postString(&eventBuf, label); - postString(&eventBuf, module); - postString(&eventBuf, srcloc); - RELEASE_LOCK(&eventBufMutex); -} void postHeapProfSampleCostCentre(StgWord8 profile_id, CostCentreStack *stack, @@ -1503,6 +1478,32 @@ void postProfBegin(void) } #endif /* PROFILING */ +void postIPE(StgWord64 info, + const char *table_name, + const char *closure_desc, + const char *label, + const char *module, + const char *srcloc) +{ + ACQUIRE_LOCK(&eventBufMutex); + StgWord table_name_len = strlen(table_name); + StgWord closure_desc_len = strlen(closure_desc); + StgWord label_len = strlen(label); + StgWord module_len = strlen(module); + StgWord srcloc_len = strlen(srcloc); + StgWord len = 8+table_name_len+closure_desc_len+label_len+module_len+srcloc_len+3; + ensureRoomForVariableEvent(&eventBuf, len); + postEventHeader(&eventBuf, EVENT_IPE); + postPayloadSize(&eventBuf, len); + postWord64(&eventBuf, info); + postString(&eventBuf, table_name); + postString(&eventBuf, closure_desc); + postString(&eventBuf, label); + postString(&eventBuf, module); + postString(&eventBuf, srcloc); + RELEASE_LOCK(&eventBufMutex); +} + void printAndClearEventBuf (EventsBuf *ebuf) { closeBlockMarker(ebuf); ===================================== rts/eventlog/EventLog.h ===================================== @@ -157,12 +157,6 @@ void postHeapProfCostCentre(StgWord32 ccID, const char *module, const char *srcloc, StgBool is_caf); -void postIPE(StgWord64 info, - const char *table_name, - const char *closure_desc, - const char *label, - const char *module, - const char *srcloc); void postHeapProfSampleCostCentre(StgWord8 profile_id, CostCentreStack *stack, @@ -174,6 +168,13 @@ void postProfSampleCostCentre(Capability *cap, void postProfBegin(void); #endif /* PROFILING */ +void postIPE(StgWord64 info, + const char *table_name, + const char *closure_desc, + const char *label, + const char *module, + const char *srcloc); + void postConcUpdRemSetFlush(Capability *cap); void postConcMarkEnd(StgWord32 marked_obj_count); void postNonmovingHeapCensus(int log_blk_size, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d92b162377ac683780ba565afdc4830d11904e5d...395abf45f360f56e27cd947a96c4854e879232f7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d92b162377ac683780ba565afdc4830d11904e5d...395abf45f360f56e27cd947a96c4854e879232f7 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 Wed Nov 4 17:59:47 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 12:59:47 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/weak-sanity-race Message-ID: <5fa2ec1376892_10ee3ffb8e4291589888@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/weak-sanity-race 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 Wed Nov 4 18:00:13 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 13:00:13 -0500 Subject: [Git][ghc/ghc][wip/weak-sanity-race] 5 commits: testsuite: Add performance test for #18698 Message-ID: <5fa2ec2d4fe1_10ee3ffb919d077099068@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC Commits: bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 8808ca7f by Ben Gamari at 2020-11-04T13:00:07-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/TyCon/RecWalk.hs - compiler/GHC/Core/TyCon/Set.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Driver/Backpack.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a9cefb02bc64e99cea96db8c1739caf2aca9ea7f...8808ca7fb49cb46038f9f7e516217c82a4709771 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a9cefb02bc64e99cea96db8c1739caf2aca9ea7f...8808ca7fb49cb46038f9f7e516217c82a4709771 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 Wed Nov 4 18:18:58 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 13:18:58 -0500 Subject: [Git][ghc/ghc][wip/weak-sanity-race] rts/Sanity: Avoid nasty race in weak pointer sanity-checking Message-ID: <5fa2f092c617a_10ee3ffbc96303801028e0@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC Commits: 0a8dd6e5 by Ben Gamari at 2020-11-04T13:18:51-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 1 changed file: - rts/sm/Sanity.c Changes: ===================================== rts/sm/Sanity.c ===================================== @@ -233,6 +233,110 @@ checkClosureProfSanity(const StgClosure *p) } #endif +/* Note [Racing weak pointer evacuation] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * While debugging a GC crash (#18919) I noticed a spurious crash due to the + * end-of-GC sanity check stumbling across a weak pointer with unevacuated key. + * This can happen when two GC threads race to evacuate a weak pointer. + * Specifically, we start out with a heap with a weak pointer reachable + * from both a generation's weak pointer list and some other root-reachable + * closure (e.g. a Just constructor): + * + * O W + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ ╭───→ │ Weak# │ ←─────── weak_ptr_list + * Set ├──────────┤ │ ├──────────┤ + * │ │ ────╯ │ value │ ─→ ... + * └──────────┘ │ key │ ───╮ K + * │ ... │ │ ┌──────────┐ + * └──────────┘ ╰──→ │ ... │ + * ├──────────┤ + * + * The situation proceeds as follows: + * + * 1. Thread A initiates a GC, wakes up the GC worker threads, and starts + * evacuating roots. + * 2. Thread A evacuates a weak pointer object O to location O'. + * 3. Thread A fills the block where O' lives and pushes it to its + * work-stealing queue. + * 4. Thread B steals the O' block and starts scavenging it. + * 5. Thread A enters markWeakPtrList. + * 6. Thread A starts evacuating W, resulting in Wb'. + * 7. Thread B scavenges O', evacuating W', resulting in Wa'. + * 8. Thread A and B are now racing to evacuate W. Only one will win the race + * (due to the CAS in copy_tag). Let the winning copy be called W'. + * 9. W will be replaced by a forwarding pointer to the winning copy, W'. + * 10. Whichever thread loses the race will retry evacuation, see + * that W has already been evacuated, and proceed as usual. + * 10. W' will get added to weak_ptr_list by markWeakPtrList. + * 11. Eventually W' will be scavenged. + * 12. traverseWeakPtrList will see that W' has been scavenged and evacuate the + * its key. + * 13. However, the copy that lost the race is not on `weak_ptr_list` + * and will therefore never get its `key` field scavenged (since + * `traverseWeakPtrList` will never see it). + * + * Now the heap looks like: + * + * O' W (from-space) + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ │ Fwd-ptr │ ───────────╮ + * Set ├──────────┤ ├──────────┤ │ + * │ │ ────╮ │ value │ ─→ ... │ + * └──────────┘ │ │ key │ ────────────────────────╮ + * │ │ ... │ │ │ + * │ └──────────┘ │ │ + * │ │ │ + * │ Wa' │ │ + * │ ┌──────────┐ ╭────╯ │ + * ╰───→ │ Weak# │ ←─────┤ │ + * ├──────────┤ ╰─ weak_ptr_list │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K' │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ ... │ │ + * ├──────────┤ │ + * Wb' │ + * ┌──────────┐ │ + * │ Weak# │ │ + * ├──────────┤ │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K (from-space) │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ 0xaaaaa │ ←──╯ + * ├──────────┤ + * + * + * Without sanity checking this is fine; we have introduced a spurious copy of + * W, Wb' into the heap but it is unreachable and therefore won't cause any + * trouble. However, with sanity checking we may encounter this spurious copy + * when walking the heap. Moreover, this copy was never added to weak_ptr_list, + * meaning that its key field will not get scavenged and will therefore point + * into from-space.. + * + * To avoid this checkClosure skips over the key field when it sees a weak + * pointer. Note that all fields of Wb' *other* than the key field should be + * valid, so we don't skip the closure entirely. + * + * We then do additional checking of all closures on the weak_ptr_lists, where + * we *do* check `key`. + */ + +// Check validity of objects on weak_ptr_list. +// See Note [Racing weak pointer evacuation]. +static void +checkGenWeakPtrList( uint32_t g ) +{ + for (StgWeak *w = generations[g].weak_ptr_list; w != NULL; w = w->link) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w)); + ASSERT(&get_itbl(w) == stg_WEAK_info); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); + } +} + // Returns closure size in words StgOffset checkClosure( const StgClosure* p ) @@ -352,9 +456,11 @@ checkClosure( const StgClosure* p ) * representative of the actual layout. */ { StgWeak *w = (StgWeak *)p; - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + // N.B. Checking the key is not safe. + // See Note [Racing weak pointer evacuation] for why. ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); if (w->link) { ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->link)); } @@ -852,6 +958,12 @@ static void checkGeneration (generation *gen, checkHeapChain(ws->scavd_list); } + // Check weak pointer lists + // See Note [Racing weak pointer evacuation]. + for (uint32_t g = 0; g <= RtsFlags.GcFlags.generations; g++) { + checkGenWeakPtrList(g); + } + checkLargeObjects(gen->large_objects); checkCompactObjects(gen->compact_objects); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0a8dd6e5e2a7469617b1e0ca93a4022be45532ef -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0a8dd6e5e2a7469617b1e0ca93a4022be45532ef 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 Wed Nov 4 18:22:33 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 13:22:33 -0500 Subject: [Git][ghc/ghc][wip/weak-sanity-race] rts/Sanity: Avoid nasty race in weak pointer sanity-checking Message-ID: <5fa2f16919ebd_10ee3ffbadf677d0103434@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC Commits: 55fbeb76 by Ben Gamari at 2020-11-04T13:22:26-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 1 changed file: - rts/sm/Sanity.c Changes: ===================================== rts/sm/Sanity.c ===================================== @@ -233,6 +233,110 @@ checkClosureProfSanity(const StgClosure *p) } #endif +/* Note [Racing weak pointer evacuation] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * While debugging a GC crash (#18919) I noticed a spurious crash due to the + * end-of-GC sanity check stumbling across a weak pointer with unevacuated key. + * This can happen when two GC threads race to evacuate a weak pointer. + * Specifically, we start out with a heap with a weak pointer reachable + * from both a generation's weak pointer list and some other root-reachable + * closure (e.g. a Just constructor): + * + * O W + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ ╭───→ │ Weak# │ ←─────── weak_ptr_list + * Set ├──────────┤ │ ├──────────┤ + * │ │ ────╯ │ value │ ─→ ... + * └──────────┘ │ key │ ───╮ K + * │ ... │ │ ┌──────────┐ + * └──────────┘ ╰──→ │ ... │ + * ├──────────┤ + * + * The situation proceeds as follows: + * + * 1. Thread A initiates a GC, wakes up the GC worker threads, and starts + * evacuating roots. + * 2. Thread A evacuates a weak pointer object O to location O'. + * 3. Thread A fills the block where O' lives and pushes it to its + * work-stealing queue. + * 4. Thread B steals the O' block and starts scavenging it. + * 5. Thread A enters markWeakPtrList. + * 6. Thread A starts evacuating W, resulting in Wb'. + * 7. Thread B scavenges O', evacuating W', resulting in Wa'. + * 8. Thread A and B are now racing to evacuate W. Only one will win the race + * (due to the CAS in copy_tag). Let the winning copy be called W'. + * 9. W will be replaced by a forwarding pointer to the winning copy, W'. + * 10. Whichever thread loses the race will retry evacuation, see + * that W has already been evacuated, and proceed as usual. + * 10. W' will get added to weak_ptr_list by markWeakPtrList. + * 11. Eventually W' will be scavenged. + * 12. traverseWeakPtrList will see that W' has been scavenged and evacuate the + * its key. + * 13. However, the copy that lost the race is not on `weak_ptr_list` + * and will therefore never get its `key` field scavenged (since + * `traverseWeakPtrList` will never see it). + * + * Now the heap looks like: + * + * O' W (from-space) + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ │ Fwd-ptr │ ───────────╮ + * Set ├──────────┤ ├──────────┤ │ + * │ │ ────╮ │ value │ ─→ ... │ + * └──────────┘ │ │ key │ ────────────────────────╮ + * │ │ ... │ │ │ + * │ └──────────┘ │ │ + * │ │ │ + * │ Wa' │ │ + * │ ┌──────────┐ ╭────╯ │ + * ╰───→ │ Weak# │ ←─────┤ │ + * ├──────────┤ ╰─ weak_ptr_list │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K' │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ ... │ │ + * ├──────────┤ │ + * Wb' │ + * ┌──────────┐ │ + * │ Weak# │ │ + * ├──────────┤ │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K (from-space) │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ 0xaaaaa │ ←──╯ + * ├──────────┤ + * + * + * Without sanity checking this is fine; we have introduced a spurious copy of + * W, Wb' into the heap but it is unreachable and therefore won't cause any + * trouble. However, with sanity checking we may encounter this spurious copy + * when walking the heap. Moreover, this copy was never added to weak_ptr_list, + * meaning that its key field will not get scavenged and will therefore point + * into from-space.. + * + * To avoid this checkClosure skips over the key field when it sees a weak + * pointer. Note that all fields of Wb' *other* than the key field should be + * valid, so we don't skip the closure entirely. + * + * We then do additional checking of all closures on the weak_ptr_lists, where + * we *do* check `key`. + */ + +// Check validity of objects on weak_ptr_list. +// See Note [Racing weak pointer evacuation]. +static void +checkGenWeakPtrList( uint32_t g ) +{ + for (StgWeak *w = generations[g].weak_ptr_list; w != NULL; w = w->link) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w)); + ASSERT(get_itbl((StgClosure *) w) == &stg_WEAK_info); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); + } +} + // Returns closure size in words StgOffset checkClosure( const StgClosure* p ) @@ -352,9 +456,11 @@ checkClosure( const StgClosure* p ) * representative of the actual layout. */ { StgWeak *w = (StgWeak *)p; - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + // N.B. Checking the key is not safe. + // See Note [Racing weak pointer evacuation] for why. ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); if (w->link) { ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->link)); } @@ -852,6 +958,12 @@ static void checkGeneration (generation *gen, checkHeapChain(ws->scavd_list); } + // Check weak pointer lists + // See Note [Racing weak pointer evacuation]. + for (uint32_t g = 0; g <= RtsFlags.GcFlags.generations; g++) { + checkGenWeakPtrList(g); + } + checkLargeObjects(gen->large_objects); checkCompactObjects(gen->compact_objects); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55fbeb76a4ca58373b6c021a25666d74d5aadcd9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/55fbeb76a4ca58373b6c021a25666d74d5aadcd9 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 Wed Nov 4 18:25:37 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 13:25:37 -0500 Subject: [Git][ghc/ghc][wip/weak-sanity-race] rts/Sanity: Avoid nasty race in weak pointer sanity-checking Message-ID: <5fa2f221190e5_10ee3ffbacf386341042ca@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC Commits: 58fb14ab by Ben Gamari at 2020-11-04T13:25:29-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 1 changed file: - rts/sm/Sanity.c Changes: ===================================== rts/sm/Sanity.c ===================================== @@ -233,6 +233,110 @@ checkClosureProfSanity(const StgClosure *p) } #endif +/* Note [Racing weak pointer evacuation] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * While debugging a GC crash (#18919) I noticed a spurious crash due to the + * end-of-GC sanity check stumbling across a weak pointer with unevacuated key. + * This can happen when two GC threads race to evacuate a weak pointer. + * Specifically, we start out with a heap with a weak pointer reachable + * from both a generation's weak pointer list and some other root-reachable + * closure (e.g. a Just constructor): + * + * O W + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ ╭───→ │ Weak# │ ←─────── weak_ptr_list + * Set ├──────────┤ │ ├──────────┤ + * │ │ ────╯ │ value │ ─→ ... + * └──────────┘ │ key │ ───╮ K + * │ ... │ │ ┌──────────┐ + * └──────────┘ ╰──→ │ ... │ + * ├──────────┤ + * + * The situation proceeds as follows: + * + * 1. Thread A initiates a GC, wakes up the GC worker threads, and starts + * evacuating roots. + * 2. Thread A evacuates a weak pointer object O to location O'. + * 3. Thread A fills the block where O' lives and pushes it to its + * work-stealing queue. + * 4. Thread B steals the O' block and starts scavenging it. + * 5. Thread A enters markWeakPtrList. + * 6. Thread A starts evacuating W, resulting in Wb'. + * 7. Thread B scavenges O', evacuating W', resulting in Wa'. + * 8. Thread A and B are now racing to evacuate W. Only one will win the race + * (due to the CAS in copy_tag). Let the winning copy be called W'. + * 9. W will be replaced by a forwarding pointer to the winning copy, W'. + * 10. Whichever thread loses the race will retry evacuation, see + * that W has already been evacuated, and proceed as usual. + * 10. W' will get added to weak_ptr_list by markWeakPtrList. + * 11. Eventually W' will be scavenged. + * 12. traverseWeakPtrList will see that W' has been scavenged and evacuate the + * its key. + * 13. However, the copy that lost the race is not on `weak_ptr_list` + * and will therefore never get its `key` field scavenged (since + * `traverseWeakPtrList` will never see it). + * + * Now the heap looks like: + * + * O' W (from-space) + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ │ Fwd-ptr │ ───────────╮ + * Set ├──────────┤ ├──────────┤ │ + * │ │ ────╮ │ value │ ─→ ... │ + * └──────────┘ │ │ key │ ────────────────────────╮ + * │ │ ... │ │ │ + * │ └──────────┘ │ │ + * │ │ │ + * │ Wa' │ │ + * │ ┌──────────┐ ╭────╯ │ + * ╰───→ │ Weak# │ ←─────┤ │ + * ├──────────┤ ╰─ weak_ptr_list │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K' │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ ... │ │ + * ├──────────┤ │ + * Wb' │ + * ┌──────────┐ │ + * │ Weak# │ │ + * ├──────────┤ │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K (from-space) │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ 0xaaaaa │ ←──╯ + * ├──────────┤ + * + * + * Without sanity checking this is fine; we have introduced a spurious copy of + * W, Wb' into the heap but it is unreachable and therefore won't cause any + * trouble. However, with sanity checking we may encounter this spurious copy + * when walking the heap. Moreover, this copy was never added to weak_ptr_list, + * meaning that its key field will not get scavenged and will therefore point + * into from-space.. + * + * To avoid this checkClosure skips over the key field when it sees a weak + * pointer. Note that all fields of Wb' *other* than the key field should be + * valid, so we don't skip the closure entirely. + * + * We then do additional checking of all closures on the weak_ptr_lists, where + * we *do* check `key`. + */ + +// Check validity of objects on weak_ptr_list. +// See Note [Racing weak pointer evacuation]. +static void +checkGenWeakPtrList( uint32_t g ) +{ + for (StgWeak *w = generations[g].weak_ptr_list; w != NULL; w = w->link) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w)); + ASSERT(w->header.info == &stg_WEAK_info); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); + } +} + // Returns closure size in words StgOffset checkClosure( const StgClosure* p ) @@ -352,9 +456,11 @@ checkClosure( const StgClosure* p ) * representative of the actual layout. */ { StgWeak *w = (StgWeak *)p; - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + // N.B. Checking the key is not safe. + // See Note [Racing weak pointer evacuation] for why. ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); if (w->link) { ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->link)); } @@ -852,6 +958,12 @@ static void checkGeneration (generation *gen, checkHeapChain(ws->scavd_list); } + // Check weak pointer lists + // See Note [Racing weak pointer evacuation]. + for (uint32_t g = 0; g <= RtsFlags.GcFlags.generations; g++) { + checkGenWeakPtrList(g); + } + checkLargeObjects(gen->large_objects); checkCompactObjects(gen->compact_objects); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58fb14ab1c51b5d563eefe6b367c0951a8b72b69 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58fb14ab1c51b5d563eefe6b367c0951a8b72b69 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 Wed Nov 4 18:27:17 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 13:27:17 -0500 Subject: [Git][ghc/ghc][wip/weak-sanity-race] rts/Sanity: Avoid nasty race in weak pointer sanity-checking Message-ID: <5fa2f28522654_10ee3ffb8c2431c41065e7@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC Commits: 84ec4cee by Ben Gamari at 2020-11-04T13:27:09-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 1 changed file: - rts/sm/Sanity.c Changes: ===================================== rts/sm/Sanity.c ===================================== @@ -233,6 +233,110 @@ checkClosureProfSanity(const StgClosure *p) } #endif +/* Note [Racing weak pointer evacuation] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * While debugging a GC crash (#18919) I noticed a spurious crash due to the + * end-of-GC sanity check stumbling across a weak pointer with unevacuated key. + * This can happen when two GC threads race to evacuate a weak pointer. + * Specifically, we start out with a heap with a weak pointer reachable + * from both a generation's weak pointer list and some other root-reachable + * closure (e.g. a Just constructor): + * + * O W + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ ╭───→ │ Weak# │ ←─────── weak_ptr_list + * Set ├──────────┤ │ ├──────────┤ + * │ │ ────╯ │ value │ ─→ ... + * └──────────┘ │ key │ ───╮ K + * │ ... │ │ ┌──────────┐ + * └──────────┘ ╰──→ │ ... │ + * ├──────────┤ + * + * The situation proceeds as follows: + * + * 1. Thread A initiates a GC, wakes up the GC worker threads, and starts + * evacuating roots. + * 2. Thread A evacuates a weak pointer object O to location O'. + * 3. Thread A fills the block where O' lives and pushes it to its + * work-stealing queue. + * 4. Thread B steals the O' block and starts scavenging it. + * 5. Thread A enters markWeakPtrList. + * 6. Thread A starts evacuating W, resulting in Wb'. + * 7. Thread B scavenges O', evacuating W', resulting in Wa'. + * 8. Thread A and B are now racing to evacuate W. Only one will win the race + * (due to the CAS in copy_tag). Let the winning copy be called W'. + * 9. W will be replaced by a forwarding pointer to the winning copy, W'. + * 10. Whichever thread loses the race will retry evacuation, see + * that W has already been evacuated, and proceed as usual. + * 10. W' will get added to weak_ptr_list by markWeakPtrList. + * 11. Eventually W' will be scavenged. + * 12. traverseWeakPtrList will see that W' has been scavenged and evacuate the + * its key. + * 13. However, the copy that lost the race is not on `weak_ptr_list` + * and will therefore never get its `key` field scavenged (since + * `traverseWeakPtrList` will never see it). + * + * Now the heap looks like: + * + * O' W (from-space) + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ │ Fwd-ptr │ ───────────╮ + * Set ├──────────┤ ├──────────┤ │ + * │ │ ────╮ │ value │ ─→ ... │ + * └──────────┘ │ │ key │ ────────────────────────╮ + * │ │ ... │ │ │ + * │ └──────────┘ │ │ + * │ │ │ + * │ Wa' │ │ + * │ ┌──────────┐ ╭────╯ │ + * ╰───→ │ Weak# │ ←─────┤ │ + * ├──────────┤ ╰─ weak_ptr_list │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K' │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ ... │ │ + * ├──────────┤ │ + * Wb' │ + * ┌──────────┐ │ + * │ Weak# │ │ + * ├──────────┤ │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K (from-space) │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ 0xaaaaa │ ←──╯ + * ├──────────┤ + * + * + * Without sanity checking this is fine; we have introduced a spurious copy of + * W, Wb' into the heap but it is unreachable and therefore won't cause any + * trouble. However, with sanity checking we may encounter this spurious copy + * when walking the heap. Moreover, this copy was never added to weak_ptr_list, + * meaning that its key field will not get scavenged and will therefore point + * into from-space.. + * + * To avoid this checkClosure skips over the key field when it sees a weak + * pointer. Note that all fields of Wb' *other* than the key field should be + * valid, so we don't skip the closure entirely. + * + * We then do additional checking of all closures on the weak_ptr_lists, where + * we *do* check `key`. + */ + +// Check validity of objects on weak_ptr_list. +// See Note [Racing weak pointer evacuation]. +static void +checkGenWeakPtrList( uint32_t g ) +{ + for (StgWeak *w = generations[g].weak_ptr_list; w != NULL; w = w->link) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w)); + ASSERT(w->header.info == &stg_WEAK_info); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); + } +} + // Returns closure size in words StgOffset checkClosure( const StgClosure* p ) @@ -352,9 +456,11 @@ checkClosure( const StgClosure* p ) * representative of the actual layout. */ { StgWeak *w = (StgWeak *)p; - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + // N.B. Checking the key is not safe. + // See Note [Racing weak pointer evacuation] for why. ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); if (w->link) { ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->link)); } @@ -852,6 +958,12 @@ static void checkGeneration (generation *gen, checkHeapChain(ws->scavd_list); } + // Check weak pointer lists + // See Note [Racing weak pointer evacuation]. + for (uint32_t g = 0; g < RtsFlags.GcFlags.generations; g++) { + checkGenWeakPtrList(g); + } + checkLargeObjects(gen->large_objects); checkCompactObjects(gen->compact_objects); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/84ec4ceef113017b83f8888636ebff7b7e0f8cb6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/84ec4ceef113017b83f8888636ebff7b7e0f8cb6 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 Wed Nov 4 19:43:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 04 Nov 2020 14:43:56 -0500 Subject: [Git][ghc/ghc][wip/weak-sanity-race] rts/Sanity: Avoid nasty race in weak pointer sanity-checking Message-ID: <5fa3047c10736_10ee3ffbac3fd558122457@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/weak-sanity-race at Glasgow Haskell Compiler / GHC Commits: 17c238a8 by Ben Gamari at 2020-11-04T14:43:45-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 1 changed file: - rts/sm/Sanity.c Changes: ===================================== rts/sm/Sanity.c ===================================== @@ -233,6 +233,111 @@ checkClosureProfSanity(const StgClosure *p) } #endif +/* Note [Racing weak pointer evacuation] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * While debugging a GC crash (#18919) I noticed a spurious crash due to the + * end-of-GC sanity check stumbling across a weak pointer with unevacuated key. + * This can happen when two GC threads race to evacuate a weak pointer. + * Specifically, we start out with a heap with a weak pointer reachable + * from both a generation's weak pointer list and some other root-reachable + * closure (e.g. a Just constructor): + * + * O W + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ ╭───→ │ Weak# │ ←─────── weak_ptr_list + * Set ├──────────┤ │ ├──────────┤ + * │ │ ────╯ │ value │ ─→ ... + * └──────────┘ │ key │ ───╮ K + * │ ... │ │ ┌──────────┐ + * └──────────┘ ╰──→ │ ... │ + * ├──────────┤ + * + * The situation proceeds as follows: + * + * 1. Thread A initiates a GC, wakes up the GC worker threads, and starts + * evacuating roots. + * 2. Thread A evacuates a weak pointer object O to location O'. + * 3. Thread A fills the block where O' lives and pushes it to its + * work-stealing queue. + * 4. Thread B steals the O' block and starts scavenging it. + * 5. Thread A enters markWeakPtrList. + * 6. Thread A starts evacuating W, resulting in Wb'. + * 7. Thread B scavenges O', evacuating W', resulting in Wa'. + * 8. Thread A and B are now racing to evacuate W. Only one will win the race + * (due to the CAS in copy_tag). Let the winning copy be called W'. + * 9. W will be replaced by a forwarding pointer to the winning copy, W'. + * 10. Whichever thread loses the race will retry evacuation, see + * that W has already been evacuated, and proceed as usual. + * 10. W' will get added to weak_ptr_list by markWeakPtrList. + * 11. Eventually W' will be scavenged. + * 12. traverseWeakPtrList will see that W' has been scavenged and evacuate the + * its key. + * 13. However, the copy that lost the race is not on `weak_ptr_list` + * and will therefore never get its `key` field scavenged (since + * `traverseWeakPtrList` will never see it). + * + * Now the heap looks like: + * + * O' W (from-space) + * ┌──────────┐ ┌──────────┐ + * Root ────→ │ Just │ │ Fwd-ptr │ ───────────╮ + * Set ├──────────┤ ├──────────┤ │ + * │ │ ────╮ │ value │ ─→ ... │ + * └──────────┘ │ │ key │ ────────────────────────╮ + * │ │ ... │ │ │ + * │ └──────────┘ │ │ + * │ │ │ + * │ Wa' │ │ + * │ ┌──────────┐ ╭────╯ │ + * ╰───→ │ Weak# │ ←─────┤ │ + * ├──────────┤ ╰─ weak_ptr_list │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K' │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ ... │ │ + * ├──────────┤ │ + * Wb' │ + * ┌──────────┐ │ + * │ Weak# │ │ + * ├──────────┤ │ + * │ value │ ─→ ... │ + * │ key │ ───╮ K (from-space) │ + * │ ... │ │ ┌──────────┐ │ + * └──────────┘ ╰──→ │ 0xaaaaa │ ←──╯ + * ├──────────┤ + * + * + * Without sanity checking this is fine; we have introduced a spurious copy of + * W, Wb' into the heap but it is unreachable and therefore won't cause any + * trouble. However, with sanity checking we may encounter this spurious copy + * when walking the heap. Moreover, this copy was never added to weak_ptr_list, + * meaning that its key field (along with the other fields mark as + * non-pointers) will not get scavenged and will therefore point into + * from-space. + * + * To avoid this checkClosure skips over the key field when it sees a weak + * pointer. Note that all fields of Wb' *other* than the key field should be + * valid, so we don't skip the closure entirely. + * + * We then do additional checking of all closures on the weak_ptr_lists, where + * we *do* check `key`. + */ + +// Check validity of objects on weak_ptr_list. +// See Note [Racing weak pointer evacuation]. +static void +checkGenWeakPtrList( uint32_t g ) +{ + for (StgWeak *w = generations[g].weak_ptr_list; w != NULL; w = w->link) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w)); + ASSERT(w->header.info == &stg_WEAK_info); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); + } +} + // Returns closure size in words StgOffset checkClosure( const StgClosure* p ) @@ -352,12 +457,9 @@ checkClosure( const StgClosure* p ) * representative of the actual layout. */ { StgWeak *w = (StgWeak *)p; - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->key)); - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->value)); - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->finalizer)); - if (w->link) { - ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->link)); - } + // N.B. Checking most of the fields here is not safe. + // See Note [Racing weak pointer evacuation] for why. + ASSERT(LOOKS_LIKE_CLOSURE_PTR(w->cfinalizers)); return sizeW_fromITBL(info); } @@ -852,6 +954,12 @@ static void checkGeneration (generation *gen, checkHeapChain(ws->scavd_list); } + // Check weak pointer lists + // See Note [Racing weak pointer evacuation]. + for (uint32_t g = 0; g < RtsFlags.GcFlags.generations; g++) { + checkGenWeakPtrList(g); + } + checkLargeObjects(gen->large_objects); checkCompactObjects(gen->compact_objects); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17c238a88b4d7ba026e780416c134e3c60586b57 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17c238a88b4d7ba026e780416c134e3c60586b57 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 Wed Nov 4 19:52:05 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 04 Nov 2020 14:52:05 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 2 commits: Update Note [TyVar/TyVar orientation] Message-ID: <5fa306655d6b4_10ee3ffbc91ed5fc1273c4@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 05b06a8d by Richard Eisenberg at 2020-11-04T14:41:37-05:00 Update Note [TyVar/TyVar orientation] - - - - - 9d122639 by Richard Eisenberg at 2020-11-04T14:51:54-05:00 Actually add tests - - - - - 4 changed files: - compiler/GHC/Tc/Utils/Unify.hs - + testsuite/tests/typecheck/should_compile/CbvOverlap.hs - + testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs - + testsuite/tests/typecheck/should_compile/InstanceGivenOverlap2.hs Changes: ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -1502,14 +1502,12 @@ lhsPriority tv {- Note [TyVar/TyVar orientation] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": Update - Given (a ~ b), should we orient the CEqCan as (a~b) or (b~a)? This is a surprisingly tricky question! This is invariant (TyEq:TV). -The question is answered by swapOverTyVars, which is use +The question is answered by swapOverTyVars, which is used - in the eager unifier, in GHC.Tc.Utils.Unify.uUnfilledVar1 - - in the constraint solver, in GHC.Tc.Solver.Canonical.canEqTyVarHomo + - in the constraint solver, in GHC.Tc.Solver.Canonical.canEqCanLHS2 First note: only swap if you have to! See Note [Avoid unnecessary swaps] @@ -1529,15 +1527,23 @@ So we look for a positive reason to swap, using a three-step test: looks for meta tyvars on the left Tie-breaking rules for MetaTvs: - - TauTv = 3: if we have tyv_tv ~ tau_tv, - put tau_tv on the left because there are fewer - restrictions on updating TauTvs. Or to say it another - way, then we won't lose the TyVarTv flag + - CycleBreakerTv: This is essentially a stand-in for another type; + it's untouchable and should have the same priority as a skolem: 0. + + - TyVarTv: These can unify only with another tyvar, but we can't unify + a TyVarTv with a TauTv, because then the TyVarTv could (transitively) + get a non-tyvar type. So give these a low priority: 1. + + - TauTv: This is the common case; we want these on the left so that they + can be written to: 2. - - TyVarTv = 2: TyVarTvs come next + - RuntimeUnkTv: These aren't really meta-variables used in type inference, + but just a convenience in the implementation of the GHCi debugger. + Eagerly write to these: 3. See Note [RuntimeUnkTv] in + GHC.Runtime.Heap.Inspect. * Names. If the level and priority comparisons are all - equal, try to eliminate a TyVars with a System Name in + equal, try to eliminate a TyVar with a System Name in favour of ones with a Name derived from a user type signature * Age. At one point in the past we tried to break any remaining ===================================== testsuite/tests/typecheck/should_compile/CbvOverlap.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE TypeFamilies, FlexibleInstances, FlexibleContexts #-} + +module CbvOverlap where + +-- This is concerned with Note [Type variable cycles in Givens] and class lookup + +class C a where + meth :: a -> () + +instance C Int where + meth _ = () + +type family F a + +foo :: C (F a) => a -> Int -> () +foo _ n = meth n ===================================== testsuite/tests/typecheck/should_compile/InstanceGivenOverlap.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE ScopedTypeVariables, FlexibleInstances, MultiParamTypeClasses, + TypeFamilies, FlexibleContexts, AllowAmbiguousTypes #-} + +module InstanceGivenOverlap where + +-- See Note [Instance and Given overlap] in GHC.Tc.Solver.Interact. +-- This tests the Note when the Wanted contains a type family. + +class P a +class Q a +class R a b + +instance P x => Q [x] +instance (x ~ y) => R y [x] + +type family F a b where + F [a] a = a + +wob :: forall a b. (Q [F a b], R b a) => a -> Int +wob = undefined + +g :: forall a. Q [a] => [a] -> Int +g x = wob x ===================================== testsuite/tests/typecheck/should_compile/InstanceGivenOverlap2.hs ===================================== @@ -0,0 +1,44 @@ +{-# LANGUAGE ScopedTypeVariables, AllowAmbiguousTypes, TypeApplications, + TypeFamilies, PolyKinds, DataKinds, FlexibleInstances, + MultiParamTypeClasses, FlexibleContexts, PartialTypeSignatures #-} +{-# OPTIONS_GHC -Wno-partial-type-signatures #-} + +module InstanceGivenOverlap2 where + +import Data.Proxy + +class P a +class Q a +class R a b + +newtype Tagged (t :: k) a = Tagged a + +type family F a +type instance F (Tagged @Bool t a) = [a] + +instance P x => Q [x] +instance (x ~ y) => R y [x] + +wob :: forall a b. (Q [b], R b a) => a -> Int +wob = undefined + +it'sABoolNow :: forall (t :: Bool). Int +it'sABoolNow = undefined + +class HasBoolKind t +instance k ~ Bool => HasBoolKind (t :: k) + +it'sABoolLater :: forall t. HasBoolKind t => Int +it'sABoolLater = undefined + +g :: forall t a. Q (F (Tagged t a)) => Proxy t -> [a] -> _ +g _ x = it'sABoolNow @t + wob x + +g2 :: forall t a. Q (F (Tagged t a)) => Proxy t -> [a] -> _ +g2 _ x = wob x + it'sABoolNow @t + +g3 :: forall t a. Q (F (Tagged t a)) => Proxy t -> [a] -> _ +g3 _ x = it'sABoolLater @t + wob x + +g4 :: forall t a. Q (F (Tagged t a)) => Proxy t -> [a] -> _ +g4 _ x = wob x + it'sABoolLater @t View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebfebd6fd6e6407bc0c8ad81d31616b76fc8ce3d...9d122639ed288a794ffa20dae3ba9721f319c004 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ebfebd6fd6e6407bc0c8ad81d31616b76fc8ce3d...9d122639ed288a794ffa20dae3ba9721f319c004 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 Wed Nov 4 20:48:57 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 04 Nov 2020 15:48:57 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Do mightMatchLater correctlier. Message-ID: <5fa313b914545_10ee3ffbad34fc7c1364c7@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 5a9c4936 by Richard Eisenberg at 2020-11-04T15:48:36-05:00 Do mightMatchLater correctlier. - - - - - 3 changed files: - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -156,7 +156,7 @@ module GHC.Core.Type ( coVarsOfType, coVarsOfTypes, - anyFreeVarsOfType, + anyFreeVarsOfType, anyFreeVarsOfTypes, noFreeVarsOfType, splitVisVarsOfType, splitVisVarsOfTypes, expandTypeSynonyms, ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -1790,9 +1790,9 @@ flattenTys is defined here because of module dependencies. -} data FlattenEnv - = FlattenEnv { fe_type_map :: TypeMap TyVar + = FlattenEnv { fe_type_map :: TypeMap (TyVar, TyCon, [Type]) -- domain: exactly-saturated type family applications - -- range: fresh variables + -- range: (fresh variable, type family tycon, args) , fe_in_scope :: InScopeSet } -- See Note [Flattening] @@ -1808,15 +1808,26 @@ flattenTys :: InScopeSet -> [Type] -> [Type] -- See Note [Flattening] flattenTys in_scope tys = fst (flattenTysX in_scope tys) -flattenTysX :: InScopeSet -> [Type] -> ([Type], TyVarSet) +flattenTysX :: InScopeSet -> [Type] -> ([Type], TyVarEnv (TyCon, [Type])) -- See Note [Flattening] -- NB: the returned types mention the fresh type variables --- in the returned set. We don't return the --- mapping from those fresh vars to the ty-fam --- applications they stand for (we could, but no need) +-- in the domain of the returned env, whose range includes +-- the original type family applications. Building a substitution +-- from this information and applying it would yield the original +-- types -- almost. The problem is that the original type might +-- have something like (forall b. F a b); the returned environment +-- can't really sensibly refer to that b. So it may include a locally- +-- bound tyvar in its range. Currently, the only usage of this env't +-- checks whether there are any meta-variables in it +-- (in GHC.Tc.Solver.Monad.mightMatchLater), so this is all OK. flattenTysX in_scope tys = let (env, result) = coreFlattenTys emptyTvSubstEnv (emptyFlattenEnv in_scope) tys in - (result, foldTM (flip extendVarSet) (fe_type_map env) emptyVarSet) + (result, build_env (fe_type_map env)) + where + build_env :: TypeMap (TyVar, TyCon, [Type]) -> TyVarEnv (TyCon, [Type]) + build_env env_in + = foldTM (\(tv, tc, tys) env_out -> extendVarEnv env_out tv (tc, tys)) + env_in emptyVarEnv coreFlattenTys :: TvSubstEnv -> FlattenEnv -> [Type] -> (FlattenEnv, [Type]) @@ -1899,15 +1910,17 @@ coreFlattenTyFamApp :: TvSubstEnv -> FlattenEnv -> (FlattenEnv, Type) coreFlattenTyFamApp tv_subst env fam_tc fam_args = case lookupTypeMap type_map fam_ty of - Just tv -> (env', mkAppTys (mkTyVarTy tv) leftover_args') - Nothing -> let tyvar_name = mkFlattenFreshTyName fam_tc - tv = uniqAway in_scope $ - mkTyVar tyvar_name (typeKind fam_ty) - - ty' = mkAppTys (mkTyVarTy tv) leftover_args' - env'' = env' { fe_type_map = extendTypeMap type_map fam_ty tv - , fe_in_scope = extendInScopeSet in_scope tv } - in (env'', ty') + Just (tv, _, _) -> (env', mkAppTys (mkTyVarTy tv) leftover_args') + Nothing -> + let tyvar_name = mkFlattenFreshTyName fam_tc + tv = uniqAway in_scope $ + mkTyVar tyvar_name (typeKind fam_ty) + + ty' = mkAppTys (mkTyVarTy tv) leftover_args' + env'' = env' { fe_type_map = extendTypeMap type_map fam_ty + (tv, fam_tc, sat_fam_args) + , fe_in_scope = extendInScopeSet in_scope tv } + in (env'', ty') where arity = tyConArity fam_tc tcv_subst = TCvSubst (fe_in_scope env) tv_subst emptyVarEnv ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -1,6 +1,6 @@ {-# LANGUAGE CPP, DeriveFunctor, TypeFamilies, ScopedTypeVariables #-} -{-# OPTIONS_GHC -Wno-incomplete-record-updates #-} +{-# OPTIONS_GHC -Wno-incomplete-record-updates -Wno-incomplete-uni-patterns #-} -- | Type definitions for the constraint solver module GHC.Tc.Solver.Monad ( @@ -2129,25 +2129,20 @@ mightMatchLater given_pred given_loc wanted_pred wanted_loc | prohibitedSuperClassSolve given_loc wanted_loc = False - | SurelyApart <- tcUnifyTysFG bind_meta_tv flattened_given flattened_wanted + | SurelyApart <- tcUnifyTysFG bind_meta_tv [flattened_given] [flattened_wanted] = False | otherwise = True -- safe answer where - given_in_scope = mkInScopeSet $ tyCoVarsOfType given_pred - wanted_in_scope = mkInScopeSet $ tyCoVarsOfType wanted_pred + in_scope = mkInScopeSet $ tyCoVarsOfTypes [given_pred, wanted_pred] - (flattened_given, given_vars) - | anyFreeVarsOfType isMetaTyVar given_pred - = flattenTysX given_in_scope [given_pred] - | otherwise - = ([given_pred], emptyVarSet) - - (flattened_wanted, wanted_vars) - = flattenTysX wanted_in_scope [wanted_pred] - - all_flat_vars = given_vars `unionVarSet` wanted_vars + -- NB: flatten both at the same time, so that we can share mappings + -- from type family applications to variables, and also to guarantee + -- that the fresh variables are really fresh between the given and + -- the wanted. + ([flattened_given, flattened_wanted], var_mapping) + = flattenTysX in_scope [given_pred, wanted_pred] bind_meta_tv :: TcTyVar -> BindFlag -- Any meta tyvar may be unified later, so we treat it as @@ -2156,12 +2151,17 @@ mightMatchLater given_pred given_loc wanted_pred wanted_loc -- something that matches the 'given', until demonstrated -- otherwise. More info in Note [Instance and Given overlap] -- in GHC.Tc.Solver.Interact - bind_meta_tv tv | isMetaTyVar tv - , not (isCycleBreakerTyVar tv) = BindMe - -- a cycle-breaker var really stands for a type family - -- application where all variables are skolems - | tv `elemVarSet` all_flat_vars = BindMe - | otherwise = Skolem + bind_meta_tv tv | is_meta_tv tv = BindMe + + | Just (_fam_tc, fam_args) <- lookupVarEnv var_mapping tv + , anyFreeVarsOfTypes is_meta_tv fam_args + = BindMe + + | otherwise = Skolem + + -- CycleBreakerTvs really stands for a type family application in + -- a given; these won't contain touchable meta-variables + is_meta_tv = isMetaTyVar <&&> not . isCycleBreakerTyVar prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool -- See Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance @@ -2187,30 +2187,21 @@ in the Wanted might be arbitrarily instantiated. We do *not* want to allow skolems in the Given to be instantiated. But what about type family applications? -We break this down into two cases: a type family application in the -Given, and a type family application in the Wanted. - -* Given: Before ever looking at Wanteds, we process and simplify all -the Givens. So any type family applications in a Given have already -been fully reduced. Furthermore, future Wanteds won't rewrite Givens, -so information we learn later can't come to bear. So we worry about -reduction of a type family application in a Given only when it has -an metavariable in it (necessarily unfilled, because these types -have been zonked before getting here). A Given with a metavariable -is rare, but it can happen. See typecheck/should_compile/InstanceGivenOverlap2, -which uses partial type signatures and polykinds to pull it off. - -* Wanted: Unlike the Given case, a type family application in a -Wanted is always a cause for concern. Further information might allow -it to reduce, so we want to say that a type family application could -unify with any type. - -How we do this: we use the *core* flattener, as defined in the -flattenTys function. See Note [Flattening] in GHC.Core.Unify. This -function takes any type family application and turns it into a fresh -variable. These fresh variables must be flagged with BindMe in the -bind_meta_tv function, so that the unifier will match them. This -is the only reason we need to collect them here. +To allow flexibility in how type family applications unify we use +the Core flattener. See Note [Flattening] in GHC.Core.Unify. +This is *distinct* from the flattener in GHC.Tc.Solver.Flatten. +The Core flattener replaces all type family applications with +fresh variables. The next question: should we allow these fresh +variables in the domian of a unifying substitution? + +A type family application that mentions only skolems is settled: any +skolems would have been rewritten w.r.t. Givens by now. These type +family applications match only themselves. A type family application +that mentions metavariables, on the other hand, can match anything. +So, if the original type family application contains a metavariable, +we use BindMe to tell the unifier to allow it in the substitution. +On the other hand, a type family application with only skolems is +considered rigid. Note [When does an implication have given equalities?] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a9c493677d0ccbab27eaa467a0b095dbd6daef1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a9c493677d0ccbab27eaa467a0b095dbd6daef1 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 Wed Nov 4 21:47:35 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 04 Nov 2020 16:47:35 -0500 Subject: [Git][ghc/ghc][master] NCG: Fix 64bit int comparisons on 32bit x86 Message-ID: <5fa321777b24d_10ee3ffb8d3ef6c0141913@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - 6 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1824,6 +1824,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1841,22 +1870,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/GHC/CmmToAsm/X86/Cond.hs ===================================== @@ -11,22 +11,22 @@ import GHC.Prelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condToUnsigned :: Cond -> Cond ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb100805337adc666867da300ee5b0b11c18fe00 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb100805337adc666867da300ee5b0b11c18fe00 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 Wed Nov 4 21:48:48 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 04 Nov 2020 16:48:48 -0500 Subject: [Git][ghc/ghc][master] Don't use LEA with 8-bit registers (#18614) Message-ID: <5fa321c0bb57d_10ee3ffbc97f6a84145556@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 3 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - + testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_compile/all.T Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1052,7 +1052,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps -------------------- add_code :: Width -> CmmExpr -> CmmExpr -> NatM Register add_code rep x (CmmLit (CmmInt y _)) - | is32BitInteger y = add_int rep x y + | is32BitInteger y + , rep /= W8 -- LEA doesn't support byte size (#18614) + = add_int rep x y add_code rep x y = trivialCode rep (ADD format) (Just (ADD format)) x y where format = intFormat rep -- TODO: There are other interesting patterns we want to replace @@ -1061,7 +1063,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps -------------------- sub_code :: Width -> CmmExpr -> CmmExpr -> NatM Register sub_code rep x (CmmLit (CmmInt y _)) - | is32BitInteger (-y) = add_int rep x (-y) + | is32BitInteger (-y) + , rep /= W8 -- LEA doesn't support byte size (#18614) + = add_int rep x (-y) sub_code rep x y = trivialCode rep (SUB (intFormat rep)) Nothing x y -- our three-operand add instruction: ===================================== testsuite/tests/codeGen/should_compile/T18614.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +{-# OPTIONS_GHC -O #-} + +module Main where + +import GHC.Exts + +main = pure () + +test :: Word8# -> Word8# +test x = x `plusWord8#` narrowWord8# 1## ===================================== testsuite/tests/codeGen/should_compile/all.T ===================================== @@ -101,3 +101,5 @@ test('T15570', compile, ['-Wno-overflowed-literals']) # skipped with CmmToC because it generates a warning: # warning: integer constant is so large that it is unsigned + +test('T18614', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81560981fd9af7ea21b2592c405e9e22af838aab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/81560981fd9af7ea21b2592c405e9e22af838aab 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 Wed Nov 4 21:48:05 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 04 Nov 2020 16:48:05 -0500 Subject: [Git][ghc/ghc][master] Testsuite: Support for user supplied package dbs Message-ID: <5fa32195d9568_10ee3ffbc97f6a841423ec@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 4 changed files: - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk Changes: ===================================== testsuite/driver/runtests.py ===================================== @@ -73,6 +73,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -109,6 +110,9 @@ config.baseline_commit = args.perf_baseline if args.top: config.top = args.top +if args.test_package_db: + config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testglobals.py ===================================== @@ -169,6 +169,9 @@ class TestConfig: # Baseline commit for performane metric comparisons. self.baseline_commit = None # type: Optional[GitRef] + # Additional package dbs to inspect for test dependencies. + self.test_package_db = [] # type: [PathToPackageDb] + # Should we skip performance tests self.skip_perf_tests = False ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b790b7f91104197429cd80e2c192a6fcda9dd6b4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b790b7f91104197429cd80e2c192a6fcda9dd6b4 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 Nov 5 00:20:28 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 04 Nov 2020 19:20:28 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: NCG: Fix 64bit int comparisons on 32bit x86 Message-ID: <5fa3454c92987_10eeffdd9281656df@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - cefa2d98 by Viktor Dukhovni at 2020-11-04T19:20:14-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 99413bee by Ryan Scott at 2020-11-04T19:20:14-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - 23 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/StgToCmm/Prim.hs - libraries/base/GHC/Event/Internal.hs - libraries/ghc-prim/changelog.md - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm - + testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_compile/all.T - testsuite/tests/codeGen/should_compile/cg011.hs - testsuite/tests/codeGen/should_run/cas_int.hs - testsuite/tests/codeGen/should_run/cgrun080.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.stdout - + testsuite/tests/typecheck/should_compile/T18920.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -2079,39 +2079,47 @@ primop WriteOffAddrOp_Word64 "writeWord64OffAddr#" GenPrimOp with has_side_effects = True can_fail = True -primop InterlockedExchange_Addr "atomicExchangeAddr#" GenPrimOp +primop InterlockedExchange_Addr "atomicExchangeAddrAddr#" GenPrimOp Addr# -> Addr# -> State# s -> (# State# s, Addr# #) {The atomic exchange operation. Atomically exchanges the value at the first address with the Addr# given as second argument. Implies a read barrier.} with has_side_effects = True + can_fail = True -primop InterlockedExchange_Int "atomicExchangeInt#" GenPrimOp - Addr# -> Int# -> State# s -> (# State# s, Int# #) +primop InterlockedExchange_Word "atomicExchangeWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) {The atomic exchange operation. Atomically exchanges the value at the address with the given value. Returns the old value. Implies a read barrier.} with has_side_effects = True + can_fail = True -primop AtomicCompareExchange_Int "atomicCasInt#" GenPrimOp - Addr# -> Int# -> Int# -> State# s -> (# State# s, Int# #) +primop CasAddrOp_Addr "atomicCasAddrAddr#" GenPrimOp + Addr# -> Addr# -> Addr# -> State# s -> (# State# s, Addr# #) { Compare and swap on a word-sized memory location. - Use as atomicCasInt# location expected desired + Use as: \s -> atomicCasAddrAddr# location expected desired s - This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures). + This version always returns the old value read. This follows the normal + protocol for CAS operations (and matches the underlying instruction on + most architectures). Implies a full memory barrier.} with has_side_effects = True + can_fail = True -primop AtomicCompareExchange_Addr "atomicCasAddr#" GenPrimOp - Addr# -> Addr# -> Addr# -> State# s -> (# State# s, Addr# #) - { Compare and swap on a word-sized memory location. +primop CasAddrOp_Word "atomicCasWordAddr#" GenPrimOp + Addr# -> Word# -> Word# -> State# s -> (# State# s, Word# #) + { Compare and swap on a word-sized and aligned memory location. - Use as atomicCasAddr# location expected desired + Use as: \s -> atomicCasWordAddr# location expected desired s - This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures). + This version always returns the old value read. This follows the normal + protocol for CAS operations (and matches the underlying instruction on + most architectures). Implies a full memory barrier.} with has_side_effects = True + can_fail = True ------------------------------------------------------------------------ section "Mutable variables" ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1052,7 +1052,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps -------------------- add_code :: Width -> CmmExpr -> CmmExpr -> NatM Register add_code rep x (CmmLit (CmmInt y _)) - | is32BitInteger y = add_int rep x y + | is32BitInteger y + , rep /= W8 -- LEA doesn't support byte size (#18614) + = add_int rep x y add_code rep x y = trivialCode rep (ADD format) (Just (ADD format)) x y where format = intFormat rep -- TODO: There are other interesting patterns we want to replace @@ -1061,7 +1063,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps -------------------- sub_code :: Width -> CmmExpr -> CmmExpr -> NatM Register sub_code rep x (CmmLit (CmmInt y _)) - | is32BitInteger (-y) = add_int rep x (-y) + | is32BitInteger (-y) + , rep /= W8 -- LEA doesn't support byte size (#18614) + = add_int rep x (-y) sub_code rep x y = trivialCode rep (SUB (intFormat rep)) Nothing x y -- our three-operand add instruction: @@ -1824,6 +1828,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1841,22 +1874,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/GHC/CmmToAsm/X86/Cond.hs ===================================== @@ -11,22 +11,22 @@ import GHC.Prelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condToUnsigned :: Cond -> Cond ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -848,11 +848,11 @@ emitPrimOp dflags primop = case primop of -- Atomic operations InterlockedExchange_Addr -> \[src, value] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] - InterlockedExchange_Int -> \[src, value] -> opIntoRegs $ \[res] -> + InterlockedExchange_Word -> \[src, value] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] - AtomicCompareExchange_Int -> \[dst, expected, new] -> opIntoRegs $ \[res] -> + CasAddrOp_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] - AtomicCompareExchange_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> + CasAddrOp_Word -> \[dst, expected, new] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] -- SIMD primops ===================================== libraries/base/GHC/Event/Internal.hs ===================================== @@ -109,5 +109,5 @@ throwErrnoIfMinus1NoRetry loc f = do exchangePtr :: Ptr (Ptr a) -> Ptr a -> IO (Ptr a) exchangePtr (Ptr dst) (Ptr val) = IO $ \s -> - case (atomicExchangeAddr# dst val s) of + case (atomicExchangeAddrAddr# dst val s) of (# s2, old_val #) -> (# s2, Ptr old_val #) ===================================== libraries/ghc-prim/changelog.md ===================================== @@ -1,6 +1,6 @@ ## 0.7.0 (edit as necessary) -- Shipped with GHC 8.12.1 +- Shipped with GHC 9.0.1 - Add known-key `cstringLength#` to `GHC.CString`. This is just the C function `strlen`, but a built-in rewrite rule allows GHC to @@ -21,8 +21,13 @@ - Add primops for atomic exchange: - atomicExchangeAddr# :: Addr# -> Addr# -> State# s -> (# State# s, Addr# #) - atomicExchangeInt# :: Addr# -> Int# -> State# s -> (# State# s, Int# #) + atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# s -> (# State# s, Addr# #) + atomicExchangeWordAddr# :: Addr# -> Word# -> State# s -> (# State# s, Word# #) + +- Add primops for atomic compare and swap at a given Addr#: + + atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# s -> (# State# s, Addr# #) + atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# s -> (# State# s, Word# #) - Add an explicit fixity for `(~)` and `(~~)`: ===================================== testsuite/driver/runtests.py ===================================== @@ -73,6 +73,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -109,6 +110,9 @@ config.baseline_commit = args.perf_baseline if args.top: config.top = args.top +if args.test_package_db: + config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testglobals.py ===================================== @@ -169,6 +169,9 @@ class TestConfig: # Baseline commit for performane metric comparisons. self.baseline_commit = None # type: Optional[GitRef] + # Additional package dbs to inspect for test dependencies. + self.test_package_db = [] # type: [PathToPackageDb] + # Should we skip performance tests self.skip_perf_tests = False ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + ===================================== testsuite/tests/codeGen/should_compile/T18614.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +{-# OPTIONS_GHC -O #-} + +module Main where + +import GHC.Exts + +main = pure () + +test :: Word8# -> Word8# +test x = x `plusWord8#` narrowWord8# 1## ===================================== testsuite/tests/codeGen/should_compile/all.T ===================================== @@ -101,3 +101,5 @@ test('T15570', compile, ['-Wno-overflowed-literals']) # skipped with CmmToC because it generates a warning: # warning: integer constant is so large that it is unsigned + +test('T18614', normal, compile, ['']) ===================================== testsuite/tests/codeGen/should_compile/cg011.hs ===================================== @@ -4,8 +4,8 @@ module M where -import GHC.Exts (atomicExchangeInt#, Int#, Addr#, State# ) +import GHC.Exts (atomicExchangeWordAddr#, Word#, Addr#, State# ) -swap :: Addr# -> Int# -> State# s -> (# #) -swap ptr val s = case (atomicExchangeInt# ptr val s) of +swap :: Addr# -> Word# -> State# s -> (# #) +swap ptr val s = case (atomicExchangeWordAddr# ptr val s) of (# s2, old_val #) -> (# #) ===================================== testsuite/tests/codeGen/should_run/cas_int.hs ===================================== @@ -26,16 +26,16 @@ import GHC.Ptr #include "MachDeps.h" main = do - alloca $ \(ptr_p :: Ptr (Ptr Int)) -> do - alloca $ \(ptr_i :: Ptr Int) -> do - alloca $ \(ptr_j :: Ptr Int) -> do - poke ptr_i (1 :: Int) - poke ptr_j (2 :: Int) + alloca $ \(ptr_p :: Ptr (Ptr Word)) -> do + alloca $ \(ptr_i :: Ptr Word) -> do + alloca $ \(ptr_j :: Ptr Word) -> do + poke ptr_i (1 :: Word) + poke ptr_j (2 :: Word) --expected to swap - res_i <- cas ptr_i 1 3 :: IO Int + res_i <- cas ptr_i 1 3 :: IO Word -- expected to fail - res_j <- cas ptr_j 1 4 :: IO Int + res_j <- cas ptr_j 1 4 :: IO Word putStrLn "Returned results:" --(1,2) @@ -48,7 +48,7 @@ main = do --(3,2) print (i,j) -cas :: Ptr Int -> Int -> Int -> IO Int -cas (Ptr ptr) (I# expected) (I# desired)= do - IO $ \s -> case (atomicCasInt# ptr expected desired s) of - (# s2, old_val #) -> (# s2, I# old_val #) +cas :: Ptr Word -> Word -> Word -> IO Word +cas (Ptr ptr) (W# expected) (W# desired)= do + IO $ \s -> case (atomicCasWordAddr# ptr expected desired s) of + (# s2, old_val #) -> (# s2, W# old_val #) ===================================== testsuite/tests/codeGen/should_run/cgrun080.hs ===================================== @@ -25,8 +25,8 @@ import GHC.Types main = do alloca $ \ptr_i -> do - poke ptr_i (1 :: Int) - w1 <- newEmptyMVar :: IO (MVar Int) + poke ptr_i (1 :: Word) + w1 <- newEmptyMVar :: IO (MVar Word) forkIO $ do v <- swapN 50000 2 ptr_i putMVar w1 v @@ -37,15 +37,14 @@ main = do -- Should be [1,2,3] print $ sort [v0,v1,v2] -swapN :: Int -> Int -> Ptr Int -> IO Int +swapN :: Word -> Word -> Ptr Word -> IO Word swapN 0 val ptr = return val swapN n val ptr = do val' <- swap ptr val swapN (n-1) val' ptr -swap :: Ptr Int -> Int -> IO Int -swap (Ptr ptr) (I# val) = do - IO $ \s -> case (atomicExchangeInt# ptr val s) of - (# s2, old_val #) -> (# s2, I# old_val #) - +swap :: Ptr Word -> Word -> IO Word +swap (Ptr ptr) (W# val) = do + IO $ \s -> case (atomicExchangeWordAddr# ptr val s) of + (# s2, old_val #) -> (# s2, W# old_val #) ===================================== testsuite/tests/concurrent/should_run/AtomicPrimops.hs ===================================== @@ -6,6 +6,8 @@ module Main ( main ) where import Control.Concurrent import Control.Concurrent.MVar import Control.Monad (when) +import Foreign.Marshal.Alloc +import Foreign.Ptr import Foreign.Storable import GHC.Exts import GHC.IO @@ -22,6 +24,7 @@ main = do fetchOrTest fetchXorTest casTest + casTestAddr readWriteTest -- | Test fetchAddIntArray# by having two threads concurrenctly @@ -54,12 +57,14 @@ fetchXorTest = do work mba 0 val = return () work mba n val = fetchXorIntArray mba 0 val >> work mba (n-1) val - -- Initial value is a large prime and the two patterns are 1010... - -- and 0101... + -- The two patterns are 1010... and 0101... The second pattern is larger + -- than maxBound, avoid warnings by initialising as a Word. (n0, t1pat, t2pat) | sizeOf (undefined :: Int) == 8 = - (0x00000000ffffffff, 0x5555555555555555, 0x9999999999999999) - | otherwise = (0x0000ffff, 0x55555555, 0x99999999) + ( 0x00000000ffffffff, 0x5555555555555555 + , fromIntegral (0x9999999999999999 :: Word)) + | otherwise = ( 0x0000ffff, 0x55555555 + , fromIntegral (0x99999999 :: Word)) expected | sizeOf (undefined :: Int) == 8 = 4294967295 | otherwise = 65535 @@ -90,13 +95,15 @@ fetchOpTest op expected name = do -- | Initial value and operation arguments for race test. -- --- Initial value is a large prime and the two patterns are 1010... --- and 0101... +-- The two patterns are 1010... and 0101... The second pattern is larger than +-- maxBound, avoid warnings by initialising as a Word. n0, t1pat, t2pat :: Int (n0, t1pat, t2pat) | sizeOf (undefined :: Int) == 8 = - (0x00000000ffffffff, 0x5555555555555555, 0x9999999999999999) - | otherwise = (0x0000ffff, 0x55555555, 0x99999999) + ( 0x00000000ffffffff, 0x5555555555555555 + , fromIntegral (0x9999999999999999 :: Word)) + | otherwise = ( 0x0000ffff, 0x55555555 + , fromIntegral (0x99999999 :: Word)) fetchAndTest :: IO () fetchAndTest = fetchOpTest fetchAndIntArray expected "fetchAndTest" @@ -120,8 +127,10 @@ fetchNandTest = do fetchOrTest :: IO () fetchOrTest = fetchOpTest fetchOrIntArray expected "fetchOrTest" where expected - | sizeOf (undefined :: Int) == 8 = 15987178197787607039 - | otherwise = 3722313727 + | sizeOf (undefined :: Int) == 8 + = fromIntegral (15987178197787607039 :: Word) + | otherwise + = fromIntegral (3722313727 :: Word) -- | Test casIntArray# by using it to emulate fetchAddIntArray# and -- then having two threads concurrenctly increment a counter, @@ -131,7 +140,7 @@ casTest = do tot <- race 0 (\ mba -> work mba iters 1) (\ mba -> work mba iters 2) - assertEq 3000000 tot "casTest" + assertEq (3 * iters) tot "casTest" where work :: MByteArray -> Int -> Int -> IO () work mba 0 val = return () @@ -179,6 +188,45 @@ race n0 thread1 thread2 = do mapM_ takeMVar [done1, done2] readIntArray mba 0 +-- | Test atomicCasWordAddr# by having two threads concurrenctly increment a +-- counter, checking the sum at the end. +casTestAddr :: IO () +casTestAddr = do + tot <- raceAddr 0 + (\ addr -> work addr (fromIntegral iters) 1) + (\ addr -> work addr (fromIntegral iters) 2) + assertEq (3 * fromIntegral iters) tot "casTestAddr" + where + work :: Ptr Word -> Word -> Word -> IO () + work ptr 0 val = return () + work ptr n val = add ptr val >> work ptr (n-1) val + + -- Fetch-and-add implemented using CAS. + add :: Ptr Word -> Word -> IO () + add ptr n = peek ptr >>= go + where + go old = do + old' <- atomicCasWordPtr ptr old (old + n) + when (old /= old') $ go old' + + -- | Create two threads that mutate the byte array passed to them + -- concurrently. The array is one word large. + raceAddr :: Word -- ^ Initial value of array element + -> (Ptr Word -> IO ()) -- ^ Thread 1 action + -> (Ptr Word -> IO ()) -- ^ Thread 2 action + -> IO Word -- ^ Final value of array element + raceAddr n0 thread1 thread2 = do + done1 <- newEmptyMVar + done2 <- newEmptyMVar + ptr <- asWordPtr <$> callocBytes (sizeOf (undefined :: Word)) + forkIO $ thread1 ptr >> putMVar done1 () + forkIO $ thread2 ptr >> putMVar done2 () + mapM_ takeMVar [done1, done2] + peek ptr + where + asWordPtr :: Ptr a -> Ptr Word + asWordPtr = castPtr + ------------------------------------------------------------------------ -- Test helper @@ -254,3 +302,13 @@ casIntArray :: MByteArray -> Int -> Int -> Int -> IO Int casIntArray (MBA mba#) (I# ix#) (I# old#) (I# new#) = IO $ \ s# -> case casIntArray# mba# ix# old# new# s# of (# s2#, old2# #) -> (# s2#, I# old2# #) + +------------------------------------------------------------------------ +-- Wrappers around Addr# + +-- Should this be added to Foreign.Storable? Similar to poke, but does the +-- update atomically. +atomicCasWordPtr :: Ptr Word -> Word -> Word -> IO Word +atomicCasWordPtr (Ptr addr#) (W# old#) (W# new#) = IO $ \ s# -> + case atomicCasWordAddr# addr# old# new# s# of + (# s2#, old2# #) -> (# s2#, W# old2# #) ===================================== testsuite/tests/concurrent/should_run/AtomicPrimops.stdout ===================================== @@ -4,4 +4,5 @@ fetchNandTest: OK fetchOrTest: OK fetchXorTest: OK casTest: OK +casTestAddr: OK readWriteTest: OK ===================================== testsuite/tests/typecheck/should_compile/T18920.hs ===================================== @@ -0,0 +1,37 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE GADTs #-} +module T18920 where + +import Data.Kind + +class Monad solver => Solver solver where + type Constraint solver :: Type + type Label solver :: Type + +class Queue q + +data Tree s a where + NewVar :: Term s t => (t -> Tree s a) -> Tree s a + +class Solver solver => Term solver term + +class Transformer t where + type EvalState t :: Type + type TreeState t :: Type + type ForSolver t :: (Type -> Type) + type ForResult t :: Type + nextT :: SearchSig (ForSolver t) q t (ForResult t) + returnT :: ContinueSig solver q t (ForResult t) + +type ContinueSig solver q t a = + ( Solver solver, Queue q, Transformer t ) + => Int -> q -> t -> EvalState t + -> solver (Int, [a]) + +type SearchSig solver q t a = + (Solver solver, Queue q, Transformer t ) + => Int -> Tree solver a -> q -> t -> EvalState t -> TreeState t + -> solver (Int,[a]) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -725,6 +725,7 @@ test('T18470', normal, compile, ['']) test('T18323', normal, compile, ['']) test('T18585', normal, compile, ['']) test('T18831', normal, compile, ['']) +test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f782f586c353afe0999dbc189af5213ec3bf8817...99413bee163030a93ab4b8be75cb44b17a1f7d7a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f782f586c353afe0999dbc189af5213ec3bf8817...99413bee163030a93ab4b8be75cb44b17a1f7d7a 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 Nov 5 03:45:38 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 04 Nov 2020 22:45:38 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Simplify getNoGivenEqs Message-ID: <5fa37562eee9b_10ee80ba98418233@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: c65dc726 by Richard Eisenberg at 2020-11-04T22:45:26-05:00 Simplify getNoGivenEqs - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -2055,9 +2055,34 @@ getNoGivenEqs :: TcLevel -- TcLevel of this implication getNoGivenEqs tclvl skol_tvs = do { inerts@(IC { inert_eqs = ieqs, inert_funeqs = funeqs, inert_irreds = irreds }) <- getInertCans - ; let has_given_eqs = foldr ((||) . ct_given_here) False irreds - || anyDVarEnv tv_eqs_given_here ieqs - || anyFunEqMap funeqs fun_eqs_given_here + ; tc_lvl <- getTcLevel + ; let is_local_given_ct :: Ct -> Bool + is_local_given_ct = ct_given_here <&&> ct_mentions_outer_var + + is_local_given_equal_ct_list :: EqualCtList -> Bool + is_local_given_equal_ct_list [ct] = is_local_given_ct ct + -- Givens are always singletons in an EqualCtList + is_local_given_equal_ct_list _ = False + + ct_given_here :: Ct -> Bool + -- True for a Given bound by the current implication, + -- i.e. the current level + ct_given_here ct = isGiven ev + && tclvl == ctLocLevel (ctEvLoc ev) + where + ev = ctEvidence ct + + ct_mentions_outer_var :: Ct -> Bool + ct_mentions_outer_var = anyFreeVarsOfType is_outer_var . ctPred + + is_outer_var :: TyCoVar -> Bool + is_outer_var tv + | isTyVar tv = tc_lvl `strictlyDeeperThan` tcTyVarLevel tv + | otherwise = False + + has_given_eqs = anyBag is_local_given_ct irreds + || anyDVarEnv is_local_given_equal_ct_list ieqs + || anyFunEqMap funeqs is_local_given_equal_ct_list insols = filterBag insolubleEqCt irreds -- Specifically includes ones that originated in some -- outer context but were refined to an insoluble by @@ -2070,30 +2095,6 @@ getNoGivenEqs tclvl skol_tvs , text "Inerts:" <+> ppr inerts , text "Insols:" <+> ppr insols] ; return (not has_given_eqs, insols) } - where - tv_eqs_given_here :: EqualCtList -> Bool - tv_eqs_given_here [ct@(CEqCan { cc_lhs = TyVarLHS tv })] - -- Givens are always a singleton - = not (skolem_bound_here tv) && ct_given_here ct - tv_eqs_given_here _ = False - - fun_eqs_given_here :: EqualCtList -> Bool - fun_eqs_given_here [ct] = ct_given_here ct - fun_eqs_given_here _ = False - - ct_given_here :: Ct -> Bool - -- True for a Given bound by the current implication, - -- i.e. the current level - ct_given_here ct = isGiven ev - && tclvl == ctLocLevel (ctEvLoc ev) - where - ev = ctEvidence ct - - skol_tv_set = mkVarSet skol_tvs - skolem_bound_here tv -- See Note [Let-bound skolems] - = case tcTyVarDetails tv of - SkolemTv {} -> tv `elemVarSet` skol_tv_set - _ -> False -- | Returns Given constraints that might, -- potentially, match the given pred. This is used when checking to see if a @@ -2248,6 +2249,8 @@ are some wrinkles: Note [Let-bound skolems] ~~~~~~~~~~~~~~~~~~~~~~~~ +"RAE": Update note. + If * the inert set contains a canonical Given CEqCan (a ~ ty) and * 'a' is a skolem bound in this very implication, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c65dc7261c1ccef93fd3e54fb2d84282f3225dbd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c65dc7261c1ccef93fd3e54fb2d84282f3225dbd 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 Nov 5 03:49:49 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 04 Nov 2020 22:49:49 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Simplify code a bit Message-ID: <5fa3765d8711b_10ee3ffb979042f0183330@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 564244ce by Richard Eisenberg at 2020-11-04T22:49:39-05:00 Simplify code a bit - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -2055,32 +2055,7 @@ getNoGivenEqs :: TcLevel -- TcLevel of this implication getNoGivenEqs tclvl skol_tvs = do { inerts@(IC { inert_eqs = ieqs, inert_funeqs = funeqs, inert_irreds = irreds }) <- getInertCans - ; tc_lvl <- getTcLevel - ; let is_local_given_ct :: Ct -> Bool - is_local_given_ct = ct_given_here <&&> ct_mentions_outer_var - - is_local_given_equal_ct_list :: EqualCtList -> Bool - is_local_given_equal_ct_list [ct] = is_local_given_ct ct - -- Givens are always singletons in an EqualCtList - is_local_given_equal_ct_list _ = False - - ct_given_here :: Ct -> Bool - -- True for a Given bound by the current implication, - -- i.e. the current level - ct_given_here ct = isGiven ev - && tclvl == ctLocLevel (ctEvLoc ev) - where - ev = ctEvidence ct - - ct_mentions_outer_var :: Ct -> Bool - ct_mentions_outer_var = anyFreeVarsOfType is_outer_var . ctPred - - is_outer_var :: TyCoVar -> Bool - is_outer_var tv - | isTyVar tv = tc_lvl `strictlyDeeperThan` tcTyVarLevel tv - | otherwise = False - - has_given_eqs = anyBag is_local_given_ct irreds + ; let has_given_eqs = anyBag is_local_given_ct irreds || anyDVarEnv is_local_given_equal_ct_list ieqs || anyFunEqMap funeqs is_local_given_equal_ct_list insols = filterBag insolubleEqCt irreds @@ -2095,6 +2070,28 @@ getNoGivenEqs tclvl skol_tvs , text "Inerts:" <+> ppr inerts , text "Insols:" <+> ppr insols] ; return (not has_given_eqs, insols) } + where + is_local_given_ct :: Ct -> Bool + is_local_given_ct = (given_here <&&> mentions_outer_var) . ctEvidence + + is_local_given_equal_ct_list :: EqualCtList -> Bool + is_local_given_equal_ct_list [ct] = is_local_given_ct ct + -- Givens are always singletons in an EqualCtList + is_local_given_equal_ct_list _ = False + + given_here :: CtEvidence -> Bool + -- True for a Given bound by the current implication, + -- i.e. the current level + given_here ev = isGiven ev + && tclvl == ctLocLevel (ctEvLoc ev) + + mentions_outer_var :: CtEvidence -> Bool + mentions_outer_var = anyFreeVarsOfType is_outer_var . ctEvPred + + is_outer_var :: TyCoVar -> Bool + is_outer_var tv + | isTyVar tv = tclvl `strictlyDeeperThan` tcTyVarLevel tv + | otherwise = False -- | Returns Given constraints that might, -- potentially, match the given pred. This is used when checking to see if a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/564244cef7c6a106bbb9d893e63fd84126dcf842 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/564244cef7c6a106bbb9d893e63fd84126dcf842 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 Nov 5 04:41:42 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Wed, 04 Nov 2020 23:41:42 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-always-pic] 4 commits: NCG: Fix 64bit int comparisons on 32bit x86 Message-ID: <5fa382864d264_10ee3ffbd500cac4185970@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-always-pic at Glasgow Haskell Compiler / GHC Commits: bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 842e3f38 by Moritz Angermann at 2020-11-04T23:41:37-05:00 [AArch64] Aarch64 Always PIC - - - - - 18 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/runtime_control.rst - includes/rts/Flags.h - rts/Libdw.c - rts/Linker.c - rts/LinkerInternals.h - testsuite/driver/runtests.py - testsuite/driver/testglobals.py - testsuite/driver/testlib.py - testsuite/mk/test.mk - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm - + testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_compile/all.T Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1052,7 +1052,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps -------------------- add_code :: Width -> CmmExpr -> CmmExpr -> NatM Register add_code rep x (CmmLit (CmmInt y _)) - | is32BitInteger y = add_int rep x y + | is32BitInteger y + , rep /= W8 -- LEA doesn't support byte size (#18614) + = add_int rep x y add_code rep x y = trivialCode rep (ADD format) (Just (ADD format)) x y where format = intFormat rep -- TODO: There are other interesting patterns we want to replace @@ -1061,7 +1063,9 @@ getRegister' _ is32Bit (CmmMachOp mop [x, y]) = -- dyadic MachOps -------------------- sub_code :: Width -> CmmExpr -> CmmExpr -> NatM Register sub_code rep x (CmmLit (CmmInt y _)) - | is32BitInteger (-y) = add_int rep x (-y) + | is32BitInteger (-y) + , rep /= W8 -- LEA doesn't support byte size (#18614) + = add_int rep x (-y) sub_code rep x y = trivialCode rep (SUB (intFormat rep)) Nothing x y -- our three-operand add instruction: @@ -1824,6 +1828,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1841,22 +1874,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/GHC/CmmToAsm/X86/Cond.hs ===================================== @@ -11,22 +11,22 @@ import GHC.Prelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condToUnsigned :: Cond -> Cond ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3796,8 +3796,21 @@ validHoleFitsImpliedGFlags default_PIC :: Platform -> [GeneralFlag] default_PIC platform = case (platformOS platform, platformArch platform) of - (OSDarwin, ArchX86_64) -> [Opt_PIC] - (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in + -- Darwin always requires PIC. Especially on more recent macOS releases + -- there will be a 4GB __ZEROPAGE that prevents us from using 32bit addresses + -- while we could work around this on x86_64 (like WINE does), we won't be + -- able on aarch64, where this is enforced. + (OSDarwin, ArchX86_64) -> [Opt_PIC] + -- For AArch64, we need to always have PIC enabled. The relocation model + -- on AArch64 does not permit arbitrary relocations. Under ASLR, we can't + -- control much how far apart symbols are in memory for our in-memory static + -- linker; and thus need to ensure we get sufficiently capable relocations. + -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top + -- of that. Subsequently we expect all code on aarch64/linux (and macOS) to + -- be built with -fPIC. + (OSDarwin, ArchARM64) -> [Opt_PIC] + (OSLinux, ArchARM64) -> [Opt_PIC, Opt_ExternalDynamicRefs] + (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release -- (1 May 2013) we need to -- always generate PIC. See ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -327,8 +327,10 @@ Miscellaneous RTS options an object, the linker will probably fail with an error message when the problem is detected. - On some platforms where PIC is always the case, e.g. x86_64 MacOS X, this - flag is enabled by default. + On some platforms where PIC is always the case, e.g. macOS and OpenBSD on + x86_64, and macOS and Linux on aarch64 this flag is enabled by default. + One repercussion of this is that referenced system libraries also need to be + compiled with ``-fPIC`` if we need to load them in the runtime linker. .. rts-flag:: -xm ⟨address⟩ ===================================== includes/rts/Flags.h ===================================== @@ -200,7 +200,7 @@ typedef struct _CONCURRENT_FLAGS { * files were compiled with -fPIC -fexternal-dynamic-refs and load them * anywhere in the address space. */ -#if defined(x86_64_HOST_ARCH) && defined(darwin_HOST_OS) +#if defined(darwin_HOST_OS) || defined(aarch64_HOST_ARCH) #define DEFAULT_LINKER_ALWAYS_PIC true #else #define DEFAULT_LINKER_ALWAYS_PIC false ===================================== rts/Libdw.c ===================================== @@ -133,8 +133,9 @@ int libdwLookupLocation(LibdwSession *session, Location *frame, Dwfl_Module *mod = dwfl_addrmodule(session->dwfl, addr); if (mod == NULL) return 1; + void *object_file = &frame->object_file; dwfl_module_info(mod, NULL, NULL, NULL, NULL, NULL, - &frame->object_file, NULL); + object_file, NULL); // Find function name frame->function = dwfl_module_addrname(mod, addr); ===================================== rts/Linker.c ===================================== @@ -1022,42 +1022,6 @@ resolveSymbolAddr (pathchar* buffer, int size, } #if RTS_LINKER_USE_MMAP - -/* ----------------------------------------------------------------------------- - Occationally we depend on mmap'd region being close to already mmap'd regions. - - Our static in-memory linker may be restricted by the architectures relocation - range. E.g. aarch64 has a +-4GB range for PIC code, thus we'd preferrably - get memory for the linker close to existing mappings. mmap on it's own is - free to return any memory location, independent of what the preferred - location argument indicates. - - For example mmap (via qemu) might give you addresses all over the available - memory range if the requested location is already occupied. - - mmap_next will do a linear search from the start page upwards to find a - suitable location that is as close as possible to the locations (proivded - via the first argument). - -------------------------------------------------------------------------- */ - -void* -mmap_next(void *addr, size_t length, int prot, int flags, int fd, off_t offset) { - if(addr == NULL) return mmap(addr, length, prot, flags, fd, offset); - // we are going to look for up to pageSize * 1024 * 1024 (4GB) from the - // address. - size_t pageSize = getPageSize(); - for(int i = (uintptr_t)addr & (pageSize-1) ? 1 : 0; i < 1024*1024; i++) { - void *target = (void*)(((uintptr_t)addr & ~(pageSize-1))+(i*pageSize)); - void *mem = mmap(target, length, prot, flags, fd, offset); - if(mem == NULL) return mem; - if(mem == target) return mem; - munmap(mem, length); - IF_DEBUG(linker && (i % 1024 == 0), - debugBelch("mmap_next failed to find suitable space in %p - %p\n", addr, target)); - } - return NULL; -} - // // Returns NULL on failure. // @@ -1089,8 +1053,8 @@ mmap_again: debugBelch("mmapForLinker: \tflags %#0x\n", MAP_PRIVATE | tryMap32Bit | fixed | flags)); - result = mmap_next(map_addr, size, prot, - MAP_PRIVATE|tryMap32Bit|fixed|flags, fd, offset); + result = mmap(map_addr, size, prot, + MAP_PRIVATE|tryMap32Bit|fixed|flags, fd, offset); if (result == MAP_FAILED) { sysErrorBelch("mmap %" FMT_Word " bytes at %p",(W_)size,map_addr); ===================================== rts/LinkerInternals.h ===================================== @@ -14,7 +14,6 @@ #if RTS_LINKER_USE_MMAP #include -void* mmap_next(void *addr, size_t length, int prot, int flags, int fd, off_t offset); #endif void printLoadedObjects(void); ===================================== testsuite/driver/runtests.py ===================================== @@ -73,6 +73,7 @@ parser.add_argument("--junit", type=argparse.FileType('wb'), help="output testsu parser.add_argument("--broken-test", action="append", default=[], help="a test name to mark as broken for this run") parser.add_argument("--test-env", default='local', help="Override default chosen test-env.") parser.add_argument("--perf-baseline", type=GitRef, metavar='COMMIT', help="Baseline commit for performance comparsons.") +parser.add_argument("--test-package-db", dest="test_package_db", action="append", help="Package db providing optional packages used by the testsuite.") perf_group.add_argument("--skip-perf-tests", action="store_true", help="skip performance tests") perf_group.add_argument("--only-perf-tests", action="store_true", help="Only do performance tests") @@ -109,6 +110,9 @@ config.baseline_commit = args.perf_baseline if args.top: config.top = args.top +if args.test_package_db: + config.test_package_db = args.test_package_db + if args.only: config.only = args.only config.run_only_some_tests = True ===================================== testsuite/driver/testglobals.py ===================================== @@ -169,6 +169,9 @@ class TestConfig: # Baseline commit for performane metric comparisons. self.baseline_commit = None # type: Optional[GitRef] + # Additional package dbs to inspect for test dependencies. + self.test_package_db = [] # type: [PathToPackageDb] + # Should we skip performance tests self.skip_perf_tests = False ===================================== testsuite/driver/testlib.py ===================================== @@ -165,7 +165,16 @@ def have_library(lib: str) -> bool: got_it = have_lib_cache[lib] else: cmd = strip_quotes(config.ghc_pkg) - p = subprocess.Popen([cmd, '--no-user-package-db', 'describe', lib], + cmd_line = [cmd, '--no-user-package-db'] + + for db in config.test_package_db: + cmd_line.append("--package-db="+db) + + cmd_line.extend(['describe', lib]) + + print(cmd_line) + + p = subprocess.Popen(cmd_line, stdout=subprocess.PIPE, stderr=subprocess.PIPE, env=ghc_env) @@ -181,6 +190,10 @@ def have_library(lib: str) -> bool: def _reqlib( name, opts, lib ): if not have_library(lib): opts.expect = 'missing-lib' + else: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package ' + lib + ' ' + for db in config.test_package_db: + opts.extra_hc_opts = opts.extra_hc_opts + ' -package-db=' + db + ' ' def req_haddock( name, opts ): if not config.haddock: ===================================== testsuite/mk/test.mk ===================================== @@ -216,6 +216,10 @@ ifneq "$(THREADS)" "" RUNTEST_OPTS += --threads=$(THREADS) endif +ifneq "$(PACKAGE_DB)" "" +RUNTEST_OPTS += --test-package-db=$(PACKAGE_DB) +endif + ifneq "$(VERBOSE)" "" RUNTEST_OPTS += --verbose=$(VERBOSE) endif ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + ===================================== testsuite/tests/codeGen/should_compile/T18614.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE MagicHash, UnboxedTuples #-} +{-# OPTIONS_GHC -O #-} + +module Main where + +import GHC.Exts + +main = pure () + +test :: Word8# -> Word8# +test x = x `plusWord8#` narrowWord8# 1## ===================================== testsuite/tests/codeGen/should_compile/all.T ===================================== @@ -101,3 +101,5 @@ test('T15570', compile, ['-Wno-overflowed-literals']) # skipped with CmmToC because it generates a warning: # warning: integer constant is so large that it is unsigned + +test('T18614', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6cc2b8646579e296f49f1029d660c38bb44d979a...842e3f3888f73567d4f20e7e213c6ad28cfa0eb2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6cc2b8646579e296f49f1029d660c38bb44d979a...842e3f3888f73567d4f20e7e213c6ad28cfa0eb2 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 Nov 5 04:58:35 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Wed, 04 Nov 2020 23:58:35 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 10 commits: Update inlining flags documentation Message-ID: <5fa3867b3f8a8_10ee3ffb94f1afc0190511@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - bc741fff by Moritz Angermann at 2020-11-05T04:54:12+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 27 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - + compiler/GHC/HsToCore/PmCheck/Oracle.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - + compiler/GHC/Linker.hs - + compiler/GHC/Linker/Dynamic.hs - compiler/GHC/SysTools/ExtraObj.hs → compiler/GHC/Linker/ExtraObj.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70d20e24088fe6a36dfd800e4f56796e5b98a60c...bc741fff17ef302f28ca86d36f842e867049462c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70d20e24088fe6a36dfd800e4f56796e5b98a60c...bc741fff17ef302f28ca86d36f842e867049462c 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 Nov 5 05:50:32 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 05 Nov 2020 00:50:32 -0500 Subject: [Git][ghc/ghc][master] Naming, value types and tests for Addr# atomics Message-ID: <5fa392a8afac4_10ee3ffbadf6938c20284f@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 9 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/StgToCmm/Prim.hs - libraries/base/GHC/Event/Internal.hs - libraries/ghc-prim/changelog.md - testsuite/tests/codeGen/should_compile/cg011.hs - testsuite/tests/codeGen/should_run/cas_int.hs - testsuite/tests/codeGen/should_run/cgrun080.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.stdout Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -2079,39 +2079,47 @@ primop WriteOffAddrOp_Word64 "writeWord64OffAddr#" GenPrimOp with has_side_effects = True can_fail = True -primop InterlockedExchange_Addr "atomicExchangeAddr#" GenPrimOp +primop InterlockedExchange_Addr "atomicExchangeAddrAddr#" GenPrimOp Addr# -> Addr# -> State# s -> (# State# s, Addr# #) {The atomic exchange operation. Atomically exchanges the value at the first address with the Addr# given as second argument. Implies a read barrier.} with has_side_effects = True + can_fail = True -primop InterlockedExchange_Int "atomicExchangeInt#" GenPrimOp - Addr# -> Int# -> State# s -> (# State# s, Int# #) +primop InterlockedExchange_Word "atomicExchangeWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) {The atomic exchange operation. Atomically exchanges the value at the address with the given value. Returns the old value. Implies a read barrier.} with has_side_effects = True + can_fail = True -primop AtomicCompareExchange_Int "atomicCasInt#" GenPrimOp - Addr# -> Int# -> Int# -> State# s -> (# State# s, Int# #) +primop CasAddrOp_Addr "atomicCasAddrAddr#" GenPrimOp + Addr# -> Addr# -> Addr# -> State# s -> (# State# s, Addr# #) { Compare and swap on a word-sized memory location. - Use as atomicCasInt# location expected desired + Use as: \s -> atomicCasAddrAddr# location expected desired s - This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures). + This version always returns the old value read. This follows the normal + protocol for CAS operations (and matches the underlying instruction on + most architectures). Implies a full memory barrier.} with has_side_effects = True + can_fail = True -primop AtomicCompareExchange_Addr "atomicCasAddr#" GenPrimOp - Addr# -> Addr# -> Addr# -> State# s -> (# State# s, Addr# #) - { Compare and swap on a word-sized memory location. +primop CasAddrOp_Word "atomicCasWordAddr#" GenPrimOp + Addr# -> Word# -> Word# -> State# s -> (# State# s, Word# #) + { Compare and swap on a word-sized and aligned memory location. - Use as atomicCasAddr# location expected desired + Use as: \s -> atomicCasWordAddr# location expected desired s - This version always returns the old value read. This follows the normal protocol for CAS operations (and matches the underlying instruction on most architectures). + This version always returns the old value read. This follows the normal + protocol for CAS operations (and matches the underlying instruction on + most architectures). Implies a full memory barrier.} with has_side_effects = True + can_fail = True ------------------------------------------------------------------------ section "Mutable variables" ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -848,11 +848,11 @@ emitPrimOp dflags primop = case primop of -- Atomic operations InterlockedExchange_Addr -> \[src, value] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] - InterlockedExchange_Int -> \[src, value] -> opIntoRegs $ \[res] -> + InterlockedExchange_Word -> \[src, value] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] - AtomicCompareExchange_Int -> \[dst, expected, new] -> opIntoRegs $ \[res] -> + CasAddrOp_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] - AtomicCompareExchange_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> + CasAddrOp_Word -> \[dst, expected, new] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] -- SIMD primops ===================================== libraries/base/GHC/Event/Internal.hs ===================================== @@ -109,5 +109,5 @@ throwErrnoIfMinus1NoRetry loc f = do exchangePtr :: Ptr (Ptr a) -> Ptr a -> IO (Ptr a) exchangePtr (Ptr dst) (Ptr val) = IO $ \s -> - case (atomicExchangeAddr# dst val s) of + case (atomicExchangeAddrAddr# dst val s) of (# s2, old_val #) -> (# s2, Ptr old_val #) ===================================== libraries/ghc-prim/changelog.md ===================================== @@ -1,6 +1,6 @@ ## 0.7.0 (edit as necessary) -- Shipped with GHC 8.12.1 +- Shipped with GHC 9.0.1 - Add known-key `cstringLength#` to `GHC.CString`. This is just the C function `strlen`, but a built-in rewrite rule allows GHC to @@ -21,8 +21,13 @@ - Add primops for atomic exchange: - atomicExchangeAddr# :: Addr# -> Addr# -> State# s -> (# State# s, Addr# #) - atomicExchangeInt# :: Addr# -> Int# -> State# s -> (# State# s, Int# #) + atomicExchangeAddrAddr# :: Addr# -> Addr# -> State# s -> (# State# s, Addr# #) + atomicExchangeWordAddr# :: Addr# -> Word# -> State# s -> (# State# s, Word# #) + +- Add primops for atomic compare and swap at a given Addr#: + + atomicCasAddrAddr# :: Addr# -> Addr# -> Addr# -> State# s -> (# State# s, Addr# #) + atomicCasWordAddr# :: Addr# -> Word# -> Word# -> State# s -> (# State# s, Word# #) - Add an explicit fixity for `(~)` and `(~~)`: ===================================== testsuite/tests/codeGen/should_compile/cg011.hs ===================================== @@ -4,8 +4,8 @@ module M where -import GHC.Exts (atomicExchangeInt#, Int#, Addr#, State# ) +import GHC.Exts (atomicExchangeWordAddr#, Word#, Addr#, State# ) -swap :: Addr# -> Int# -> State# s -> (# #) -swap ptr val s = case (atomicExchangeInt# ptr val s) of +swap :: Addr# -> Word# -> State# s -> (# #) +swap ptr val s = case (atomicExchangeWordAddr# ptr val s) of (# s2, old_val #) -> (# #) ===================================== testsuite/tests/codeGen/should_run/cas_int.hs ===================================== @@ -26,16 +26,16 @@ import GHC.Ptr #include "MachDeps.h" main = do - alloca $ \(ptr_p :: Ptr (Ptr Int)) -> do - alloca $ \(ptr_i :: Ptr Int) -> do - alloca $ \(ptr_j :: Ptr Int) -> do - poke ptr_i (1 :: Int) - poke ptr_j (2 :: Int) + alloca $ \(ptr_p :: Ptr (Ptr Word)) -> do + alloca $ \(ptr_i :: Ptr Word) -> do + alloca $ \(ptr_j :: Ptr Word) -> do + poke ptr_i (1 :: Word) + poke ptr_j (2 :: Word) --expected to swap - res_i <- cas ptr_i 1 3 :: IO Int + res_i <- cas ptr_i 1 3 :: IO Word -- expected to fail - res_j <- cas ptr_j 1 4 :: IO Int + res_j <- cas ptr_j 1 4 :: IO Word putStrLn "Returned results:" --(1,2) @@ -48,7 +48,7 @@ main = do --(3,2) print (i,j) -cas :: Ptr Int -> Int -> Int -> IO Int -cas (Ptr ptr) (I# expected) (I# desired)= do - IO $ \s -> case (atomicCasInt# ptr expected desired s) of - (# s2, old_val #) -> (# s2, I# old_val #) +cas :: Ptr Word -> Word -> Word -> IO Word +cas (Ptr ptr) (W# expected) (W# desired)= do + IO $ \s -> case (atomicCasWordAddr# ptr expected desired s) of + (# s2, old_val #) -> (# s2, W# old_val #) ===================================== testsuite/tests/codeGen/should_run/cgrun080.hs ===================================== @@ -25,8 +25,8 @@ import GHC.Types main = do alloca $ \ptr_i -> do - poke ptr_i (1 :: Int) - w1 <- newEmptyMVar :: IO (MVar Int) + poke ptr_i (1 :: Word) + w1 <- newEmptyMVar :: IO (MVar Word) forkIO $ do v <- swapN 50000 2 ptr_i putMVar w1 v @@ -37,15 +37,14 @@ main = do -- Should be [1,2,3] print $ sort [v0,v1,v2] -swapN :: Int -> Int -> Ptr Int -> IO Int +swapN :: Word -> Word -> Ptr Word -> IO Word swapN 0 val ptr = return val swapN n val ptr = do val' <- swap ptr val swapN (n-1) val' ptr -swap :: Ptr Int -> Int -> IO Int -swap (Ptr ptr) (I# val) = do - IO $ \s -> case (atomicExchangeInt# ptr val s) of - (# s2, old_val #) -> (# s2, I# old_val #) - +swap :: Ptr Word -> Word -> IO Word +swap (Ptr ptr) (W# val) = do + IO $ \s -> case (atomicExchangeWordAddr# ptr val s) of + (# s2, old_val #) -> (# s2, W# old_val #) ===================================== testsuite/tests/concurrent/should_run/AtomicPrimops.hs ===================================== @@ -6,6 +6,8 @@ module Main ( main ) where import Control.Concurrent import Control.Concurrent.MVar import Control.Monad (when) +import Foreign.Marshal.Alloc +import Foreign.Ptr import Foreign.Storable import GHC.Exts import GHC.IO @@ -22,6 +24,7 @@ main = do fetchOrTest fetchXorTest casTest + casTestAddr readWriteTest -- | Test fetchAddIntArray# by having two threads concurrenctly @@ -54,12 +57,14 @@ fetchXorTest = do work mba 0 val = return () work mba n val = fetchXorIntArray mba 0 val >> work mba (n-1) val - -- Initial value is a large prime and the two patterns are 1010... - -- and 0101... + -- The two patterns are 1010... and 0101... The second pattern is larger + -- than maxBound, avoid warnings by initialising as a Word. (n0, t1pat, t2pat) | sizeOf (undefined :: Int) == 8 = - (0x00000000ffffffff, 0x5555555555555555, 0x9999999999999999) - | otherwise = (0x0000ffff, 0x55555555, 0x99999999) + ( 0x00000000ffffffff, 0x5555555555555555 + , fromIntegral (0x9999999999999999 :: Word)) + | otherwise = ( 0x0000ffff, 0x55555555 + , fromIntegral (0x99999999 :: Word)) expected | sizeOf (undefined :: Int) == 8 = 4294967295 | otherwise = 65535 @@ -90,13 +95,15 @@ fetchOpTest op expected name = do -- | Initial value and operation arguments for race test. -- --- Initial value is a large prime and the two patterns are 1010... --- and 0101... +-- The two patterns are 1010... and 0101... The second pattern is larger than +-- maxBound, avoid warnings by initialising as a Word. n0, t1pat, t2pat :: Int (n0, t1pat, t2pat) | sizeOf (undefined :: Int) == 8 = - (0x00000000ffffffff, 0x5555555555555555, 0x9999999999999999) - | otherwise = (0x0000ffff, 0x55555555, 0x99999999) + ( 0x00000000ffffffff, 0x5555555555555555 + , fromIntegral (0x9999999999999999 :: Word)) + | otherwise = ( 0x0000ffff, 0x55555555 + , fromIntegral (0x99999999 :: Word)) fetchAndTest :: IO () fetchAndTest = fetchOpTest fetchAndIntArray expected "fetchAndTest" @@ -120,8 +127,10 @@ fetchNandTest = do fetchOrTest :: IO () fetchOrTest = fetchOpTest fetchOrIntArray expected "fetchOrTest" where expected - | sizeOf (undefined :: Int) == 8 = 15987178197787607039 - | otherwise = 3722313727 + | sizeOf (undefined :: Int) == 8 + = fromIntegral (15987178197787607039 :: Word) + | otherwise + = fromIntegral (3722313727 :: Word) -- | Test casIntArray# by using it to emulate fetchAddIntArray# and -- then having two threads concurrenctly increment a counter, @@ -131,7 +140,7 @@ casTest = do tot <- race 0 (\ mba -> work mba iters 1) (\ mba -> work mba iters 2) - assertEq 3000000 tot "casTest" + assertEq (3 * iters) tot "casTest" where work :: MByteArray -> Int -> Int -> IO () work mba 0 val = return () @@ -179,6 +188,45 @@ race n0 thread1 thread2 = do mapM_ takeMVar [done1, done2] readIntArray mba 0 +-- | Test atomicCasWordAddr# by having two threads concurrenctly increment a +-- counter, checking the sum at the end. +casTestAddr :: IO () +casTestAddr = do + tot <- raceAddr 0 + (\ addr -> work addr (fromIntegral iters) 1) + (\ addr -> work addr (fromIntegral iters) 2) + assertEq (3 * fromIntegral iters) tot "casTestAddr" + where + work :: Ptr Word -> Word -> Word -> IO () + work ptr 0 val = return () + work ptr n val = add ptr val >> work ptr (n-1) val + + -- Fetch-and-add implemented using CAS. + add :: Ptr Word -> Word -> IO () + add ptr n = peek ptr >>= go + where + go old = do + old' <- atomicCasWordPtr ptr old (old + n) + when (old /= old') $ go old' + + -- | Create two threads that mutate the byte array passed to them + -- concurrently. The array is one word large. + raceAddr :: Word -- ^ Initial value of array element + -> (Ptr Word -> IO ()) -- ^ Thread 1 action + -> (Ptr Word -> IO ()) -- ^ Thread 2 action + -> IO Word -- ^ Final value of array element + raceAddr n0 thread1 thread2 = do + done1 <- newEmptyMVar + done2 <- newEmptyMVar + ptr <- asWordPtr <$> callocBytes (sizeOf (undefined :: Word)) + forkIO $ thread1 ptr >> putMVar done1 () + forkIO $ thread2 ptr >> putMVar done2 () + mapM_ takeMVar [done1, done2] + peek ptr + where + asWordPtr :: Ptr a -> Ptr Word + asWordPtr = castPtr + ------------------------------------------------------------------------ -- Test helper @@ -254,3 +302,13 @@ casIntArray :: MByteArray -> Int -> Int -> Int -> IO Int casIntArray (MBA mba#) (I# ix#) (I# old#) (I# new#) = IO $ \ s# -> case casIntArray# mba# ix# old# new# s# of (# s2#, old2# #) -> (# s2#, I# old2# #) + +------------------------------------------------------------------------ +-- Wrappers around Addr# + +-- Should this be added to Foreign.Storable? Similar to poke, but does the +-- update atomically. +atomicCasWordPtr :: Ptr Word -> Word -> Word -> IO Word +atomicCasWordPtr (Ptr addr#) (W# old#) (W# new#) = IO $ \ s# -> + case atomicCasWordAddr# addr# old# new# s# of + (# s2#, old2# #) -> (# s2#, W# old2# #) ===================================== testsuite/tests/concurrent/should_run/AtomicPrimops.stdout ===================================== @@ -4,4 +4,5 @@ fetchNandTest: OK fetchOrTest: OK fetchXorTest: OK casTest: OK +casTestAddr: OK readWriteTest: OK View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17d5c51834d64f1762320b7abaa40c5686564f4d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17d5c51834d64f1762320b7abaa40c5686564f4d 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 Nov 5 05:51:08 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 05 Nov 2020 00:51:08 -0500 Subject: [Git][ghc/ghc][master] Add a regression test for #18920 Message-ID: <5fa392cc74a23_10ee3ffbaf41888c206828@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - 2 changed files: - + testsuite/tests/typecheck/should_compile/T18920.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== testsuite/tests/typecheck/should_compile/T18920.hs ===================================== @@ -0,0 +1,37 @@ +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE Rank2Types #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE GADTs #-} +module T18920 where + +import Data.Kind + +class Monad solver => Solver solver where + type Constraint solver :: Type + type Label solver :: Type + +class Queue q + +data Tree s a where + NewVar :: Term s t => (t -> Tree s a) -> Tree s a + +class Solver solver => Term solver term + +class Transformer t where + type EvalState t :: Type + type TreeState t :: Type + type ForSolver t :: (Type -> Type) + type ForResult t :: Type + nextT :: SearchSig (ForSolver t) q t (ForResult t) + returnT :: ContinueSig solver q t (ForResult t) + +type ContinueSig solver q t a = + ( Solver solver, Queue q, Transformer t ) + => Int -> q -> t -> EvalState t + -> solver (Int, [a]) + +type SearchSig solver q t a = + (Solver solver, Queue q, Transformer t ) + => Int -> Tree solver a -> q -> t -> EvalState t -> TreeState t + -> solver (Int,[a]) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -725,6 +725,7 @@ test('T18470', normal, compile, ['']) test('T18323', normal, compile, ['']) test('T18585', normal, compile, ['']) test('T18831', normal, compile, ['']) +test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2125b1d6bea0c620e3a089603dace6bb38020c81 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2125b1d6bea0c620e3a089603dace6bb38020c81 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 Fri Nov 6 17:40:09 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Fri, 06 Nov 2020 12:40:09 -0500 Subject: [Git][ghc/ghc][wip/con-info] 2 commits: Info table rather than closure Message-ID: <5fa58a79bf4c4_10ee3ffbac65a7605148dd@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: d95bb9ec by Matthew Pickering at 2020-11-06T17:02:17+00:00 Info table rather than closure - - - - - 2eed068b by Matthew Pickering at 2020-11-06T17:39:53+00:00 Try to fix performance problem - - - - - 4 changed files: - compiler/GHC/StgToCmm/Monad.hs - includes/rts/IPE.h - rts/IPE.c - rts/PrimOps.cmm Changes: ===================================== compiler/GHC/StgToCmm/Monad.hs ===================================== @@ -817,8 +817,13 @@ emitProc mb_info lbl live blocks offset do_layout proc_block = CmmProc tinfo lbl live blks ; state <- getState + ; dflags <- getDynFlags + ; let new_info + | gopt Opt_InfoTableMap dflags + = maybe (cgs_used_info state) (: cgs_used_info state) mb_info + | otherwise = [] ; setState $ state { cgs_tops = cgs_tops state `snocOL` proc_block - , cgs_used_info = maybe (cgs_used_info state) (: cgs_used_info state) mb_info } } + , cgs_used_info = new_info } } getCmm :: FCode () -> FCode CmmGroup -- Get all the CmmTops (there should be no stmts) ===================================== includes/rts/IPE.h ===================================== @@ -14,4 +14,4 @@ #pragma once void registerInfoProvList(InfoProvEnt **cc_list); -InfoProvEnt * lookupIPE(StgClosure *info); \ No newline at end of file +InfoProvEnt * lookupIPE(StgInfoTable *info); \ No newline at end of file ===================================== rts/IPE.c ===================================== @@ -69,18 +69,17 @@ void registerInfoProvList(InfoProvEnt **ent_list) // MP: TODO: This should not be a linear search, need to improve // the IPE_LIST structure -InfoProvEnt * lookupIPE(StgClosure *clos) +InfoProvEnt * lookupIPE(StgInfoTable *info) { - StgInfoTable * info; - info = GET_INFO(clos); InfoProvEnt *ip, *next; - //printf("%p\n", info); +// printf("%p\n", info); //printf("%p\n\n", clos); for (ip = IPE_LIST; ip != NULL; ip = next) { +// printf("%p\n", ip->info); if (ip->info == info) { //printf("Found %p\n", ip->info); return ip; } next = ip->link; } -} \ No newline at end of file +} ===================================== rts/PrimOps.cmm ===================================== @@ -2412,7 +2412,9 @@ stg_closureSizzezh (P_ clos) stg_whereFromzh (P_ clos) { P_ ipe; - (ipe) = foreign "C" lookupIPE(UNTAG(clos) "ptr"); + W_ info; + info = GET_INFO(UNTAG(clos)); + (ipe) = foreign "C" lookupIPE(info "ptr"); return (ipe); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b21a42b28d7e9c4927cdcdda08a28551acee512f...2eed068bef601f3ea544dc906b7f6b5fd3211f06 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b21a42b28d7e9c4927cdcdda08a28551acee512f...2eed068bef601f3ea544dc906b7f6b5fd3211f06 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 Fri Nov 6 17:44:37 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Fri, 06 Nov 2020 12:44:37 -0500 Subject: [Git][ghc/ghc][wip/con-info] Refine tests Message-ID: <5fa58b85eda3a_10ee3ffbd52eaae85157e0@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: cc717d63 by Matthew Pickering at 2020-11-06T17:44:23+00:00 Refine tests - - - - - 4 changed files: - testsuite/tests/profiling/should_run/staticcallstack001.hs - testsuite/tests/profiling/should_run/staticcallstack001.stdout - testsuite/tests/profiling/should_run/staticcallstack002.hs - testsuite/tests/profiling/should_run/staticcallstack002.stdout Changes: ===================================== testsuite/tests/profiling/should_run/staticcallstack001.hs ===================================== @@ -13,7 +13,7 @@ qq x = D x caf = D 5 main = do - print =<< whereFrom (D 5) - print =<< whereFrom caf - print =<< whereFrom (id (D 5)) + print . tail =<< whereFrom (D 5) + print . tail =<< whereFrom caf + print . tail =<< whereFrom (id (D 5)) ===================================== testsuite/tests/profiling/should_run/staticcallstack001.stdout ===================================== @@ -1,3 +1,3 @@ -["D_Main_4_con_info","0","","main","Main","staticcallstack001.hs:16:13-27"] -["D_Main_2_con_info","0","","caf","Main","staticcallstack001.hs:13:1-9"] -["sat_sZR_info","15","D","main","Main","staticcallstack001.hs:18:23-32"] +["0","","main","Main","staticcallstack001.hs:16:20-34"] +["0","","caf","Main","staticcallstack001.hs:13:1-9"] +["15","D","main","Main","staticcallstack001.hs:18:30-39"] ===================================== testsuite/tests/profiling/should_run/staticcallstack002.hs ===================================== @@ -7,8 +7,8 @@ import GHC.Stack.CCS -- a special case to not generate distinct info tables for unboxed -- constructors. main = do - print =<< whereFrom (undefined (# #)) - print =<< whereFrom (undefined (# () #)) - print =<< whereFrom (undefined (# (), () #)) - print =<< whereFrom (undefined (# | () #)) + print . tail =<< whereFrom (undefined (# #)) + print . tail =<< whereFrom (undefined (# () #)) + print . tail =<< whereFrom (undefined (# (), () #)) + print . tail =<< whereFrom (undefined (# | () #)) ===================================== testsuite/tests/profiling/should_run/staticcallstack002.stdout ===================================== @@ -1,4 +1,4 @@ -["sat_sZt_info","15","main","Main","staticcallstack002.hs:10:23-39"] -["sat_sZJ_info","15","main","Main","staticcallstack002.hs:11:23-42"] -["sat_sZZ_info","15","main","Main","staticcallstack002.hs:12:23-46"] -["sat_s10f_info","15","main","Main","staticcallstack002.hs:13:23-44"] +["15","Any","main","Main","staticcallstack002.hs:10:30-46"] +["15","Any","main","Main","staticcallstack002.hs:11:30-49"] +["15","Any","main","Main","staticcallstack002.hs:12:30-53"] +["15","Any","main","Main","staticcallstack002.hs:13:30-51"] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc717d630a86502f1a204783215ce5f304113ce3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc717d630a86502f1a204783215ce5f304113ce3 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 Fri Nov 6 17:45:57 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Fri, 06 Nov 2020 12:45:57 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18891 Message-ID: <5fa58bd5bb531_10ee10f3b0b45164f5@gitlab.haskell.org.mail> Simon Peyton Jones pushed new branch wip/T18891 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18891 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 Fri Nov 6 17:49:45 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Fri, 06 Nov 2020 12:49:45 -0500 Subject: [Git][ghc/ghc][wip/con-info] More memory fix Message-ID: <5fa58cb99e6a4_10ee3ffbae496da051822b@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: eb5cae12 by Matthew Pickering at 2020-11-06T17:49:28+00:00 More memory fix - - - - - 1 changed file: - compiler/GHC/CoreToStg.hs Changes: ===================================== compiler/GHC/CoreToStg.hs ===================================== @@ -52,7 +52,7 @@ import GHC.Builtin.Names ( unsafeEqualityProofName ) import GHC.Data.Maybe import Data.List.NonEmpty (nonEmpty, toList) -import Control.Monad (ap) +import Control.Monad (when, ap) import qualified Data.Set as Set import Control.Monad.Trans.RWS import GHC.Types.Unique.Map @@ -952,7 +952,7 @@ incDc dc = CtsM $ \dflags _ _ -> if not (gopt Opt_DistinctConstructorTables dfla return (fst . head <$> r) recordStgIdPosition :: Id -> Maybe (RealSrcSpan, String) -> Maybe (RealSrcSpan, String) -> CtsM () -recordStgIdPosition id best_span ss = CtsM $ \dflags _ _ -> do +recordStgIdPosition id best_span ss = CtsM $ \dflags _ _ -> when (gopt Opt_InfoTableMap dflags) $ do cc <- ask let tyString = showPpr dflags (idType id) --pprTraceM "recordStgIdPosition" (ppr id $$ ppr cc $$ ppr ss) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb5cae122f9149d3a176f47753016340a2093087 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb5cae122f9149d3a176f47753016340a2093087 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 Fri Nov 6 17:59:43 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Fri, 06 Nov 2020 12:59:43 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_getClosureFromHeapRep] ghc-heap: expose decoding from heap representation Message-ID: <5fa58f0fcd37b_10ee3ffbac04e844522874@gitlab.haskell.org.mail> David Eichmann pushed to branch wip/ghc-debug_getClosureFromHeapRep at Glasgow Haskell Compiler / GHC Commits: 4de4be2b by David Eichmann at 2020-11-06T17:59:13+00:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 3 changed files: - includes/rts/storage/Heap.h - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/Heap.c Changes: ===================================== includes/rts/storage/Heap.h ===================================== @@ -16,3 +16,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs , StgClosure *fun, StgClosure **payload, StgWord size); StgWord heap_view_closureSize(StgClosure *closure); + +/* + * Collect the pointers of a closure into the given array. `size` should be + * large enough to hold all collected pointers e.g. + * `heap_view_closureSize(closure)`. Returns the number of pointers collected. + * The caller must ensure that `closure` is not modified (or moved by the GC) + * for the duration of the call to `collect_pointers`. + */ +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[]); ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -7,6 +7,9 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE UnliftedFFITypes #-} {-| Module : GHC.Exts.Heap @@ -25,6 +28,7 @@ module GHC.Exts.Heap ( , ClosureType(..) , PrimType(..) , HasHeapRep(getClosureData) + , getClosureDataFromHeapRep -- * Info Table types , StgInfoTable(..) @@ -58,7 +62,7 @@ import GHC.Exts.Heap.Utils import Control.Monad import Data.Bits -import GHC.Arr +import Foreign import GHC.Exts import GHC.Int import GHC.Word @@ -66,13 +70,19 @@ import GHC.Word #include "ghcconfig.h" class HasHeapRep (a :: TYPE rep) where - getClosureData :: a -> IO Closure + + -- | Decode a closure to it's heap representation ('GenClosure'). + getClosureData + :: a + -- ^ Closure to decode. + -> IO Closure + -- ^ Heap representation of the closure. instance HasHeapRep (a :: TYPE 'LiftedRep) where - getClosureData = getClosure + getClosureData = getClosureDataFromHeapObject instance HasHeapRep (a :: TYPE 'UnliftedRep) where - getClosureData x = getClosure (unsafeCoerce# x) + getClosureData x = getClosureDataFromHeapObject (unsafeCoerce# x) instance Int# ~ a => HasHeapRep (a :: TYPE 'IntRep) where getClosureData x = return $ @@ -102,49 +112,84 @@ instance Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) where getClosureData x = return $ DoubleClosure { ptipe = PDouble, doubleVal = D# x } --- | This returns the raw representation of the given argument. The second --- component of the triple is the raw words of the closure on the heap, and the --- third component is those words that are actually pointers. Once back in the --- Haskell world, the raw words that hold pointers may be outdated after a --- garbage collector run, but the corresponding values in 'Box's will still --- point to the correct value. -getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box]) -getClosureRaw x = do +-- | Get the heap representation of a closure _at this moment_, even if it is +-- unevaluated or an indirection or other exotic stuff. Beware when passing +-- something to this function, the same caveats as for +-- 'GHC.Exts.Heap.Closures.asBox' apply. +-- +-- For most use cases 'getClosureData' is an easier to use alternative. +-- +-- Currently TSO and STACK objects will return `UnsupportedClosure`. This is +-- because it is not memory safe to extract TSO and STACK objects (done via +-- `unpackClosure#`). Other threads may be mutating those objects and interleave +-- with reads in `unpackClosure#`. This is particularly problematic with STACKs +-- where pointer values may be overwritten by non-pointer values as the +-- corresponding haskell thread runs. +getClosureDataFromHeapObject + :: a + -- ^ Heap object to decode. + -> IO Closure + -- ^ Heap representation of the closure. +getClosureDataFromHeapObject x = do case unpackClosure# x of --- This is a hack to cover the bootstrap compiler using the old version of --- 'unpackClosure'. The new 'unpackClosure' return values are not merely --- a reordering, so using the old version would not work. - (# iptr, dat, pointers #) -> do - let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE - end = fromIntegral nelems - 1 - rawWds = [W# (indexWordArray# dat i) | I# i <- [0.. end] ] - pelems = I# (sizeofArray# pointers) - ptrList = amap' Box $ Array 0 (pelems - 1) pelems pointers - pure (Ptr iptr, rawWds, ptrList) - --- From GHC.Runtime.Heap.Inspect -amap' :: (t -> b) -> Array Int t -> [b] -amap' f (Array i0 i _ arr#) = map g [0 .. i - i0] - where g (I# i#) = case indexArray# arr# i# of - (# e #) -> f e - --- | This function returns a parsed heap representation of the argument _at --- this moment_, even if it is unevaluated or an indirection or other exotic --- stuff. Beware when passing something to this function, the same caveats as --- for 'asBox' apply. -getClosure :: a -> IO Closure -getClosure x = do - (iptr, wds, pts) <- getClosureRaw x - itbl <- peekItbl iptr - -- The remaining words after the header - let rawWds = drop (closureTypeHeaderSize (tipe itbl)) wds - -- For data args in a pointers then non-pointers closure - -- This is incorrect in non pointers-first setups - -- not sure if that happens - npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) wds +#if MIN_VERSION_ghc_prim(0,5,3) + (# infoTableAddr, heapRep, pointersArray #) -> do +#else + -- This is a hack to cover the bootstrap compiler using the old version + -- of 'unpackClosure'. The new 'unpackClosure' return values are not + -- merely a reordering, so using the old version would not work. + (# infoTableAddr, pointersArray, heapRep #) -> do +#endif + let infoTablePtr = Ptr infoTableAddr + ptrList = [case indexArray# pointersArray i of + (# ptr #) -> Box ptr + | I# i <- [0..(I# (sizeofArray# pointersArray)) - 1] + ] + + infoTable <- peekItbl infoTablePtr + case tipe infoTable of + TSO -> pure $ UnsupportedClosure infoTable + STACK -> pure $ UnsupportedClosure infoTable + _ -> getClosureDataFromHeapRep heapRep infoTablePtr ptrList + +-- | Convert an unpacked heap object, to a `GenClosure b`. The inputs to this +-- function can be generated from a heap object using `unpackClosure#`. +getClosureDataFromHeapRep + :: ByteArray# + -- ^ Heap representation of the closure as returned by `unpackClosure#`. + -- This includes all of the object including the header, info table + -- pointer, pointer data, and non-pointer data. The ByteArray# may be + -- pinned or unpinned. + -> Ptr StgInfoTable + -- ^ Pointer to the `StgInfoTable` of the closure, extracted from the heap + -- representation. The info table must not be movable by GC i.e. must be in + -- pinned or off-heap memory. + -> [b] + -- ^ Pointers in the payload of the closure, extracted from the heap + -- representation as returned by `collect_pointers()` in `Heap.c`. The type + -- `b` is some representation of a pointer e.g. `Any` or `Ptr Any`. + -> IO (GenClosure b) + -- ^ Heap representation of the closure. +getClosureDataFromHeapRep heapRep infoTablePtr pts = do + itbl <- peekItbl infoTablePtr + let -- heapRep as a list of words. + rawHeapWords :: [Word] + rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ] + where + nelems = (I# (sizeofByteArray# heapRep)) `div` wORD_SIZE + end = fromIntegral nelems - 1 + + -- Just the payload of rawHeapWords (no header). + payloadWords :: [Word] + payloadWords = drop (closureTypeHeaderSize (tipe itbl)) rawHeapWords + + -- The non-pointer words in the payload. Only valid for closures with a + -- "pointers first" layout. Not valid for bit field layout. + npts :: [Word] + npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) rawHeapWords case tipe itbl of t | t >= CONSTR && t <= CONSTR_NOCAF -> do - (p, m, n) <- dataConNames iptr + (p, m, n) <- dataConNames infoTablePtr if m == "GHC.ByteCode.Instr" && n == "BreakInfo" then pure $ UnsupportedClosure itbl else pure $ ConstrClosure itbl pts npts p m n @@ -164,9 +209,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to AP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 raw words to AP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ APClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -181,9 +226,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to PAP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail "Expected at least 2 raw words to PAP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ PAPClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -218,10 +263,10 @@ getClosure x = do unless (length pts >= 3) $ fail $ "Expected at least 3 ptr argument to BCO, found " ++ show (length pts) - unless (length rawWds >= 4) $ + unless (length payloadWords >= 4) $ fail $ "Expected at least 4 words to BCO, found " - ++ show (length rawWds) - let splitWord = rawWds !! 3 + ++ show (length payloadWords) + let splitWord = payloadWords !! 3 pure $ BCOClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -230,27 +275,30 @@ getClosure x = do (fromIntegral splitWord) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) #endif - (drop 4 rawWds) + (drop 4 payloadWords) ARR_WORDS -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 words to ARR_WORDS, found " - ++ show (length rawWds) - pure $ ArrWordsClosure itbl (head rawWds) (tail rawWds) + ++ show (length payloadWords) + pure $ ArrWordsClosure itbl (head payloadWords) (tail payloadWords) t | t >= MUT_ARR_PTRS_CLEAN && t <= MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 words to MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ MutArrClosure itbl (rawWds !! 0) (rawWds !! 1) pts + ++ "found " ++ show (length payloadWords) + pure $ MutArrClosure itbl (payloadWords !! 0) (payloadWords !! 1) pts t | t >= SMALL_MUT_ARR_PTRS_CLEAN && t <= SMALL_MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 word to SMALL_MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ SmallMutArrClosure itbl (rawWds !! 0) pts + ++ "found " ++ show (length payloadWords) + pure $ SmallMutArrClosure itbl (payloadWords !! 0) pts - t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> + t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> do + unless (length pts >= 1) $ + fail $ "Expected at least 1 words to MUT_VAR, found " + ++ show (length pts) pure $ MutVarClosure itbl (head pts) t | t == MVAR_CLEAN || t == MVAR_DIRTY -> do @@ -260,13 +308,12 @@ getClosure x = do pure $ MVarClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) BLOCKING_QUEUE -> - pure $ OtherClosure itbl pts wds + pure $ OtherClosure itbl pts rawHeapWords -- pure $ BlockingQueueClosure itbl -- (pts !! 0) (pts !! 1) (pts !! 2) (pts !! 3) - -- pure $ OtherClosure itbl pts wds + -- pure $ OtherClosure itbl pts rawHeapWords -- - WEAK -> pure $ WeakClosure { info = itbl ===================================== rts/Heap.c ===================================== @@ -76,23 +76,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs } } -StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { - ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); - - StgWord size = heap_view_closureSize(closure); - StgWord nptrs = 0; - StgWord i; - - // First collect all pointers here, with the comfortable memory bound - // of the whole closure. Afterwards we know how many pointers are in - // the closure and then we can allocate space on the heap and copy them - // there - StgClosure *ptrs[size]; - +// See Heap.h +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[size]) { StgClosure **end; - StgClosure **ptr; - const StgInfoTable *info = get_itbl(closure); + StgWord nptrs = 0; + StgWord i; switch (info->type) { case INVALID_OBJECT: @@ -101,6 +90,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { // No pointers case ARR_WORDS: + case STACK: break; // Default layout @@ -123,7 +113,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case FUN_0_2: case FUN_STATIC: end = closure->payload + info->layout.payload.ptrs; - for (ptr = closure->payload; ptr < end; ptr++) { + for (StgClosure **ptr = closure->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -136,7 +126,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case THUNK_0_2: case THUNK_STATIC: end = ((StgThunk *)closure)->payload + info->layout.payload.ptrs; - for (ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { + for (StgClosure **ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -228,6 +218,21 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { break; } + return nptrs; +} + +StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); + + StgWord size = heap_view_closureSize(closure); + + // First collect all pointers here, with the comfortable memory bound + // of the whole closure. Afterwards we know how many pointers are in + // the closure and then we can allocate space on the heap and copy them + // there + StgClosure *ptrs[size]; + StgWord nptrs = collect_pointers(closure, size, ptrs); + size = nptrs + mutArrPtrsCardTableSize(nptrs); StgMutArrPtrs *arr = (StgMutArrPtrs *)allocate(cap, sizeofW(StgMutArrPtrs) + size); @@ -236,7 +241,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { arr->ptrs = nptrs; arr->size = size; - for (i = 0; ipayload[i] = ptrs[i]; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4de4be2be940dba84f50abd91a67d78fc4615634 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4de4be2be940dba84f50abd91a67d78fc4615634 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 Fri Nov 6 20:20:07 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Fri, 06 Nov 2020 15:20:07 -0500 Subject: [Git][ghc/ghc][wip/amg/hasfield-2020] 155 commits: Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Message-ID: <5fa5aff7a3694_10ee3ffbadbfe080538978@gitlab.haskell.org.mail> Adam Gundry pushed to branch wip/amg/hasfield-2020 at Glasgow Haskell Compiler / GHC Commits: bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 342e178d by Adam Gundry at 2020-11-06T14:49:35+00:00 Update GHC.Records to use hasField instead of getField - - - - - b2684b6c by Adam Gundry at 2020-11-06T19:27:42+00:00 Add updaters to FieldLabels and solve new HasField constraints (#16232) - - - - - 70fe0565 by Adam Gundry at 2020-11-06T19:27:42+00:00 Refactor: move addClsInsts and addFamInsts out of tcInstDecls1 Also modify addTyConsToGblEnv to use the thing_inside pattern - - - - - 7c2606de by Adam Gundry at 2020-11-06T19:27:42+00:00 Update user's guide for changes to HasField - - - - - 6f46e74a by Adam Gundry at 2020-11-06T19:27:42+00:00 Update HasField tests Adapt overloadedrecflds tests and T17355 to new definition of HasField Extend hasfieldrun01 test with partial record field test Update hasfieldfail02 test to check unlifted type case Accept changed T14189 output due to FieldLabel additional field Adjust expected output from dynamic-paper Add hasfieldrun03 test for example from user's guide (Probable) Metric Increase: T12227 T12707 T13056 T15630 T18304 T9233 T9675 - - - - - 355fd370 by Adam Gundry at 2020-11-06T19:27:42+00:00 Exclude record updaters from HIE files I'm unsure if this is the right way to accomplish this, or even if this is desireable in the first place, but it prevents them showing up in haddockHypsrcTest. - - - - - 991e84b1 by Adam Gundry at 2020-11-06T19:27:42+00:00 Keep track of Origin for RecordUpd - - - - - 424b1ef9 by Adam Gundry at 2020-11-06T19:27:42+00:00 Generate alternative form of updaters that are faster to typecheck - - - - - 828b222d by Adam Gundry at 2020-11-06T20:13:56+00:00 Experiment with using as-patterns in updaters - - - - - 6ce03739 by Adam Gundry at 2020-11-06T20:14:14+00:00 Revert "Experiment with using as-patterns in updaters" This reverts commit 828b222d14345423861658369751eccfb2b845e6. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Monad.hs → compiler/GHC/Cmm/Parser/Monad.hs - compiler/GHC/Cmm/Pipeline.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bd38281d87b736631056d2cd835dd230bcbc330e...6ce037393b555389b84bc0e7af53757ba6f4347d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bd38281d87b736631056d2cd835dd230bcbc330e...6ce037393b555389b84bc0e7af53757ba6f4347d 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 Sat Nov 7 13:40:07 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sat, 07 Nov 2020 08:40:07 -0500 Subject: [Git][ghc/ghc][wip/T18914] Use HsOuterExplicit in instance sigs in deriving-generated code Message-ID: <5fa6a3b7af5d8_10ee3ffbaf4a6394594383@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: 1553ed81 by Ryan Scott at 2020-11-07T08:37:26-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. - - - - - 10 changed files: - compiler/GHC/Hs/Type.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/deriving/should_compile/T14578.stderr - + testsuite/tests/deriving/should_compile/T18914.hs - testsuite/tests/deriving/should_compile/all.T - utils/haddock Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -24,7 +24,7 @@ module GHC.Hs.Type ( HsArrow(..), arrowToHsType, hsLinear, hsUnrestricted, isUnrestricted, - HsType(..), NewHsTypeX(..), LHsType, HsKind, LHsKind, + HsType(..), HsCoreTy(..), LHsType, HsKind, LHsKind, HsForAllTelescope(..), HsTyVarBndr(..), LHsTyVarBndr, LHsQTyVars(..), HsOuterTyVarBndrs(..), HsOuterFamEqnTyVarBndrs, HsOuterSigTyVarBndrs, @@ -1077,16 +1077,19 @@ data HsType pass | XHsType (XXType pass) -data NewHsTypeX - = NHsCoreTy Type -- An escape hatch for tunnelling a *closed* - -- Core Type through HsSyn. - -- See also Note [Typechecking NHsCoreTys] in - -- GHC.Tc.Gen.HsType. - deriving Data +-- An escape hatch for tunnelling a Core 'Type' through 'HsType'. +-- For more details on how this works, see: +-- +-- * @Note [Renaming HsCoreTys]@ in "GHC.Rename.HsType" +-- +-- * @Note [Typechecking HsCoreTys]@ in "GHC.Tc.Gen.HsType" +newtype HsCoreTy + = HsCoreTy Type -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None + deriving Data -instance Outputable NewHsTypeX where - ppr (NHsCoreTy ty) = ppr ty +instance Outputable HsCoreTy where + ppr (HsCoreTy ty) = ppr ty type instance XForAllTy (GhcPass _) = NoExtField type instance XQualTy (GhcPass _) = NoExtField @@ -1124,7 +1127,7 @@ type instance XTyLit (GhcPass _) = NoExtField type instance XWildCardTy (GhcPass _) = NoExtField -type instance XXType (GhcPass _) = NewHsTypeX +type instance XXType (GhcPass _) = HsCoreTy -- Note [Literal source text] in GHC.Types.Basic for SourceText fields in @@ -2250,7 +2253,7 @@ hsTypeNeedsParens p = go_hs_ty go_hs_ty (HsOpTy{}) = p >= opPrec go_hs_ty (HsParTy{}) = False go_hs_ty (HsDocTy _ (L _ t) _) = go_hs_ty t - go_hs_ty (XHsType (NHsCoreTy ty)) = go_core_ty ty + go_hs_ty (XHsType (HsCoreTy ty)) = go_core_ty ty go_core_ty (TyVarTy{}) = False go_core_ty (AppTy{}) = p >= appPrec ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -39,6 +39,7 @@ import GHC.Prelude import {-# SOURCE #-} GHC.Rename.Splice( rnSpliceType ) +import GHC.Core.TyCo.FVs ( tyCoVarsOfTypeList ) import GHC.Driver.Session import GHC.Hs import GHC.Rename.Env @@ -48,6 +49,7 @@ import GHC.Rename.Utils ( HsDocContext(..), inHsDocContext, withHsDocContext , checkShadowedRdrNames ) import GHC.Rename.Fixity ( lookupFieldFixityRn, lookupFixityRn , lookupTyFixityRn ) +import GHC.Rename.Unbound ( notInScopeErr ) import GHC.Tc.Utils.Monad import GHC.Types.Name.Reader import GHC.Builtin.Names @@ -634,10 +636,20 @@ rnHsTyKi env (HsDocTy _ ty haddock_doc) = do { (ty', fvs) <- rnLHsTyKi env ty ; return (HsDocTy noExtField ty' haddock_doc, fvs) } -rnHsTyKi _ (XHsType (NHsCoreTy ty)) - = return (XHsType (NHsCoreTy ty), emptyFVs) - -- The emptyFVs probably isn't quite right - -- but I don't think it matters +-- See Note [Renaming HsCoreTys] +rnHsTyKi env (XHsType (HsCoreTy ty)) + = do mapM_ (check_in_scope . nameRdrName) fvs_list + return (XHsType (HsCoreTy ty), fvs) + where + fvs_list = map getName $ tyCoVarsOfTypeList ty + fvs = mkFVs fvs_list + + check_in_scope :: RdrName -> RnM () + check_in_scope rdr_name = do + mb_name <- lookupLocalOccRn_maybe rdr_name + when (isNothing mb_name) $ + addErr $ withHsDocContext (rtke_ctxt env) $ + notInScopeErr rdr_name rnHsTyKi env ty@(HsExplicitListTy _ ip tys) = do { data_kinds <- xoptM LangExt.DataKinds @@ -661,6 +673,39 @@ rnHsArrow _env (HsLinearArrow u) = return (HsLinearArrow u, emptyFVs) rnHsArrow env (HsExplicitMult u p) = (\(mult, fvs) -> (HsExplicitMult u mult, fvs)) <$> rnLHsTyKi env p +{- +Note [Renaming HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to rename an HsCoreTy, +since it's already been renamed to some extent. However, in an attempt to +detect ill-formed HsCoreTys, the renamer checks to see if all free type +variables in an HsCoreTy are in scope. To see why this can matter, consider +this example from #18914: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +Because of #18914, a previous GHC would generate the following code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) -- The type within @(...) is an HsCoreTy + @(N f a) -- So is this + (m @f) + +There are two HsCoreTys in play—(f a) and (N f a)—both of which have +`f` and `a` as free type variables. The `f` is in scope from the instance head, +but `a` is completely unbound, which is what led to #18914. To avoid this sort +of mistake going forward, the renamer will now detect that `a` is unbound and +throw an error accordingly. +-} + -------------- rnTyVar :: RnTyKiEnv -> RdrName -> RnM Name rnTyVar env rdr_name ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1819,6 +1819,94 @@ a truly higher-rank type like so: Then the same situation will arise again. But at least it won't arise for the common case of methods with ordinary, prenex-quantified types. +----- +-- Wrinkle: Use HsOuterExplicit +----- + +One minor complication with the plan above is that we need to ensure that the +type variables from a method's instance signature properly scope over the body +of the method. For example, recall: + + instance (C m, forall p q. Coercible p q => Coercible (m p) (m q)) => + C (T m) where + join :: forall a. T m (T m a) -> T m a + join = coerce @( m (m a) -> m a) + @(T m (T m a) -> T m a) + join + +In the example above, it is imperative that the `a` in the instance signature +for `join` scope over the body of `join` by way of ScopedTypeVariables. +This might sound obvious, but note that in gen_Newtype_binds, which is +responsible for generating the code above, the type in `join`'s instance +signature is given as a Core type, whereas gen_Newtype_binds will eventually +produce HsBinds (i.e., source Haskell) that is renamed and typechecked. We +must ensure that `a` is in scope over the body of `join` during renaming +or else the generated code will be rejected. + +In short, we need to convert the instance signature from a Core type to an +HsType (i.e., a source Haskell type). Two possible options are: + +1. Convert the Core type entirely to an HsType (i.e., a source Haskell type). +2. Embed the entire Core type using HsCoreTy. + +Neither option is quite satisfactory: + +1. Converting a Core type to an HsType in full generality is surprisingly + complicated. Previous versions of GHCs did this, but it was the source of + numerous bugs (see #14579 and #16518, for instance). +2. While HsCoreTy is much less complicated that option (1), it's not quite + what we want. In order for `a` to be in scope over the body of `join` during + renaming, the `forall` must be contained in an HsOuterExplicit. + (See Note [Lexically scoped type variables] in GHC.Hs.Type.) HsCoreTy + bypasses HsOuterExplicit, so this won't work either. + +As a compromise, we adopt a combination of the two options above: + +* Split apart the top-level ForAllTys in the instance signature's Core type, +* Convert the top-level ForAllTys to an HsOuterExplicit, and +* Embed the remainder of the Core type in an HsCoreTy. + +This retains most of the simplicity of option (2) while still ensuring that +the type variables are correctly scoped. + +Note that splitting apart top-level ForAllTys will expand any type synonyms +in the Core type itself. This ends up being important to fix a corner case +observed in #18914. Consider this example: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +What code should `deriving C` generate? It will have roughly the following +shape: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(...) (...) (m @f) + +At a minimum, we must instantiate `coerce` with `@(T f)` and `@(T (N f))`, but +with the `forall`s removed in order to make them monotypes. However, the +`forall` is hidden underneath the `T` type synonym, so we must first expand `T` +before we can strip of the `forall`. Expanding `T`, we get +`coerce @(forall a. f a) @(forall a. N f a)`, and after omitting the `forall`s, +we get `coerce @(f a) @(N f a)`. + +We can't stop there, however, or else we would end up with this code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) @(N f a) (m @f) + +Notice that the type variable `a` is completely unbound. In order to make sure +that `a` is in scope, we must /also/ expand the `T` in `m :: T (N f)` to get +`m :: forall a. N f a`. Fortunately, we will do just that in the plan outlined +above, since when we split off the top-level ForAllTys in the instance +signature, we must first expand the T type synonym. + Note [GND and ambiguity] ~~~~~~~~~~~~~~~~~~~~~~~~ We make an effort to make the code generated through GND be robust w.r.t. @@ -1891,13 +1979,30 @@ gen_Newtype_binds loc cls inst_tvs inst_tys rhs_ty , -- The derived instance signature, e.g., -- -- op :: forall c. a -> [T x] -> c -> Int + -- + -- Make sure that `forall c` is in an HsOuterExplicit so that it + -- scopes over the body of `op`. See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. L loc $ ClassOpSig noExtField False [loc_meth_RDR] - $ L loc $ mkHsImplicitSigType $ nlHsCoreTy to_ty + $ L loc $ mkHsExplicitSigType + (map mk_hs_tvb to_tvbs) + (nlHsCoreTy to_rho) ) where Pair from_ty to_ty = mkCoerceClassMethEqn cls inst_tvs inst_tys rhs_ty meth_id - (_, _, from_tau) = tcSplitSigmaTy from_ty - (_, _, to_tau) = tcSplitSigmaTy to_ty + (_, _, from_tau) = tcSplitSigmaTy from_ty + (to_tvbs, to_rho) = tcSplitForAllTysInvis to_ty + (_, to_tau) = tcSplitPhiTy to_rho + -- The use of tcSplitForAllTysInvis above expands type synonyms, which + -- is important to ensure correct type variable scoping. + -- See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. + + mk_hs_tvb :: VarBndr TyVar flag -> LHsTyVarBndr flag GhcPs + mk_hs_tvb (Bndr tv flag) = noLoc $ KindedTyVar noExtField + flag + (noLoc (getRdrName tv)) + (nlHsCoreTy (tyVarKind tv)) meth_RDR = getRdrName meth_id loc_meth_RDR = L loc meth_RDR @@ -1951,7 +2056,7 @@ nlHsAppType e s = noLoc (HsAppType noExtField e hs_ty) hs_ty = mkHsWildCardBndrs $ parenthesizeHsType appPrec $ nlHsCoreTy s nlHsCoreTy :: Type -> LHsType GhcPs -nlHsCoreTy = noLoc . XHsType . NHsCoreTy +nlHsCoreTy = noLoc . XHsType . HsCoreTy mkCoerceClassMethEqn :: Class -- the class being derived -> [TyVar] -- the tvs in the instance head (this includes @@ -2079,15 +2184,15 @@ genAuxBindSpecDup loc original_rdr_name dup_spec genAuxBindSpecSig :: SrcSpan -> AuxBindSpec -> LHsSigWcType GhcPs genAuxBindSpecSig loc spec = case spec of DerivCon2Tag tycon _ - -> mk_sig $ L loc $ XHsType $ NHsCoreTy $ + -> mk_sig $ L loc $ XHsType $ HsCoreTy $ mkSpecSigmaTy (tyConTyVars tycon) (tyConStupidTheta tycon) $ mkParentType tycon `mkVisFunTyMany` intPrimTy DerivTag2Con tycon _ -> mk_sig $ L loc $ - XHsType $ NHsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $ + XHsType $ HsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $ intTy `mkVisFunTyMany` mkParentType tycon DerivMaxTag _ _ - -> mk_sig (L loc (XHsType (NHsCoreTy intTy))) + -> mk_sig (L loc (XHsType (HsCoreTy intTy))) DerivDataDataType _ _ _ -> mk_sig (nlHsTyVar dataType_RDR) DerivDataConstr _ _ _ ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -942,8 +942,8 @@ tc_infer_hs_type mode (HsSpliceTy _ (HsSpliced _ _ (HsSplicedTy ty))) tc_infer_hs_type mode (HsDocTy _ ty _) = tc_infer_lhs_type mode ty --- See Note [Typechecking NHsCoreTys] -tc_infer_hs_type _ (XHsType (NHsCoreTy ty)) +-- See Note [Typechecking HsCoreTys] +tc_infer_hs_type _ (XHsType (HsCoreTy ty)) = do env <- getLclEnv -- Raw uniques since we go from NameEnv to TvSubstEnv. let subst_prs :: [(Unique, TcTyVar)] @@ -967,21 +967,21 @@ tc_infer_hs_type mode other_ty ; return (ty', kv) } {- -Note [Typechecking NHsCoreTys] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -NHsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. -As such, there's not much to be done in order to typecheck an NHsCoreTy, +Note [Typechecking HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to typecheck an HsCoreTy, since it's already been typechecked to some extent. There is one thing that we must do, however: we must substitute the type variables from the tcl_env. To see why, consider GeneralizedNewtypeDeriving, which is one of the main -clients of NHsCoreTy (example adapted from #14579): +clients of HsCoreTy (example adapted from #14579): newtype T a = MkT a deriving newtype Eq This will produce an InstInfo GhcPs that looks roughly like this: instance forall a_1. Eq a_1 => Eq (T a_1) where - (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an NHsCoreTy + (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an HsCoreTy @(T a_1 -> T a_1 -> Bool) -- So is this (==) @@ -997,9 +997,9 @@ environment (tcl_env) with [a_1 :-> a_2]. This gives us: To ensure that the body of this instance is well scoped, every occurrence of the `a` type variable should refer to a_2, the new skolem. However, the -NHsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the +HsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the substitution we need ([a_1 :-> a_2]) to fix up the scoping. We apply this -substitution to each NHsCoreTy and all is well: +substitution to each HsCoreTy and all is well: instance forall a_2. Eq a_2 => Eq (T a_2) where (==) = coerce @( a_2 -> a_2 -> Bool) @@ -1196,7 +1196,7 @@ tc_hs_type mode ty@(HsAppTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsAppKindTy{}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsOpTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsKindSig {}) ek = tc_infer_hs_type_ek mode ty ek -tc_hs_type mode ty@(XHsType (NHsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek +tc_hs_type mode ty@(XHsType (HsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsWildCardTy _) ek = tcAnonWildCardOcc mode ty ek {- ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -291,7 +291,7 @@ no_anon_wc_ty lty = go lty HsTyLit{} -> True HsTyVar{} -> True HsStarTy{} -> True - XHsType (NHsCoreTy{}) -> True -- Core type, which does not have any wildcard + XHsType (HsCoreTy{}) -> True -- Core type, which does not have any wildcard gos = all go ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -2002,7 +2002,7 @@ mkDefMethBind dfun_id clas sel_id dm_name mk_vta :: LHsExpr GhcRn -> Type -> LHsExpr GhcRn mk_vta fun ty = noLoc (HsAppType noExtField fun (mkEmptyWildCardBndrs $ nlHsParTy - $ noLoc $ XHsType $ NHsCoreTy ty)) + $ noLoc $ XHsType $ HsCoreTy ty)) -- NB: use visible type application -- See Note [Default methods in instances] ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -9,9 +9,8 @@ Derived class instances: GHC.Base.sconcat :: GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a GHC.Base.stimes :: - forall b. - GHC.Real.Integral b => - b -> T14578.Wat f g a -> T14578.Wat f g a + forall (b :: *). + GHC.Real.Integral b => b -> T14578.Wat f g a -> T14578.Wat f g a (GHC.Base.<>) = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a @@ -39,8 +38,10 @@ Derived class instances: instance GHC.Base.Functor f => GHC.Base.Functor (T14578.App f) where GHC.Base.fmap :: - forall a b. (a -> b) -> T14578.App f a -> T14578.App f b - (GHC.Base.<$) :: forall a b. a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + (a -> b) -> T14578.App f a -> T14578.App f b + (GHC.Base.<$) :: + forall (a :: *) (b :: *). a -> T14578.App f b -> T14578.App f a GHC.Base.fmap = GHC.Prim.coerce @((a -> b) -> f a -> f b) @@ -52,17 +53,19 @@ Derived class instances: instance GHC.Base.Applicative f => GHC.Base.Applicative (T14578.App f) where - GHC.Base.pure :: forall a. a -> T14578.App f a + GHC.Base.pure :: forall (a :: *). a -> T14578.App f a (GHC.Base.<*>) :: - forall a b. + forall (a :: *) (b :: *). T14578.App f (a -> b) -> T14578.App f a -> T14578.App f b GHC.Base.liftA2 :: - forall a b c. + forall (a :: *) (b :: *) (c :: *). (a -> b -> c) -> T14578.App f a -> T14578.App f b -> T14578.App f c (GHC.Base.*>) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f b + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f b (GHC.Base.<*) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f a GHC.Base.pure = GHC.Prim.coerce @(a -> f a) @(a -> T14578.App f a) (GHC.Base.pure @f) ===================================== testsuite/tests/deriving/should_compile/T18914.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE RankNTypes #-} +module T18914 where + +type T f = forall a. f a + +class C f where + m1 :: T f + m2 :: forall a. f a + +newtype N f a = MkN (f a) + deriving C ===================================== testsuite/tests/deriving/should_compile/all.T ===================================== @@ -127,3 +127,4 @@ test('T17339', normal, compile, test('T17880', normal, compile, ['']) test('T18055', normal, compile, ['']) test('T18321', normal, compile, ['']) +test('T18914', normal, compile, ['']) ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit ad9cbad7312a64e6757c32bd9488c55ba4f2fec9 +Subproject commit 6534129304fd113324acc4a0b6c6f0a7c04e0c59 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1553ed815fae079b7464b8ba7516f9889b661ad7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1553ed815fae079b7464b8ba7516f9889b661ad7 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 Sat Nov 7 13:42:01 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sat, 07 Nov 2020 08:42:01 -0500 Subject: [Git][ghc/ghc][wip/T18914] Use HsOuterExplicit in instance sigs in deriving-generated code Message-ID: <5fa6a429965b9_10ee3ffbaf4a6394594830@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: c5da55a2 by Ryan Scott at 2020-11-07T08:41:40-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - 10 changed files: - compiler/GHC/Hs/Type.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/deriving/should_compile/T14578.stderr - + testsuite/tests/deriving/should_compile/T18914.hs - testsuite/tests/deriving/should_compile/all.T - utils/haddock Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -24,7 +24,7 @@ module GHC.Hs.Type ( HsArrow(..), arrowToHsType, hsLinear, hsUnrestricted, isUnrestricted, - HsType(..), NewHsTypeX(..), LHsType, HsKind, LHsKind, + HsType(..), HsCoreTy(..), LHsType, HsKind, LHsKind, HsForAllTelescope(..), HsTyVarBndr(..), LHsTyVarBndr, LHsQTyVars(..), HsOuterTyVarBndrs(..), HsOuterFamEqnTyVarBndrs, HsOuterSigTyVarBndrs, @@ -1077,16 +1077,19 @@ data HsType pass | XHsType (XXType pass) -data NewHsTypeX - = NHsCoreTy Type -- An escape hatch for tunnelling a *closed* - -- Core Type through HsSyn. - -- See also Note [Typechecking NHsCoreTys] in - -- GHC.Tc.Gen.HsType. - deriving Data +-- An escape hatch for tunnelling a Core 'Type' through 'HsType'. +-- For more details on how this works, see: +-- +-- * @Note [Renaming HsCoreTys]@ in "GHC.Rename.HsType" +-- +-- * @Note [Typechecking HsCoreTys]@ in "GHC.Tc.Gen.HsType" +newtype HsCoreTy + = HsCoreTy Type -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None + deriving Data -instance Outputable NewHsTypeX where - ppr (NHsCoreTy ty) = ppr ty +instance Outputable HsCoreTy where + ppr (HsCoreTy ty) = ppr ty type instance XForAllTy (GhcPass _) = NoExtField type instance XQualTy (GhcPass _) = NoExtField @@ -1124,7 +1127,7 @@ type instance XTyLit (GhcPass _) = NoExtField type instance XWildCardTy (GhcPass _) = NoExtField -type instance XXType (GhcPass _) = NewHsTypeX +type instance XXType (GhcPass _) = HsCoreTy -- Note [Literal source text] in GHC.Types.Basic for SourceText fields in @@ -2250,7 +2253,7 @@ hsTypeNeedsParens p = go_hs_ty go_hs_ty (HsOpTy{}) = p >= opPrec go_hs_ty (HsParTy{}) = False go_hs_ty (HsDocTy _ (L _ t) _) = go_hs_ty t - go_hs_ty (XHsType (NHsCoreTy ty)) = go_core_ty ty + go_hs_ty (XHsType (HsCoreTy ty)) = go_core_ty ty go_core_ty (TyVarTy{}) = False go_core_ty (AppTy{}) = p >= appPrec ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -39,6 +39,7 @@ import GHC.Prelude import {-# SOURCE #-} GHC.Rename.Splice( rnSpliceType ) +import GHC.Core.TyCo.FVs ( tyCoVarsOfTypeList ) import GHC.Driver.Session import GHC.Hs import GHC.Rename.Env @@ -48,6 +49,7 @@ import GHC.Rename.Utils ( HsDocContext(..), inHsDocContext, withHsDocContext , checkShadowedRdrNames ) import GHC.Rename.Fixity ( lookupFieldFixityRn, lookupFixityRn , lookupTyFixityRn ) +import GHC.Rename.Unbound ( notInScopeErr ) import GHC.Tc.Utils.Monad import GHC.Types.Name.Reader import GHC.Builtin.Names @@ -634,10 +636,20 @@ rnHsTyKi env (HsDocTy _ ty haddock_doc) = do { (ty', fvs) <- rnLHsTyKi env ty ; return (HsDocTy noExtField ty' haddock_doc, fvs) } -rnHsTyKi _ (XHsType (NHsCoreTy ty)) - = return (XHsType (NHsCoreTy ty), emptyFVs) - -- The emptyFVs probably isn't quite right - -- but I don't think it matters +-- See Note [Renaming HsCoreTys] +rnHsTyKi env (XHsType (HsCoreTy ty)) + = do mapM_ (check_in_scope . nameRdrName) fvs_list + return (XHsType (HsCoreTy ty), fvs) + where + fvs_list = map getName $ tyCoVarsOfTypeList ty + fvs = mkFVs fvs_list + + check_in_scope :: RdrName -> RnM () + check_in_scope rdr_name = do + mb_name <- lookupLocalOccRn_maybe rdr_name + when (isNothing mb_name) $ + addErr $ withHsDocContext (rtke_ctxt env) $ + notInScopeErr rdr_name rnHsTyKi env ty@(HsExplicitListTy _ ip tys) = do { data_kinds <- xoptM LangExt.DataKinds @@ -661,6 +673,39 @@ rnHsArrow _env (HsLinearArrow u) = return (HsLinearArrow u, emptyFVs) rnHsArrow env (HsExplicitMult u p) = (\(mult, fvs) -> (HsExplicitMult u mult, fvs)) <$> rnLHsTyKi env p +{- +Note [Renaming HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to rename an HsCoreTy, +since it's already been renamed to some extent. However, in an attempt to +detect ill-formed HsCoreTys, the renamer checks to see if all free type +variables in an HsCoreTy are in scope. To see why this can matter, consider +this example from #18914: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +Because of #18914, a previous GHC would generate the following code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) -- The type within @(...) is an HsCoreTy + @(N f a) -- So is this + (m @f) + +There are two HsCoreTys in play—(f a) and (N f a)—both of which have +`f` and `a` as free type variables. The `f` is in scope from the instance head, +but `a` is completely unbound, which is what led to #18914. To avoid this sort +of mistake going forward, the renamer will now detect that `a` is unbound and +throw an error accordingly. +-} + -------------- rnTyVar :: RnTyKiEnv -> RdrName -> RnM Name rnTyVar env rdr_name ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1819,6 +1819,94 @@ a truly higher-rank type like so: Then the same situation will arise again. But at least it won't arise for the common case of methods with ordinary, prenex-quantified types. +----- +-- Wrinkle: Use HsOuterExplicit +----- + +One minor complication with the plan above is that we need to ensure that the +type variables from a method's instance signature properly scope over the body +of the method. For example, recall: + + instance (C m, forall p q. Coercible p q => Coercible (m p) (m q)) => + C (T m) where + join :: forall a. T m (T m a) -> T m a + join = coerce @( m (m a) -> m a) + @(T m (T m a) -> T m a) + join + +In the example above, it is imperative that the `a` in the instance signature +for `join` scope over the body of `join` by way of ScopedTypeVariables. +This might sound obvious, but note that in gen_Newtype_binds, which is +responsible for generating the code above, the type in `join`'s instance +signature is given as a Core type, whereas gen_Newtype_binds will eventually +produce HsBinds (i.e., source Haskell) that is renamed and typechecked. We +must ensure that `a` is in scope over the body of `join` during renaming +or else the generated code will be rejected. + +In short, we need to convert the instance signature from a Core type to an +HsType (i.e., a source Haskell type). Two possible options are: + +1. Convert the Core type entirely to an HsType (i.e., a source Haskell type). +2. Embed the entire Core type using HsCoreTy. + +Neither option is quite satisfactory: + +1. Converting a Core type to an HsType in full generality is surprisingly + complicated. Previous versions of GHCs did this, but it was the source of + numerous bugs (see #14579 and #16518, for instance). +2. While HsCoreTy is much less complicated that option (1), it's not quite + what we want. In order for `a` to be in scope over the body of `join` during + renaming, the `forall` must be contained in an HsOuterExplicit. + (See Note [Lexically scoped type variables] in GHC.Hs.Type.) HsCoreTy + bypasses HsOuterExplicit, so this won't work either. + +As a compromise, we adopt a combination of the two options above: + +* Split apart the top-level ForAllTys in the instance signature's Core type, +* Convert the top-level ForAllTys to an HsOuterExplicit, and +* Embed the remainder of the Core type in an HsCoreTy. + +This retains most of the simplicity of option (2) while still ensuring that +the type variables are correctly scoped. + +Note that splitting apart top-level ForAllTys will expand any type synonyms +in the Core type itself. This ends up being important to fix a corner case +observed in #18914. Consider this example: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +What code should `deriving C` generate? It will have roughly the following +shape: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(...) (...) (m @f) + +At a minimum, we must instantiate `coerce` with `@(T f)` and `@(T (N f))`, but +with the `forall`s removed in order to make them monotypes. However, the +`forall` is hidden underneath the `T` type synonym, so we must first expand `T` +before we can strip of the `forall`. Expanding `T`, we get +`coerce @(forall a. f a) @(forall a. N f a)`, and after omitting the `forall`s, +we get `coerce @(f a) @(N f a)`. + +We can't stop there, however, or else we would end up with this code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) @(N f a) (m @f) + +Notice that the type variable `a` is completely unbound. In order to make sure +that `a` is in scope, we must /also/ expand the `T` in `m :: T (N f)` to get +`m :: forall a. N f a`. Fortunately, we will do just that in the plan outlined +above, since when we split off the top-level ForAllTys in the instance +signature, we must first expand the T type synonym. + Note [GND and ambiguity] ~~~~~~~~~~~~~~~~~~~~~~~~ We make an effort to make the code generated through GND be robust w.r.t. @@ -1891,13 +1979,30 @@ gen_Newtype_binds loc cls inst_tvs inst_tys rhs_ty , -- The derived instance signature, e.g., -- -- op :: forall c. a -> [T x] -> c -> Int + -- + -- Make sure that `forall c` is in an HsOuterExplicit so that it + -- scopes over the body of `op`. See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. L loc $ ClassOpSig noExtField False [loc_meth_RDR] - $ L loc $ mkHsImplicitSigType $ nlHsCoreTy to_ty + $ L loc $ mkHsExplicitSigType + (map mk_hs_tvb to_tvbs) + (nlHsCoreTy to_rho) ) where Pair from_ty to_ty = mkCoerceClassMethEqn cls inst_tvs inst_tys rhs_ty meth_id - (_, _, from_tau) = tcSplitSigmaTy from_ty - (_, _, to_tau) = tcSplitSigmaTy to_ty + (_, _, from_tau) = tcSplitSigmaTy from_ty + (to_tvbs, to_rho) = tcSplitForAllTysInvis to_ty + (_, to_tau) = tcSplitPhiTy to_rho + -- The use of tcSplitForAllTysInvis above expands type synonyms, which + -- is important to ensure correct type variable scoping. + -- See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. + + mk_hs_tvb :: VarBndr TyVar flag -> LHsTyVarBndr flag GhcPs + mk_hs_tvb (Bndr tv flag) = noLoc $ KindedTyVar noExtField + flag + (noLoc (getRdrName tv)) + (nlHsCoreTy (tyVarKind tv)) meth_RDR = getRdrName meth_id loc_meth_RDR = L loc meth_RDR @@ -1951,7 +2056,7 @@ nlHsAppType e s = noLoc (HsAppType noExtField e hs_ty) hs_ty = mkHsWildCardBndrs $ parenthesizeHsType appPrec $ nlHsCoreTy s nlHsCoreTy :: Type -> LHsType GhcPs -nlHsCoreTy = noLoc . XHsType . NHsCoreTy +nlHsCoreTy = noLoc . XHsType . HsCoreTy mkCoerceClassMethEqn :: Class -- the class being derived -> [TyVar] -- the tvs in the instance head (this includes @@ -2079,15 +2184,15 @@ genAuxBindSpecDup loc original_rdr_name dup_spec genAuxBindSpecSig :: SrcSpan -> AuxBindSpec -> LHsSigWcType GhcPs genAuxBindSpecSig loc spec = case spec of DerivCon2Tag tycon _ - -> mk_sig $ L loc $ XHsType $ NHsCoreTy $ + -> mk_sig $ L loc $ XHsType $ HsCoreTy $ mkSpecSigmaTy (tyConTyVars tycon) (tyConStupidTheta tycon) $ mkParentType tycon `mkVisFunTyMany` intPrimTy DerivTag2Con tycon _ -> mk_sig $ L loc $ - XHsType $ NHsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $ + XHsType $ HsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $ intTy `mkVisFunTyMany` mkParentType tycon DerivMaxTag _ _ - -> mk_sig (L loc (XHsType (NHsCoreTy intTy))) + -> mk_sig (L loc (XHsType (HsCoreTy intTy))) DerivDataDataType _ _ _ -> mk_sig (nlHsTyVar dataType_RDR) DerivDataConstr _ _ _ ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -942,8 +942,8 @@ tc_infer_hs_type mode (HsSpliceTy _ (HsSpliced _ _ (HsSplicedTy ty))) tc_infer_hs_type mode (HsDocTy _ ty _) = tc_infer_lhs_type mode ty --- See Note [Typechecking NHsCoreTys] -tc_infer_hs_type _ (XHsType (NHsCoreTy ty)) +-- See Note [Typechecking HsCoreTys] +tc_infer_hs_type _ (XHsType (HsCoreTy ty)) = do env <- getLclEnv -- Raw uniques since we go from NameEnv to TvSubstEnv. let subst_prs :: [(Unique, TcTyVar)] @@ -967,21 +967,21 @@ tc_infer_hs_type mode other_ty ; return (ty', kv) } {- -Note [Typechecking NHsCoreTys] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -NHsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. -As such, there's not much to be done in order to typecheck an NHsCoreTy, +Note [Typechecking HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to typecheck an HsCoreTy, since it's already been typechecked to some extent. There is one thing that we must do, however: we must substitute the type variables from the tcl_env. To see why, consider GeneralizedNewtypeDeriving, which is one of the main -clients of NHsCoreTy (example adapted from #14579): +clients of HsCoreTy (example adapted from #14579): newtype T a = MkT a deriving newtype Eq This will produce an InstInfo GhcPs that looks roughly like this: instance forall a_1. Eq a_1 => Eq (T a_1) where - (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an NHsCoreTy + (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an HsCoreTy @(T a_1 -> T a_1 -> Bool) -- So is this (==) @@ -997,9 +997,9 @@ environment (tcl_env) with [a_1 :-> a_2]. This gives us: To ensure that the body of this instance is well scoped, every occurrence of the `a` type variable should refer to a_2, the new skolem. However, the -NHsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the +HsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the substitution we need ([a_1 :-> a_2]) to fix up the scoping. We apply this -substitution to each NHsCoreTy and all is well: +substitution to each HsCoreTy and all is well: instance forall a_2. Eq a_2 => Eq (T a_2) where (==) = coerce @( a_2 -> a_2 -> Bool) @@ -1196,7 +1196,7 @@ tc_hs_type mode ty@(HsAppTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsAppKindTy{}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsOpTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsKindSig {}) ek = tc_infer_hs_type_ek mode ty ek -tc_hs_type mode ty@(XHsType (NHsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek +tc_hs_type mode ty@(XHsType (HsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsWildCardTy _) ek = tcAnonWildCardOcc mode ty ek {- ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -291,7 +291,7 @@ no_anon_wc_ty lty = go lty HsTyLit{} -> True HsTyVar{} -> True HsStarTy{} -> True - XHsType (NHsCoreTy{}) -> True -- Core type, which does not have any wildcard + XHsType (HsCoreTy{}) -> True -- Core type, which does not have any wildcard gos = all go ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -2002,7 +2002,7 @@ mkDefMethBind dfun_id clas sel_id dm_name mk_vta :: LHsExpr GhcRn -> Type -> LHsExpr GhcRn mk_vta fun ty = noLoc (HsAppType noExtField fun (mkEmptyWildCardBndrs $ nlHsParTy - $ noLoc $ XHsType $ NHsCoreTy ty)) + $ noLoc $ XHsType $ HsCoreTy ty)) -- NB: use visible type application -- See Note [Default methods in instances] ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -9,9 +9,8 @@ Derived class instances: GHC.Base.sconcat :: GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a GHC.Base.stimes :: - forall b. - GHC.Real.Integral b => - b -> T14578.Wat f g a -> T14578.Wat f g a + forall (b :: *). + GHC.Real.Integral b => b -> T14578.Wat f g a -> T14578.Wat f g a (GHC.Base.<>) = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a @@ -39,8 +38,10 @@ Derived class instances: instance GHC.Base.Functor f => GHC.Base.Functor (T14578.App f) where GHC.Base.fmap :: - forall a b. (a -> b) -> T14578.App f a -> T14578.App f b - (GHC.Base.<$) :: forall a b. a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + (a -> b) -> T14578.App f a -> T14578.App f b + (GHC.Base.<$) :: + forall (a :: *) (b :: *). a -> T14578.App f b -> T14578.App f a GHC.Base.fmap = GHC.Prim.coerce @((a -> b) -> f a -> f b) @@ -52,17 +53,19 @@ Derived class instances: instance GHC.Base.Applicative f => GHC.Base.Applicative (T14578.App f) where - GHC.Base.pure :: forall a. a -> T14578.App f a + GHC.Base.pure :: forall (a :: *). a -> T14578.App f a (GHC.Base.<*>) :: - forall a b. + forall (a :: *) (b :: *). T14578.App f (a -> b) -> T14578.App f a -> T14578.App f b GHC.Base.liftA2 :: - forall a b c. + forall (a :: *) (b :: *) (c :: *). (a -> b -> c) -> T14578.App f a -> T14578.App f b -> T14578.App f c (GHC.Base.*>) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f b + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f b (GHC.Base.<*) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f a GHC.Base.pure = GHC.Prim.coerce @(a -> f a) @(a -> T14578.App f a) (GHC.Base.pure @f) ===================================== testsuite/tests/deriving/should_compile/T18914.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE RankNTypes #-} +module T18914 where + +type T f = forall a. f a + +class C f where + m1 :: T f + m2 :: forall a. f a + +newtype N f a = MkN (f a) + deriving C ===================================== testsuite/tests/deriving/should_compile/all.T ===================================== @@ -127,3 +127,4 @@ test('T17339', normal, compile, test('T17880', normal, compile, ['']) test('T18055', normal, compile, ['']) test('T18321', normal, compile, ['']) +test('T18914', normal, compile, ['']) ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit ad9cbad7312a64e6757c32bd9488c55ba4f2fec9 +Subproject commit 6534129304fd113324acc4a0b6c6f0a7c04e0c59 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5da55a2d057cf2a534d316b620c3670f4a0b771 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c5da55a2d057cf2a534d316b620c3670f4a0b771 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 Sat Nov 7 14:19:11 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sat, 07 Nov 2020 09:19:11 -0500 Subject: [Git][ghc/ghc][wip/T18389] 34 commits: Make typechecker equality consider visibility in ForAllTys Message-ID: <5fa6acdff3bf0_10ee3ffbae006d9459868b@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18389 at Glasgow Haskell Compiler / GHC Commits: 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 8da38465 by Simon Peyton Jones at 2020-11-07T09:18:08-05:00 Work in progress on #18359 Joint work between Richard, Simon, Ryan - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCo/Rep.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b9fd0f0f98706e4eda4657c014ed69e5a9afc57e...8da38465bfce4dab706429ea3197f7b70d832320 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b9fd0f0f98706e4eda4657c014ed69e5a9afc57e...8da38465bfce4dab706429ea3197f7b70d832320 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 Sat Nov 7 18:29:15 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Sat, 07 Nov 2020 13:29:15 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 7 commits: test LocalGivenEqs Message-ID: <5fa6e77b4ee21_10ee3ffbca8e462061862b@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: fb9c27ac by Richard Eisenberg at 2020-11-05T15:34:20-05:00 test LocalGivenEqs - - - - - 29a8f7a2 by Richard Eisenberg at 2020-11-05T17:30:38-05:00 Update commentary about HasGivenEqs - - - - - 3557866f by Richard Eisenberg at 2020-11-05T18:24:12-05:00 Update notes. - - - - - a98b07cb by Richard Eisenberg at 2020-11-07T11:30:54-05:00 More documentation around LocalGivenEqs - - - - - dc6d9ef0 by Richard Eisenberg at 2020-11-07T12:33:25-05:00 Rename the flat-cache. Document it, too. - - - - - 058f4acb by Richard Eisenberg at 2020-11-07T13:16:23-05:00 Make EqualCtList into a newtype with NonEmpty - - - - - e2ec2ada by Richard Eisenberg at 2020-11-07T13:28:52-05:00 Remove Note [No FunEq improvement for Givens] - - - - - 15 changed files: - compiler/GHC/Data/Bag.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/Solver/Interact.hs - compiler/GHC/Tc/Solver/Monad.hs - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/exts/type_families.rst - testsuite/tests/indexed-types/should_fail/T13784.stderr - testsuite/tests/patsyn/should_fail/T11010.stderr - + testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs - + testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Data/Bag.hs ===================================== @@ -17,7 +17,7 @@ module GHC.Data.Bag ( filterBag, partitionBag, partitionBagWith, concatBag, catBagMaybes, foldBag, isEmptyBag, isSingletonBag, consBag, snocBag, anyBag, allBag, - listToBag, bagToList, mapAccumBagL, + listToBag, nonEmptyToBag, bagToList, mapAccumBagL, concatMapBag, concatMapBagPair, mapMaybeBag, mapBagM, mapBagM_, flatMapBagM, flatMapBagPairM, @@ -35,6 +35,7 @@ import Control.Monad import Data.Data import Data.Maybe( mapMaybe ) import Data.List ( partition, mapAccumL ) +import Data.List.NonEmpty ( NonEmpty(..) ) import qualified Data.Foldable as Foldable infixr 3 `consBag` @@ -299,6 +300,10 @@ listToBag [] = EmptyBag listToBag [x] = UnitBag x listToBag vs = ListBag vs +nonEmptyToBag :: NonEmpty a -> Bag a +nonEmptyToBag (x :| []) = UnitBag x +nonEmptyToBag (x :| xs) = ListBag (x : xs) + bagToList :: Bag a -> [a] bagToList b = foldr (:) [] b ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -260,7 +260,7 @@ data GeneralFlag | Opt_RPath | Opt_RelativeDynlibPaths | Opt_Hpc - | Opt_FlatCache + | Opt_FamAppCache | Opt_ExternalInterpreter | Opt_OptimalApplicativeDo | Opt_VersionMacros ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3404,7 +3404,7 @@ fFlagsDeps = [ flagSpec "expose-all-unfoldings" Opt_ExposeAllUnfoldings, flagSpec "external-dynamic-refs" Opt_ExternalDynamicRefs, flagSpec "external-interpreter" Opt_ExternalInterpreter, - flagSpec "flat-cache" Opt_FlatCache, + flagSpec "family-application-cache" Opt_FamAppCache, flagSpec "float-in" Opt_FloatIn, flagSpec "force-recomp" Opt_ForceRecomp, flagSpec "ignore-optim-changes" Opt_IgnoreOptimChanges, @@ -3760,7 +3760,7 @@ defaultFlags settings = [ Opt_AutoLinkPackages, Opt_DiagnosticsShowCaret, Opt_EmbedManifest, - Opt_FlatCache, + Opt_FamAppCache, Opt_GenManifest, Opt_GhciHistory, Opt_GhciSandbox, @@ -5100,4 +5100,3 @@ initSDocContext dflags style = SDC -- | Initialize the pretty-printing options using the default user style initDefaultSDocContext :: DynFlags -> SDocContext initDefaultSDocContext dflags = initSDocContext dflags defaultUserStyle - ===================================== compiler/GHC/Tc/Errors.hs ===================================== @@ -1688,7 +1688,10 @@ When reporting that GHC can't solve (a ~ c), there are two givens in scope: redundant), so it's not terribly useful to report it in an error message. To accomplish this, we discard any Implications that do not bind any equalities by filtering the `givens` selected in `misMatchOrCND` (based on -the `ic_given_eqs` field of the Implication). +the `ic_given_eqs` field of the Implication). Note that we discard givens +that have no equalities whatsoever, but we want to keep ones with only *local* +equalities, as these may be helpful to the user in understanding what went +wrong. But this is not enough to avoid all redundant givens! Consider this example, from #15361: ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -1596,7 +1596,7 @@ In this Note, "decomposition" refers to taking the constraint where that notation indicates a list of new constraints, where the new constraints may have different flavours and different roles. -The key property to consider is injectivity. When decomposing a Given the +The key property to consider is injectivity. When decomposing a Given, the decomposition is sound if and only if T is injective in all of its type arguments. When decomposing a Wanted, the decomposition is sound (assuming the correct roles in the produced equality constraints), but it may be a guess -- @@ -1614,13 +1614,13 @@ Pursuing the details requires exploring three axes: * Role: Nominal vs. Representational * TyCon species: datatype vs. newtype vs. data family vs. type family vs. type variable -(So a type variable isn't a TyCon, but it's convenient to put the AppTy case +(A type variable isn't a TyCon, of course, but it's convenient to put the AppTy case in the same table.) Right away, we can say that Derived behaves just as Wanted for the purposes of decomposition. The difference between Derived and Wanted is the handling of evidence. Since decomposition in these cases isn't a matter of soundness but of -guessing, we want the same behavior regardless of evidence. +guessing, we want the same behaviour regardless of evidence. Here is a table (discussion following) detailing where decomposition of (T s1 ... sn) ~r (T t1 .. tn) @@ -1634,7 +1634,7 @@ NOMINAL GIVEN WANTED WHERE Datatype YES YES canTyConApp Newtype YES YES canTyConApp Data family YES YES canTyConApp -Type family NO{1} YES, in injective args{1} canEqFun +Type family NO{1} YES, in injective args{1} canEqCanLHS2 AppTy YES YES can_eq_app REPRESENTATIONAL GIVEN WANTED @@ -1642,11 +1642,9 @@ REPRESENTATIONAL GIVEN WANTED Datatype YES YES canTyConApp Newtype NO{2} MAYBE{2} canTyConApp(can_decompose) Data family NO{3} MAYBE{3} canTyConApp(can_decompose) -Type family NO NO canEqFun +Type family NO NO canEqCanLHS2 AppTy NO{4} NO{4} can_eq_nc' -"RAE" update all this; no more canEqFun - {1}: Type families can be injective in some, but not all, of their arguments, so we want to do partial decomposition. This is quite different than the way other decomposition is done, where the decomposed equalities replace the original @@ -1658,9 +1656,9 @@ decompose an injective-type-family Given. {2}: See Note [Decomposing newtypes at representational role] {3}: Because of the possibility of newtype instances, we must treat -data families like newtypes. See also Note [Decomposing newtypes at -representational role]. See #10534 and test case -typecheck/should_fail/T10534. +data families like newtypes. See also +Note [Decomposing newtypes at representational role]. See #10534 and +test case typecheck/should_fail/T10534. {4}: See Note [Decomposing AppTy at representational role] @@ -2189,7 +2187,8 @@ canEqCanLHS2 ev eq_rel swapped lhs1 ps_xi1 lhs2 ps_xi2 mco | otherwise -- ordinary, non-injective type family = [] - ; mapM_ (unifyDerived (ctEvLoc ev) Nominal) inj_eqns + ; unless (isGiven ev) $ + mapM_ (unifyDerived (ctEvLoc ev) Nominal) inj_eqns ; tclvl <- getTcLevel ; dflags <- getDynFlags ===================================== compiler/GHC/Tc/Solver/Flatten.hs ===================================== @@ -31,6 +31,7 @@ import GHC.Tc.Solver.Monad as TcS import GHC.Utils.Misc import Control.Monad import GHC.Utils.Monad ( zipWith3M ) +import Data.List.NonEmpty ( NonEmpty(..) ) import Control.Arrow ( first ) @@ -273,11 +274,9 @@ flattenType loc ty {- Note [Flattening] ~~~~~~~~~~~~~~~~~~~~ -"RAE": update - flatten ty ==> (xi, co) where - xi has no type functions, unless they appear under ForAlls + xi has no reducible type functions has no skolems that are mapped in the inert set has no filled-in metavariables co :: xi ~ ty @@ -287,8 +286,7 @@ Key invariants: (F1) tcTypeKind(xi) succeeds and returns a fully zonked kind (F2) tcTypeKind(xi) `eqType` zonk(tcTypeKind(ty)) -Note that it is flatten's job to flatten *every type function it sees*. -flatten is only called on *arguments* to type functions, by canEqGiven. +Note that it is flatten's job to try to reduce *every type function it sees*. Flattening also: * zonks, removing any metavariables, and @@ -323,22 +321,12 @@ Recall that in comments we use alpha[flat = ty] to represent a flattening skolem variable alpha which has been generated to stand in for ty. ------ Example of flattening a constraint: ------ - flatten (List (F (G Int))) ==> (xi, cc) - where - xi = List alpha - cc = { G Int ~ beta[flat = G Int], - F beta ~ alpha[flat = F beta] } -Here - * alpha and beta are 'flattening skolem variables'. - * All the constraints in cc are 'given', and all their coercion terms - are the identity. - Note that we prefer to leave type synonyms unexpanded when possible, so when the flattener encounters one, it first asks whether its -transitive expansion contains any type function applications. If so, +transitive expansion contains any type function applications or is +forgetful -- that is, omits one or more type variables in its RHS. If so, it expands the synonym and proceeds; if not, it simply returns the -unexpanded synonym. +unexpanded synonym. See also Note [Flattening synonyms]. Note [flatten_args performance] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -796,8 +784,8 @@ flatten_exact_fam_app_fully tc tys ret_co = mkTyConAppCo role tc cos -- ret_co :: F xis ~ F tys; might be heterogeneous - -- Now, look in the cache - ; mb_ct <- liftTcS $ lookupFlatCache tc xis + -- Now, look in the inerts and the cache + ; mb_ct <- liftTcS $ lookupFamApp tc xis ; dflags <- getDynFlags ; loc <- getLoc ; case mb_ct of @@ -883,7 +871,7 @@ flatten_exact_fam_app_fully tc tys ; flavour <- getFlavour -- NB: only extend cache with nominal, given equalities ; when (eq_rel == NomEq && flavour == Given) $ - liftTcS $ extendFlatCache tc tys (co, xi) + liftTcS $ extendFamAppCache tc tys (co, xi) ; let role = eqRelRole eq_rel xi' = xi `mkCastTy` kind_co co' = update_co $ @@ -1027,8 +1015,8 @@ flatten_tyvar2 :: TcTyVar -> CtFlavourRole -> FlatM FlattenTvResult flatten_tyvar2 tv fr@(_, eq_rel) = do { ieqs <- liftTcS $ getInertEqs ; case lookupDVarEnv ieqs tv of - Just (ct:_) -- If the first doesn't work, - -- the subsequent ones won't either + Just (EqualCtList (ct :| _)) -- If the first doesn't work, + -- the subsequent ones won't either | CEqCan { cc_ev = ctev, cc_lhs = TyVarLHS tv , cc_rhs = rhs_ty, cc_eq_rel = ct_eq_rel } <- ct , let ct_fr = (ctEvFlavour ctev, ct_eq_rel) ===================================== compiler/GHC/Tc/Solver/Interact.hs ===================================== @@ -57,6 +57,7 @@ import GHC.Types.Unique( hasKey ) import GHC.Driver.Session import GHC.Utils.Misc import qualified GHC.LanguageExtensions as LangExt +import Data.List.NonEmpty ( NonEmpty(..) ) import Control.Monad.Trans.Class import Control.Monad.Trans.Maybe @@ -1247,11 +1248,9 @@ improveLocalFunEqs :: CtEvidence -> InertCans -> TyCon -> [TcType] -> TcType -- E.g. x + y ~ z, x + y' ~ z => [D] y ~ y' -- -- See Note [FunDep and implicit parameter reactions] --- No Givens here: Note [No FunEq improvement for Givens] -- Precondition: isImprovable work_ev improveLocalFunEqs work_ev inerts fam_tc args rhs - = ASSERT( not (isGiven work_ev) ) - ASSERT( isImprovable work_ev ) + = ASSERT( isImprovable work_ev ) unless (null improvement_eqns) $ do { traceTcS "interactFunEq improvements: " $ vcat [ text "Eqns:" <+> ppr improvement_eqns @@ -1260,7 +1259,8 @@ improveLocalFunEqs work_ev inerts fam_tc args rhs ; emitFunDepDeriveds improvement_eqns } where funeqs = inert_funeqs inerts - funeqs_for_tc = [ funeq_ct | funeq_ct : _ <- findFunEqsByTyCon funeqs fam_tc + funeqs_for_tc = [ funeq_ct | EqualCtList (funeq_ct :| _) + <- findFunEqsByTyCon funeqs fam_tc , NomEq == ctEqRel funeq_ct ] -- representational equalities don't interact -- with type family dependencies @@ -1315,16 +1315,12 @@ improveLocalFunEqs work_ev inerts fam_tc args rhs ctl_depth work_loc } {- Note [Type inference for type families with injectivity] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": Update this Note. - +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have a type family with an injectivity annotation: type family F a b = r | r -> b -Then if we have two CFunEqCan constraints for F with the same RHS - F s1 t1 ~ rhs - F s2 t2 ~ rhs -then we can use the injectivity to get a new Derived constraint on +Then if we have an equality like F s1 t1 ~ F s2 t2, +we can use the injectivity to get a new Derived constraint on the injective argument [D] t1 ~ t2 @@ -1351,8 +1347,20 @@ We could go further and offer evidence from decomposing injective type-function applications, but that would require new evidence forms, and an extension to FC, so we don't do that right now (Dec 14). -See also Note [Injective type families] in GHC.Core.TyCon +We generate these Deriveds in three places, depending on how we notice the +injectivity. + +1. When we have a [W/D] F tys1 ~ F tys2. This is handled in canEqCanLHS2, and +described in Note [Decomposing equality] in GHC.Tc.Solver.Canonical. + +2. When we have [W] F tys1 ~ T and [W] F tys2 ~ T. Note that neither of these +constraints rewrites the other, as they have different LHSs. This is done +in improveLocalFunEqs, called during the interactWithInertsStage. + +3. When we have [W] F tys ~ T and an equation for F that looks like F tys' = T. +This is done in improve_top_fun_eqs, called from the top-level reactions stage. +See also Note [Injective type families] in GHC.Core.TyCon Note [Cache-caused loops] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1454,22 +1462,19 @@ interactEq tclvl inerts workItem@(CEqCan { cc_lhs = lhs = do { traceTcS "Not unifying representational equality" (ppr workItem) ; continueWith workItem } - | isGiven ev -- See Note [Touchables and givens] - -- See Note [No FunEq improvement for Givens] - = continueWith workItem + -- try improvement, if possible + | TyFamLHS fam_tc fam_args <- lhs + , isImprovable ev + = do { improveLocalFunEqs ev inerts fam_tc fam_args rhs + ; continueWith workItem } | TyVarLHS tv <- lhs + , not (isGiven ev) -- See Note [Touchables and givens] , canSolveByUnification tclvl tv rhs = do { solveByUnification ev tv rhs ; n_kicked <- kickOutAfterUnification tv ; return (Stop ev (text "Solved by unification" <+> pprKicked n_kicked)) } - -- try improvement, if possible - | TyFamLHS fam_tc fam_args <- lhs - , isImprovable ev - = do { improveLocalFunEqs ev inerts fam_tc fam_args rhs - ; continueWith workItem } - | otherwise = continueWith workItem @@ -1740,8 +1745,7 @@ doTopReactEq work_item = doTopReactOther work_item improveTopFunEqs :: CtEvidence -> TyCon -> [TcType] -> TcType -> TcS () -- See Note [FunDep and implicit parameter reactions] improveTopFunEqs ev fam_tc args rhs - | isGiven ev -- See Note [No FunEq improvement for Givens] - || not (isImprovable ev) + | not (isImprovable ev) = return () | otherwise @@ -1871,24 +1875,6 @@ kinds much match too; so it's easier to let the normal machinery handle it. Instead we are careful to orient the new derived equality with the template on the left. Delicate, but it works. -Note [No FunEq improvement for Givens] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We don't do improvements (injectivity etc) for Givens. Why? - -* It generates Derived constraints on skolems, which don't do us - much good, except perhaps identify inaccessible branches. - (They'd be perfectly valid though.) - -* For type-nat stuff the derived constraints include type families; - e.g. (a < b), (b < c) ==> a < c If we generate a Derived for this, - we'll generate a Derived/Wanted CFunEqCan; and, since the same - InertCans (after solving Givens) are used for each iteration, that - massively confused the unflattening step (GHC.Tc.Solver.Flatten.unflatten). - - In fact it led to some infinite loops: - indexed-types/should_compile/T10806 - indexed-types/should_compile/T10507 - polykinds/T10742 -} {- ******************************************************************* ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -1,4 +1,5 @@ -{-# LANGUAGE CPP, DeriveFunctor, TypeFamilies, ScopedTypeVariables #-} +{-# LANGUAGE CPP, DeriveFunctor, TypeFamilies, ScopedTypeVariables, TypeApplications, + DerivingStrategies, GeneralizedNewtypeDeriving #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates -Wno-incomplete-uni-patterns #-} @@ -80,7 +81,7 @@ module GHC.Tc.Solver.Monad ( addDictsByClass, delDict, foldDicts, filterDicts, findDict, -- Inert CEqCans - EqualCtList, findTyEqs, foldTyEqs, + EqualCtList(..), findTyEqs, foldTyEqs, findEq, -- Inert solved dictionaries @@ -90,7 +91,7 @@ module GHC.Tc.Solver.Monad ( foldIrreds, -- The flattening cache - lookupFlatCache, extendFlatCache, + lookupFamApp, extendFamAppCache, pprKicked, -- Inert function equalities @@ -186,6 +187,8 @@ import GHC.Utils.Monad import Data.IORef import Data.List ( partition, mapAccumL ) import qualified Data.Semigroup as S +import Data.List.NonEmpty ( NonEmpty(..), cons, toList, nonEmpty ) +import qualified Data.List.NonEmpty as NE #if defined(DEBUG) import GHC.Data.Graph.Directed @@ -399,12 +402,13 @@ data InertSet -- used to undo the cycle-breaking needed to handle -- Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical - , inert_flat_cache :: FunEqMap (TcCoercion, TcType) + , inert_famapp_cache :: FunEqMap (TcCoercion, TcType) -- If F tys :-> (co, rhs, flav), -- then co :: F tys ~ rhs -- flav is [G] -- - -- Just a hash-cons cache for use when flattening only + -- Just a hash-cons cache for use when reducing family applications + -- only -- -- Only nominal, Given equalities end up in here (along with -- top-level instances) @@ -438,7 +442,7 @@ emptyInert :: InertSet emptyInert = IS { inert_cans = emptyInertCans , inert_cycle_breakers = [] - , inert_flat_cache = emptyFunEqs + , inert_famapp_cache = emptyFunEqs , inert_solved_dicts = emptyDictMap } @@ -715,7 +719,35 @@ data InertCans -- See Note [Detailed InertCans Invariants] for more } type InertEqs = DTyVarEnv EqualCtList -type EqualCtList = [Ct] -- See Note [EqualCtList invariants] + +newtype EqualCtList = EqualCtList (NonEmpty Ct) + deriving newtype Outputable + -- See Note [EqualCtList invariants] + +unitEqualCtList :: Ct -> EqualCtList +unitEqualCtList ct = EqualCtList (ct :| []) + +addToEqualCtList :: Ct -> EqualCtList -> EqualCtList +-- NB: This function maintains the "derived-before-wanted" invariant of EqualCtList, +-- but not the others. See Note [EqualCtList invariants] +addToEqualCtList ct (EqualCtList old_eqs) + | isWantedCt ct + , eq1 :| eqs <- old_eqs + = EqualCtList (eq1 :| ct : eqs) + | otherwise + = EqualCtList (ct `cons` old_eqs) + +filterEqualCtList :: (Ct -> Bool) -> EqualCtList -> Maybe EqualCtList +filterEqualCtList pred (EqualCtList cts) + = fmap EqualCtList (nonEmpty $ NE.filter pred cts) + +equalCtListToList :: EqualCtList -> [Ct] +equalCtListToList (EqualCtList cts) = toList cts + +listToEqualCtList :: [Ct] -> Maybe EqualCtList +-- NB: This does not maintain invariants other than having the EqualCtList be +-- non-empty +listToEqualCtList cts = EqualCtList <$> nonEmpty cts {- Note [Detailed InertCans Invariants] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -756,8 +788,6 @@ The Wanteds can't rewrite anything which is why we put them last Note [inert_eqs: the inert equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": update. Don't forget to update (K1). See kick_out_rewritable - Definition [Can-rewrite relation] A "can-rewrite" relation between flavours, written f1 >= f2, is a binary relation with the following properties @@ -770,25 +800,24 @@ Lemma. If f1 >= f then f1 >= f1 Proof. By property (R2), with f1=f2 Definition [Generalised substitution] -A "generalised substitution" S is a set of triples (a -f-> t), where - a is a type variable +A "generalised substitution" S is a set of triples (t0 -f-> t), where + t0 is a type variable or an exactly-saturated type family application t is a type f is a flavour such that - (WF1) if (a -f1-> t1) in S - (a -f2-> t2) in S - then neither (f1 >= f2) nor (f2 >= f1) hold - (WF2) if (a -f-> t) is in S, then t /= a + (WF1) if (t0 -f1-> t1) in S + (t0' -f2-> t2) in S + then either not (f1 >= f2) or t0 does not appear within t0' + (WF2) if (t0 -f-> t) is in S, then t /= t0 Definition [Applying a generalised substitution] If S is a generalised substitution - S(f,a) = t, if (a -fs-> t) in S, and fs >= f - = a, otherwise -Application extends naturally to types S(f,t), modulo roles. -See Note [Flavours with roles]. + S(f,t0) = t, if (t0 -fs-> t) in S, and fs >= f + = apply S to components of t0, otherwise +See also Note [Flavours with roles]. -Theorem: S(f,a) is well defined as a function. -Proof: Suppose (a -f1-> t1) and (a -f2-> t2) are both in S, +Theorem: S(f,t0) is well defined as a function. +Proof: Suppose (t0 -f1-> t1) and (t0 -f2-> t2) are both in S, and f1 >= f and f2 >= f Then by (R2) f1 >= f2 or f2 >= f1, which contradicts (WF1) @@ -811,40 +840,41 @@ Our main invariant: ---------------------------------------------------------------- Note that inertness is not the same as idempotence. To apply S to a -type, you may have to apply it recursive. But inertness does +type, you may have to apply it recursively. But inertness does guarantee that this recursive use will terminate. Note [Extending the inert equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Main Theorem [Stability under extension] Suppose we have a "work item" - a -fw-> t + t0 -fw-> t and an inert generalised substitution S, - THEN the extended substitution T = S+(a -fw-> t) + THEN the extended substitution T = S+(t0 -fw-> t) is an inert generalised substitution PROVIDED - (T1) S(fw,a) = a -- LHS of work-item is a fixpoint of S(fw,_) - (T2) S(fw,t) = t -- RHS of work-item is a fixpoint of S(fw,_) - (T3) a not in t -- No occurs check in the work item + (T1) S(fw,t0) = t0 -- LHS of work-item is a fixpoint of S(fw,_) + (T2) S(fw,t) = t -- RHS of work-item is a fixpoint of S(fw,_) + (T3) t0 not in t -- No occurs check in the work item - AND, for every (b -fs-> s) in S: + AND, for every (t0' -fs-> s) in S: (K0) not (fw >= fs) Reason: suppose we kick out (a -fs-> s), - and add (a -fw-> t) to the inert set. + and add (t0 -fw-> t) to the inert set. The latter can't rewrite the former, so the kick-out achieved nothing - OR { (K1) not ( + OR { (K1) t0 is not rewritable in t0'. That is, t0 does not occur + in t0' (except perhaps in a cast or coercion). Reason: if fw >= fs, WF1 says we can't have both - a -fw-> t and a -fs-> s + t0 -fw-> t and F t0 -fs-> s AND (K2): guarantees inertness of the new substitution { (K2a) not (fs >= fs) OR (K2b) fs >= fw - OR (K2d) a not in s } + OR (K2d) t0 not in s } AND (K3) See Note [K3: completeness of solving] - { (K3a) If the role of fs is nominal: s /= a + { (K3a) If the role of fs is nominal: s /= t0 (K3b) If the role of fs is representational: s is not of form (a t1 .. tn) } } @@ -883,10 +913,10 @@ The idea is that It's used to avoid even looking for constraint to kick out. * Lemma (L1): The conditions of the Main Theorem imply that there is no - (a -fs-> t) in S, s.t. (fs >= fw). + (t0 -fs-> t) in S, s.t. (fs >= fw). Proof. Suppose the contrary (fs >= fw). Then because of (T1), - S(fw,a)=a. But since fs>=fw, S(fw,a) = s, hence s=a. But now we - have (a -fs-> a) in S, which contradicts (WF2). + S(fw,t0)=t0. But since fs>=fw, S(fw,t0) = s, hence s=t0. But now we + have (t0 -fs-> t0) in S, which contradicts (WF2). * The extended substitution satisfies (WF1) and (WF2) - (K1) plus (L1) guarantee that the extended substitution satisfies (WF1). @@ -1034,7 +1064,7 @@ instance Outputable InertCans where , text "Unsolved goals =" <+> int count ] where - folder eqs rest = listToBag eqs `andCts` rest + folder (EqualCtList eqs) rest = nonEmptyToBag eqs `andCts` rest {- ********************************************************************* * * @@ -1364,7 +1394,7 @@ should_split_match_args inert_eqs fun_eqs tys canRewriteTv :: InertEqs -> EqRel -> TyVar -> Bool canRewriteTv inert_eqs eq_rel tv - | Just (ct : _) <- lookupDVarEnv inert_eqs tv + | Just (EqualCtList (ct :| _)) <- lookupDVarEnv inert_eqs tv , CEqCan { cc_eq_rel = eq_rel1 } <- ct = eq_rel1 `eqCanRewrite` eq_rel | otherwise @@ -1372,7 +1402,7 @@ canRewriteTv inert_eqs eq_rel tv canRewriteTyFam :: FunEqMap EqualCtList -> EqRel -> TyCon -> [Type] -> Bool canRewriteTyFam fun_eqs eq_rel tf args - | Just (ct : _) <- findFunEq fun_eqs tf args + | Just (EqualCtList (ct :| _)) <- findFunEq fun_eqs tf args , CEqCan { cc_eq_rel = eq_rel1 } <- ct = eq_rel1 `eqCanRewrite` eq_rel | otherwise @@ -1392,7 +1422,7 @@ isImprovable _ = True addTyEq :: InertEqs -> TcTyVar -> Ct -> InertEqs addTyEq old_eqs tv ct - = extendDVarEnv_C add_eq old_eqs tv [ct] + = extendDVarEnv_C add_eq old_eqs tv (unitEqualCtList ct) where add_eq old_eqs _ = addToEqualCtList ct old_eqs @@ -1402,43 +1432,36 @@ addCanFunEq old_eqs fun_tc fun_args ct = alterTcApp old_eqs fun_tc fun_args upd where upd (Just old_equal_ct_list) = Just $ addToEqualCtList ct old_equal_ct_list - upd Nothing = Just $ [ct] - -addToEqualCtList :: Ct -> EqualCtList -> EqualCtList -addToEqualCtList ct old_eqs - | isWantedCt ct - , (eq1 : eqs) <- old_eqs - = eq1 : ct : eqs - | otherwise - = ct : old_eqs + upd Nothing = Just $ unitEqualCtList ct foldTyEqs :: (Ct -> b -> b) -> InertEqs -> b -> b foldTyEqs k eqs z - = foldDVarEnv (\cts z -> foldr k z cts) z eqs + = foldDVarEnv (\(EqualCtList cts) z -> foldr k z cts) z eqs -findTyEqs :: InertCans -> TyVar -> EqualCtList -findTyEqs icans tv = lookupDVarEnv (inert_eqs icans) tv `orElse` [] +findTyEqs :: InertCans -> TyVar -> [Ct] +findTyEqs icans tv = maybe [] id (fmap @Maybe equalCtListToList $ + lookupDVarEnv (inert_eqs icans) tv) delEq :: InertCans -> CanEqLHS -> TcType -> InertCans delEq ic lhs rhs = case lhs of TyVarLHS tv - -> ic { inert_eqs = modifyDVarEnv (filter (not . isThisOne)) (inert_eqs ic) tv } + -> ic { inert_eqs = alterDVarEnv upd (inert_eqs ic) tv } TyFamLHS tf args -> ic { inert_funeqs = alterTcApp (inert_funeqs ic) tf args upd } - where - upd (Just eq_ct_list) - | null filtered = Nothing - | otherwise = Just filtered - where filtered = filter (not . isThisOne) eq_ct_list - upd Nothing = Nothing where + isThisOne :: Ct -> Bool isThisOne (CEqCan { cc_rhs = t1 }) = tcEqTypeNoKindCheck rhs t1 isThisOne other = pprPanic "delEq" (ppr lhs $$ ppr ic $$ ppr other) -findEq :: InertCans -> CanEqLHS -> EqualCtList + upd :: Maybe EqualCtList -> Maybe EqualCtList + upd (Just eq_ct_list) = filterEqualCtList (not . isThisOne) eq_ct_list + upd Nothing = Nothing + +findEq :: InertCans -> CanEqLHS -> [Ct] findEq icans (TyVarLHS tv) = findTyEqs icans tv findEq icans (TyFamLHS fun_tc fun_args) - = findFunEq (inert_funeqs icans) fun_tc fun_args `orElse` [] + = maybe [] id (fmap @Maybe equalCtListToList $ + findFunEq (inert_funeqs icans) fun_tc fun_args) {- ********************************************************************* * * @@ -1707,11 +1730,12 @@ kick_out_rewritable new_fr new_lhs -> EqualCtList -> ([Ct], container) -> ([Ct], container) kick_out_eqs extend eqs (acc_out, acc_in) - = (eqs_out `chkAppend` acc_out, case eqs_in of - [] -> acc_in - (eq1:_) -> extend acc_in (cc_lhs eq1) eqs_in) + = (eqs_out `chkAppend` acc_out, case listToEqualCtList eqs_in of + Nothing -> acc_in + Just eqs_in_ecl@(EqualCtList (eq1 :| _)) + -> extend acc_in (cc_lhs eq1) eqs_in_ecl) where - (eqs_out, eqs_in) = partition kick_out_eq eqs + (eqs_out, eqs_in) = partition kick_out_eq (equalCtListToList eqs) -- Implements criteria K1-K3 in Note [Extending the inert equalities] kick_out_eq (CEqCan { cc_lhs = lhs, cc_rhs = rhs_ty @@ -1955,8 +1979,9 @@ getInertGivens :: TcS [Ct] getInertGivens = do { inerts <- getInertCans ; let all_cts = foldDicts (:) (inert_dicts inerts) - $ foldFunEqs (++) (inert_funeqs inerts) - $ concat (dVarEnvElts (inert_eqs inerts)) + $ foldFunEqs (\ecl out -> equalCtListToList ecl ++ out) + (inert_funeqs inerts) + $ concatMap equalCtListToList (dVarEnvElts (inert_eqs inerts)) ; return (filter isGivenCt all_cts) } getPendingGivenScs :: TcS [Ct] @@ -2043,8 +2068,9 @@ getUnsolvedInerts add_if_unsolved ct cts | is_unsolved ct = ct `consCts` cts | otherwise = cts - add_if_unsolveds :: [Ct] -> Cts -> Cts - add_if_unsolveds new_cts old_cts = foldr add_if_unsolved old_cts new_cts + add_if_unsolveds :: EqualCtList -> Cts -> Cts + add_if_unsolveds new_cts old_cts = foldr add_if_unsolved old_cts + (equalCtListToList new_cts) is_unsolved ct = not (isGivenCt ct) -- Wanted or Derived @@ -2079,8 +2105,8 @@ getHasGivenEqs tclvl lift_equal_ct_list :: (Ct -> HasGivenEqs) -> EqualCtList -> HasGivenEqs -- returns NoGivenEqs for non-singleton lists, as Given lists are always -- singletons - lift_equal_ct_list check [ct] = check ct - lift_equal_ct_list _ _ = NoGivenEqs + lift_equal_ct_list check (EqualCtList (ct :| [])) = check ct + lift_equal_ct_list _ _ = NoGivenEqs check_local_given_tv_eq :: Ct -> HasGivenEqs check_local_given_tv_eq (CEqCan { cc_lhs = TyVarLHS tv, cc_ev = ev}) @@ -2102,7 +2128,10 @@ getHasGivenEqs tclvl is_outer_var :: TyCoVar -> Bool is_outer_var tv - | isTyVar tv = tclvl `strictlyDeeperThan` tcTyVarLevel tv + -- NB: a meta-tv alpha[3] may end up unifying with skolem b[2], + -- so treat it as an "outer" var, even at level 3. + | isTyVar tv = isTouchableMetaTyVar tclvl tv || + tclvl `strictlyDeeperThan` tcTyVarLevel tv | otherwise = False -- | Returns Given constraints that might, @@ -2215,8 +2244,6 @@ considered rigid. Note [When does an implication have given equalities?] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": update note - Consider an implication beta => alpha ~ Int where beta is a unification variable that has already been unified @@ -2245,23 +2272,38 @@ are some wrinkles: beta => ...blah... If we still don't know what beta is, we conservatively treat it as potentially becoming an equality. Hence including 'irreds' in the calculation or has_given_eqs. + Note that we can't really know what's in an irred, so any irred is considered + a potential equality. + + * What about something like forall a b. a ~ F b => [W] c ~ X y z? That Given + cannot affect the Wanted, because the Given is entirely *local*: it mentions + only skolems bound in the very same implication. Such equalities need not + prevent floating. (Test case typecheck/should_compile/LocalGivenEqs has a + real-life motivating example, with some detailed commentary.) These + equalities are noted with LocalGivenEqs: they do not prevent floating, but + they also are allowed to show up in error messages. See + Note [Suppress redundant givens during error reporting] in GHC.Tc.Errors. + The difference between what stops floating and what is suppressed from + error messages is why we need three options for HasGivenEqs. + + There is also a simpler case that triggers this behaviour: - * When flattening givens, we generate Given equalities like - : F [a] ~ f, - with Refl evidence, and we *don't* want those to count as an equality - in the givens! After all, the entire flattening business is just an - internal matter, and the evidence does not mention any of the 'givens' - of this implication. So we do not treat inert_funeqs as a 'given equality'. + data T where + MkT :: F a ~ G b => a -> b -> T + + f (MkT _ _) = True + + Because of this behaviour around local equality givens, we can infer the + type of f. This is typecheck/should_compile/LocalGivenEqs2. * See Note [Let-bound skolems] for another wrinkle - * We do *not* need to worry about representational equalities, because - these do not affect the ability to float constraints. + * We need not look at the equality relation involved (nominal vs representational), + because representational equalities can still imply nominal ones. For example, + if (G a ~R G b) and G's argument's role is nominal, then we can deduce a ~N b. Note [Let-bound skolems] ~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": Update note. - If * the inert set contains a canonical Given CEqCan (a ~ ty) and * 'a' is a skolem bound in this very implication, @@ -2326,20 +2368,22 @@ removeInertCt is ct = CIrredCan {} -> panic "removeInertCt: CIrredEvCan" CNonCanonical {} -> panic "removeInertCt: CNonCanonical" -lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavourRole)) -lookupFlatCache fam_tc tys - = do { IS { inert_flat_cache = flat_cache +-- | Looks up a family application in both the inerts and the famapp-cache +lookupFamApp :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavourRole)) +lookupFamApp fam_tc tys + = do { IS { inert_famapp_cache = famapp_cache , inert_cans = IC { inert_funeqs = inert_funeqs } } <- getTcSInerts ; return (firstJusts [lookup_inerts inert_funeqs, - lookup_flats flat_cache]) } + lookup_famapps famapp_cache]) } where lookup_inerts inert_funeqs - | Just (CEqCan { cc_ev = ctev, cc_rhs = rhs } : _) <- findFunEq inert_funeqs fam_tc tys + | Just (EqualCtList (CEqCan { cc_ev = ctev, cc_rhs = rhs } :| _)) + <- findFunEq inert_funeqs fam_tc tys = Just (ctEvCoercion ctev, rhs, ctEvFlavourRole ctev) | otherwise = Nothing - lookup_flats flat_cache - | Just (co, rhs) <- findFunEq flat_cache fam_tc tys + lookup_famapps famapp_cache + | Just (co, rhs) <- findFunEq famapp_cache fam_tc tys = Just (co, rhs, (Given, NomEq)) | otherwise = Nothing @@ -2841,10 +2885,8 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) , tcs_count = count } -> do { inerts <- TcM.readTcRef old_inert_var - ; let nest_inert = emptyInert - { inert_cans = inert_cans inerts - , inert_solved_dicts = inert_solved_dicts inerts } - -- See Note [Do not inherit the flat cache] + ; let nest_inert = inerts { inert_cycle_breakers = [] } + -- all other InertSet fields are inherited ; new_inert_var <- TcM.newTcRef nest_inert ; new_wl_var <- TcM.newTcRef emptyWorkList ; let nest_env = TcSEnv { tcs_ev_binds = ref @@ -2865,22 +2907,10 @@ nestImplicTcS ref inner_tclvl (TcS thing_inside) #endif ; return res } -{- Note [Do not inherit the flat cache] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We do not want to inherit the flat cache when processing nested -implications. Consider - a ~ F b, forall c. b~Int => blah -If we have F b ~ fsk in the flat-cache, and we push that into the -nested implication, we might miss that F b can be rewritten to F Int, -and hence perhaps solve it. Moreover, the fsk from outside is -flattened out after solving the outer level, but and we don't -do that flattening recursively. --} - nestTcS :: TcS a -> TcS a -- Use the current untouchables, augmenting the current -- evidence bindings, and solved dictionaries --- But have no effect on the InertCans, or on the inert_flat_cache +-- But have no effect on the InertCans, or on the inert_famapp_cache -- (we want to inherit the latter from processing the Givens) nestTcS (TcS thing_inside) = TcS $ \ env@(TcSEnv { tcs_inerts = inerts_var }) -> @@ -3168,15 +3198,15 @@ zonkTyCoVarKind :: TcTyCoVar -> TcS TcTyCoVar zonkTyCoVarKind tv = wrapTcS (TcM.zonkTyCoVarKind tv) ---------------------------- -extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcType) -> TcS () -extendFlatCache tc xi_args stuff@(_, ty) +extendFamAppCache :: TyCon -> [Type] -> (TcCoercion, TcType) -> TcS () +extendFamAppCache tc xi_args stuff@(_, ty) = do { dflags <- getDynFlags - ; when (gopt Opt_FlatCache dflags) $ - do { traceTcS "extendFlatCache" (vcat [ ppr tc <+> ppr xi_args - , ppr ty ]) + ; when (gopt Opt_FamAppCache dflags) $ + do { traceTcS "extendFamAppCache" (vcat [ ppr tc <+> ppr xi_args + , ppr ty ]) -- 'co' can be bottom, in the case of derived items - ; updInertTcS $ \ is@(IS { inert_flat_cache = fc }) -> - is { inert_flat_cache = insertFunEq fc tc xi_args stuff } } } + ; updInertTcS $ \ is@(IS { inert_famapp_cache = fc }) -> + is { inert_famapp_cache = insertFunEq fc tc xi_args stuff } } } pprKicked :: Int -> SDoc pprKicked 0 = empty ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -70,7 +70,6 @@ -fextended-default-rules -fffi -ffi --fflat-cache -ffloat-all-lams -ffloat-lam-args -ffrontend-opt ===================================== docs/users_guide/exts/type_families.rst ===================================== @@ -581,6 +581,51 @@ If the option :extension:`UndecidableInstances` is passed to the compiler, the above restrictions are not enforced and it is on the programmer to ensure termination of the normalisation of type families during type inference. +Reducing type family applications +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +.. ghc-flag:: -ffamily-application-cache + :shortdesc: Use a cache when reducing type family applications + :type: dynamic + :reverse: -fno-family-application-cache + :category: + + The flag :ghc-flag:`-ffamily-application-cache` (on by default) instructs + GHC to use a cache when reducing type family applications. In most cases, + this will speed up compilation. The use of this flag will not affect + runtime behaviour. + +When GHC encounters a type family application (like ``F Int a``) in a program, +it must often reduce it in order to complete type checking. Here is a simple +example:: + + type family F a where + F Int = Bool + F (Maybe Double) = Char + + g :: F Int -> Bool + g = not + +Despite the fact that ``g``\'s type mentions ``F Int``, GHC must recognize that +``g``\'s argument really has type ``Bool``. This is done by *reducing* ``F Int`` +to become ``Bool``. Sometimes, there is not enough information to reduce a type +family application; we say such an application is *stuck*. Continuing this example, +an occurrence of ``F (Maybe a)`` (for some type variable ``a``) would be stuck, as +no equation applies. + +During type checking, GHC uses heuristics to determine which type family application +to reduce next; there is no predictable ordering among different type family applications. +The non-determinism rarely matters in practice. In most programs, type family reduction +terminates, and so these choices are immaterial. However, if a type family application +does not terminate, it is possible that type-checking may unpredictably diverge. (GHC +will always take the same path for a given source program, but small changes in that +source program may induce GHC to take a different path. Compiling a given, unchanged +source program is still deterministic.) + +In order to speed up type family reduction, GHC normally uses a cache, remembering what +type family applications it has previously reduced. This feature can be disabled with +:ghc-flag:`-fno-family-application-cache`. + .. _type-wildcards-lhs: Wildcards on the LHS of data and type family instances ===================================== testsuite/tests/indexed-types/should_fail/T13784.stderr ===================================== @@ -1,6 +1,11 @@ T13784.hs:29:28: error: - • Couldn't match type ‘as’ with ‘a : Divide a as’ + • Could not deduce: as ~ (a : Divide a as) + from the context: (a : as) ~ (a1 : as1) + bound by a pattern with constructor: + :* :: forall a (as :: [*]). a -> Product as -> Product (a : as), + in an equation for ‘divide’ + at T13784.hs:29:13-19 Expected: Product (Divide a (a : as)) Actual: Product as1 ‘as’ is a rigid type variable bound by ===================================== testsuite/tests/patsyn/should_fail/T11010.stderr ===================================== @@ -1,6 +1,9 @@ T11010.hs:9:36: error: - • Couldn't match type ‘a1’ with ‘Int’ + • Could not deduce: a1 ~ Int + from the context: a ~ Int + bound by the signature for pattern synonym ‘IntFun’ + at T11010.hs:9:9-14 Expected: a -> b Actual: a1 -> b ‘a1’ is a rigid type variable bound by ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs ===================================== @@ -0,0 +1,137 @@ +{-# LANGUAGE RankNTypes, TypeFamilies, FlexibleInstances #-} +{-# OPTIONS_GHC -Wno-missing-methods -Wno-unused-matches #-} + +module LocalGivenEqs where + +-- See Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad; +-- this tests custom treatment for LocalGivenEqs + +{- +I (Richard E) tried somewhat half-heartedly to minimize this, but failed. +The key bit is the use of the ECP constructor inside the lambda in happyReduction_508. +(The lack of a type signature on that is not at issue, I believe.) The type +of ECP is + (forall b. DisambECP b => PV (Located b)) -> ECP +So, the argument to ECP gets a [G] DisambECP b, which (via its superclass) grants +us [G] b ~ (Body b) GhcPs. In order to infer the type of happy_var_2, we need to +float some wanted out past this equality. We have Note [Let-bound skolems] +in GHC.Tc.Solver.Monad to consider this Given equality to be let-like, and thus +not prevent floating. But, note that the equality isn't quite let-like, because +it mentions b in its RHS. It thus triggers Note [Type variable cycles in Givens] +in GHC.Tc.Solver.Canonical. That Note says we change the situation to + [G] b ~ cbv GhcPs + [G] Body b ~ cbv +for some fresh CycleBreakerTv cbv. Now, our original equality looks to be let-like, +but the new cbv equality is *not* let-like -- note that the variable is on the RHS. +The solution is to consider any equality whose free variables are all at the current +level to not stop equalities from floating. These are called *local*. Because both +Givens are local in this way, they no longer prevent floating, and we can type-check +this example. +-} + +import Data.Kind ( Type ) +import GHC.Exts ( Any ) + +infixr 9 `HappyStk` +data HappyStk a = HappyStk a (HappyStk a) +newtype HappyWrap201 = HappyWrap201 (ECP) +newtype HappyWrap205 = HappyWrap205 (([Located Token],Bool)) + +newtype HappyAbsSyn = HappyAbsSyn HappyAny +type HappyAny = Any + +newtype ECP = + ECP { unECP :: forall b. DisambECP b => PV (Located b) } + +data PV a +data P a +data GhcPs +data Token +data Located a +data AnnKeywordId = AnnIf | AnnThen | AnnElse | AnnSemi +data AddAnn +data SrcSpan +type LHsExpr a = Located (HsExpr a) +data HsExpr a + +class b ~ (Body b) GhcPs => DisambECP b where + type Body b :: Type -> Type + mkHsIfPV :: SrcSpan + -> LHsExpr GhcPs + -> Bool -- semicolon? + -> Located b + -> Bool -- semicolon? + -> Located b + -> PV (Located b) + +instance DisambECP (HsExpr GhcPs) where + type Body (HsExpr GhcPs) = HsExpr + mkHsIfPV = undefined + +instance Functor P +instance Applicative P +instance Monad P + +instance Functor PV +instance Applicative PV +instance Monad PV + +mj :: AnnKeywordId -> Located e -> AddAnn +mj = undefined + +amms :: Monad m => m (Located a) -> [AddAnn] -> m (Located a) +amms = undefined + +happyIn208 :: ECP -> HappyAbsSyn +happyIn208 = undefined + +happyReturn :: () => a -> P a +happyReturn = (return) + +happyThen :: () => P a -> (a -> P b) -> P b +happyThen = (>>=) + +comb2 :: Located a -> Located b -> SrcSpan +comb2 = undefined + +runPV :: PV a -> P a +runPV = undefined + +happyOutTok :: HappyAbsSyn -> Located Token +happyOutTok = undefined + +happyOut201 :: HappyAbsSyn -> HappyWrap201 +happyOut201 = undefined + +happyOut205 :: HappyAbsSyn -> HappyWrap205 +happyOut205 = undefined + +happyReduction_508 (happy_x_8 `HappyStk` + happy_x_7 `HappyStk` + happy_x_6 `HappyStk` + happy_x_5 `HappyStk` + happy_x_4 `HappyStk` + happy_x_3 `HappyStk` + happy_x_2 `HappyStk` + happy_x_1 `HappyStk` + happyRest) tk + = happyThen ((case happyOutTok happy_x_1 of { happy_var_1 -> + case happyOut201 happy_x_2 of { (HappyWrap201 happy_var_2) -> + case happyOut205 happy_x_3 of { (HappyWrap205 happy_var_3) -> + case happyOutTok happy_x_4 of { happy_var_4 -> + case happyOut201 happy_x_5 of { (HappyWrap201 happy_var_5) -> + case happyOut205 happy_x_6 of { (HappyWrap205 happy_var_6) -> + case happyOutTok happy_x_7 of { happy_var_7 -> + case happyOut201 happy_x_8 of { (HappyWrap201 happy_var_8) -> + -- uncomment this next signature to avoid the need + -- for special treatment of floating described above + ( runPV (unECP happy_var_2 {- :: PV (LHsExpr GhcPs) -}) >>= \ happy_var_2 -> + return $ ECP $ + unECP happy_var_5 >>= \ happy_var_5 -> + unECP happy_var_8 >>= \ happy_var_8 -> + amms (mkHsIfPV (comb2 happy_var_1 happy_var_8) happy_var_2 (snd happy_var_3) happy_var_5 (snd happy_var_6) happy_var_8) + (mj AnnIf happy_var_1:mj AnnThen happy_var_4 + :mj AnnElse happy_var_7 + :(map (\l -> mj AnnSemi l) (fst happy_var_3)) + ++(map (\l -> mj AnnSemi l) (fst happy_var_6))))}}}}}}}}) + ) (\r -> happyReturn (happyIn208 r)) ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE TypeFamilies, GADTSyntax, ExistentialQuantification #-} + +-- This is a simple case that exercises the LocalGivenEqs bullet +-- of Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad +-- If a future change rejects this, that's not the end of the world, but it's nice +-- to be able to infer `f`. + +module LocalGivenEqs2 where + +type family F a +type family G b + +data T where + MkT :: F a ~ G b => a -> b -> T + +f (MkT _ _) = True ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -726,3 +726,5 @@ test('T15942', normal, compile, ['']) test('CbvOverlap', normal, compile, ['']) test('InstanceGivenOverlap', normal, compile, ['']) test('InstanceGivenOverlap2', normal, compile, ['']) +test('LocalGivenEqs', normal, compile, ['']) +test('LocalGivenEqs2', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/86418442e025aa6e00f752bd65b67b40b66326db...e2ec2adab5f5af4756b0769dd8af8eb192700c05 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/86418442e025aa6e00f752bd65b67b40b66326db...e2ec2adab5f5af4756b0769dd8af8eb192700c05 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 Sat Nov 7 20:05:23 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Sat, 07 Nov 2020 15:05:23 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 260 commits: Make sizeExpr strict in the size threshold to facilitate WW. Message-ID: <5fa6fe0326fb4_10ee3ffb6083b9e06212fe@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - fd86ba36 by Richard Eisenberg at 2020-11-07T15:01:51-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into a new file GHC.Core.Map.Type, in order to avoid module import cycles with GHC.Core. - - - - - 2cc4e986 by Richard Eisenberg at 2020-11-07T15:02:04-05:00 Start of work in simplifying flattening - - - - - 5e1f5ac5 by Richard Eisenberg at 2020-11-07T15:02:23-05:00 Much work toward simplifying CFunEqCan - - - - - ce9166a3 by Richard Eisenberg at 2020-11-07T15:02:23-05:00 Canonicalized function equalities. Now, onto interactions. - - - - - a7257d2e by Richard Eisenberg at 2020-11-07T15:02:36-05:00 CEqCan, and canonicalization for it - - - - - 5d857dfd by Richard Eisenberg at 2020-11-07T15:02:36-05:00 Main changes done. Now to delete code. - - - - - 8064617c by Richard Eisenberg at 2020-11-07T15:02:43-05:00 Kill off CFunEqCan and CTyEqCan - - - - - 53299b6b by Richard Eisenberg at 2020-11-07T15:02:51-05:00 It compiles. - - - - - 888df57c by Richard Eisenberg at 2020-11-07T15:02:51-05:00 Some bugfixing - - - - - d0032b95 by Richard Eisenberg at 2020-11-07T15:02:51-05:00 Lots of bug fixing - - - - - 86450fea by Richard Eisenberg at 2020-11-07T15:02:51-05:00 Expand synonyms that mention families, obvs - - - - - 17b888bd by Richard Eisenberg at 2020-11-07T15:02:51-05:00 Super skolems are really super. - - - - - 11c01809 by Richard Eisenberg at 2020-11-07T15:02:51-05:00 Another bug bites the dust. - - - - - b2a42a84 by Richard Eisenberg at 2020-11-07T15:02:59-05:00 Put variable on left only when it will unify - - - - - 1fbc6d22 by Richard Eisenberg at 2020-11-07T15:02:59-05:00 Tiny little changes - - - - - 1b405f05 by Richard Eisenberg at 2020-11-07T15:03:05-05:00 Use built-in axioms for injectivity - - - - - 4a7a8281 by Richard Eisenberg at 2020-11-07T15:03:05-05:00 Stop loop in solver due to blocked hetero eqs - - - - - 2922ccff by Richard Eisenberg at 2020-11-07T15:03:05-05:00 Note [Runaway Derived rewriting] - - - - - a3a214f5 by Richard Eisenberg at 2020-11-07T15:03:05-05:00 Still need to check tyvar/funeq orientation - - - - - fe4d1646 by Richard Eisenberg at 2020-11-07T15:03:12-05:00 More bugfixing - - - - - f9ccda85 by Richard Eisenberg at 2020-11-07T15:03:13-05:00 Orient FunEq/FunEq correctly wrt occurs-check - - - - - 18e6371a by Richard Eisenberg at 2020-11-07T15:03:17-05:00 Fix import - - - - - 7838de4c by Richard Eisenberg at 2020-11-07T15:03:23-05:00 Note [Type variable cycles in Givens] - - - - - 8234e354 by Richard Eisenberg at 2020-11-07T15:03:23-05:00 Handle obscure corner case in canonicalize - - - - - 72569d5e by Richard Eisenberg at 2020-11-07T15:03:23-05:00 Handle (=>) specially in pure unifier - - - - - 172f86d1 by Richard Eisenberg at 2020-11-07T15:03:23-05:00 Start deleting stuff. Hooray! - - - - - 3c898f3d by Richard Eisenberg at 2020-11-07T15:03:30-05:00 Fix test output - - - - - 227d8cc7 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 Delete delete delete !! - - - - - 7d18c5a6 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 More deleting. Checkpoint before removing FlattenMode - - - - - b2c9e335 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 Remove FlattenMode - - - - - 306a1275 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 Stopped bumping ctLocDepth in runFlatten - - - - - 239b3a96 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 Finished deleting. - - - - - b8fb19b8 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 A few error message wibbles - - - - - 673df916 by Richard Eisenberg at 2020-11-07T15:03:30-05:00 Some small changes, mostly comments. - - - - - 109da70b by Richard Eisenberg at 2020-11-07T15:03:40-05:00 Fix #18875 by breaking type variable cycles. - - - - - 0aed9882 by Richard Eisenberg at 2020-11-07T15:03:40-05:00 Actually add test files - - - - - 7115632e by Richard Eisenberg at 2020-11-07T15:03:40-05:00 Add Detail (7) to the Note - - - - - 89733eac by Richard Eisenberg at 2020-11-07T15:03:40-05:00 A few error wibbles - - - - - 3731060d by Richard Eisenberg at 2020-11-07T15:03:40-05:00 Don't simplify extra-constraint holes - - - - - ea17f185 by Richard Eisenberg at 2020-11-07T15:03:45-05:00 Subtleties in Note [Instance and Given overlap] - - - - - f7b5ca9d by Richard Eisenberg at 2020-11-07T15:03:45-05:00 Update Note [TyVar/TyVar orientation] - - - - - 69d05279 by Richard Eisenberg at 2020-11-07T15:03:45-05:00 Actually add tests - - - - - f9260d86 by Richard Eisenberg at 2020-11-07T15:03:45-05:00 Do mightMatchLater correctlier. - - - - - 3cda4c4a by Richard Eisenberg at 2020-11-07T15:03:45-05:00 Simplify getNoGivenEqs - - - - - e518c61a by Richard Eisenberg at 2020-11-07T15:03:45-05:00 Simplify code a bit - - - - - 7a1f06bc by Richard Eisenberg at 2020-11-07T15:03:50-05:00 Introduce 3-way for ic_given_eqs - - - - - 4d9e0199 by Richard Eisenberg at 2020-11-07T15:03:50-05:00 test LocalGivenEqs - - - - - 2b29feaf by Richard Eisenberg at 2020-11-07T15:03:54-05:00 Update commentary about HasGivenEqs - - - - - cc52a521 by Richard Eisenberg at 2020-11-07T15:03:54-05:00 Update notes. - - - - - a03cacbd by Richard Eisenberg at 2020-11-07T15:03:54-05:00 More documentation around LocalGivenEqs - - - - - cf072f9a by Richard Eisenberg at 2020-11-07T15:04:38-05:00 Rename the flat-cache. Document it, too. - - - - - fc3f79e4 by Richard Eisenberg at 2020-11-07T15:04:38-05:00 Make EqualCtList into a newtype with NonEmpty - - - - - 49ba071d by Richard Eisenberg at 2020-11-07T15:04:38-05:00 Remove Note [No FunEq improvement for Givens] - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e2ec2adab5f5af4756b0769dd8af8eb192700c05...49ba071d8135a228ced201743017ab301cdb3b2c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e2ec2adab5f5af4756b0769dd8af8eb192700c05...49ba071d8135a228ced201743017ab301cdb3b2c 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 Sun Nov 8 03:44:06 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Sat, 07 Nov 2020 22:44:06 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Fix compilation errors from rebasing Message-ID: <5fa76986c337a_10ee3ffb96fef408640713@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 0957a3e4 by Richard Eisenberg at 2020-11-07T22:43:51-05:00 Fix compilation errors from rebasing - - - - - 3 changed files: - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - utils/haddock Changes: ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -177,7 +177,6 @@ import GHC.Core.Predicate import GHC.Types.Unique import GHC.Types.Unique.DFM -import GHC.Core.TyCon.Env import GHC.Types.Unique.Set import GHC.Data.Maybe ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit ad9cbad7312a64e6757c32bd9488c55ba4f2fec9 +Subproject commit ddb63957937b551367f5ae0d074098dc4ccd1882 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0957a3e4ceaa03df9981116ee185a69ccc4320f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0957a3e4ceaa03df9981116ee185a69ccc4320f4 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 Sun Nov 8 03:56:47 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Sat, 07 Nov 2020 22:56:47 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Use DTyConEnv for TcAppMap instead of UDFM Message-ID: <5fa76c7fe2d24_10ee3ffbd4fc1e20641589@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 2115585d by Richard Eisenberg at 2020-11-07T22:56:31-05:00 Use DTyConEnv for TcAppMap instead of UDFM - - - - - 2 changed files: - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Core/TyCon/Env.hs ===================================== @@ -26,11 +26,11 @@ module GHC.Core.TyCon.Env ( DTyConEnv, - emptyDTyConEnv, + emptyDTyConEnv, isEmptyDTyConEnv, lookupDTyConEnv, delFromDTyConEnv, filterDTyConEnv, mapDTyConEnv, - adjustDTyConEnv, alterDTyConEnv, extendDTyConEnv, + adjustDTyConEnv, alterDTyConEnv, extendDTyConEnv, foldDTyConEnv ) where #include "HsVersions.h" @@ -116,6 +116,9 @@ type DTyConEnv a = UniqDFM TyCon a emptyDTyConEnv :: DTyConEnv a emptyDTyConEnv = emptyUDFM +isEmptyDTyConEnv :: DTyConEnv a -> Bool +isEmptyDTyConEnv = isNullUDFM + lookupDTyConEnv :: DTyConEnv a -> TyCon -> Maybe a lookupDTyConEnv = lookupUDFM @@ -136,3 +139,6 @@ alterDTyConEnv = alterUDFM extendDTyConEnv :: DTyConEnv a -> TyCon -> a -> DTyConEnv a extendDTyConEnv = addToUDFM + +foldDTyConEnv :: (elt -> a -> a) -> a -> DTyConEnv elt -> a +foldDTyConEnv = foldUDFM ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -175,9 +175,8 @@ import GHC.Tc.Types.Origin import GHC.Tc.Types.Constraint import GHC.Core.Predicate -import GHC.Types.Unique -import GHC.Types.Unique.DFM import GHC.Types.Unique.Set +import GHC.Core.TyCon.Env import GHC.Data.Maybe import GHC.Core.Map.Type @@ -2453,41 +2452,41 @@ looking at kinds would be harmless. -} -type TcAppMap a = UniqDFM TyCon (ListMap LooseTypeMap a) +type TcAppMap a = DTyConEnv (ListMap LooseTypeMap a) -- Indexed by tycon then the arg types, using "loose" matching, where -- we don't require kind equality. This allows, for example, (a |> co) -- to match (a). -- See Note [Use loose types in inert set] -- Used for types and classes; hence UniqDFM - -- See Note [foldTM determinism] for why we use UniqDFM here + -- See Note [foldTM determinism] in GHC.Data.TrieMap for why we use DTyConEnv here isEmptyTcAppMap :: TcAppMap a -> Bool -isEmptyTcAppMap m = isNullUDFM m +isEmptyTcAppMap m = isEmptyDTyConEnv m emptyTcAppMap :: TcAppMap a -emptyTcAppMap = emptyUDFM +emptyTcAppMap = emptyDTyConEnv findTcApp :: TcAppMap a -> TyCon -> [Type] -> Maybe a -findTcApp m tc tys = do { tys_map <- lookupUDFM m tc +findTcApp m tc tys = do { tys_map <- lookupDTyConEnv m tc ; lookupTM tys tys_map } delTcApp :: TcAppMap a -> TyCon -> [Type] -> TcAppMap a -delTcApp m tc tys = adjustUDFM (deleteTM tys) m tc +delTcApp m tc tys = adjustDTyConEnv (deleteTM tys) m tc insertTcApp :: TcAppMap a -> TyCon -> [Type] -> a -> TcAppMap a -insertTcApp m tc tys ct = alterUDFM alter_tm m tc +insertTcApp m tc tys ct = alterDTyConEnv alter_tm m tc where alter_tm mb_tm = Just (insertTM tys ct (mb_tm `orElse` emptyTM)) alterTcApp :: forall a. TcAppMap a -> TyCon -> [Type] -> (Maybe a -> Maybe a) -> TcAppMap a -alterTcApp m tc tys upd = alterUDFM alter_tm m tc +alterTcApp m tc tys upd = alterDTyConEnv alter_tm m tc where alter_tm :: Maybe (ListMap LooseTypeMap a) -> Maybe (ListMap LooseTypeMap a) alter_tm m_elt = Just (alterTM tys upd (m_elt `orElse` emptyTM)) filterTcAppMap :: (Ct -> Bool) -> TcAppMap Ct -> TcAppMap Ct filterTcAppMap f m - = mapUDFM do_tm m + = mapDTyConEnv do_tm m where do_tm tm = foldTM insert_mb tm emptyTM insert_mb ct tm @@ -2502,7 +2501,7 @@ tcAppMapToBag :: TcAppMap a -> Bag a tcAppMapToBag m = foldTcAppMap consBag m emptyBag foldTcAppMap :: (a -> b -> b) -> TcAppMap a -> b -> b -foldTcAppMap k m z = foldUDFM (foldTM k) z m +foldTcAppMap k m z = foldDTyConEnv (foldTM k) z m foldMapTcAppMap :: Monoid m => (a -> m) -> TcAppMap a -> m foldMapTcAppMap f = foldMap (foldMap f) @@ -2576,8 +2575,8 @@ findDict m loc cls tys findDictsByClass :: DictMap a -> Class -> Bag a findDictsByClass m cls - | Just tm <- lookupUDFM_Directly m (getUnique cls) = foldTM consBag tm emptyBag - | otherwise = emptyBag + | Just tm <- lookupDTyConEnv m (classTyCon cls) = foldTM consBag tm emptyBag + | otherwise = emptyBag delDict :: DictMap a -> Class -> [Type] -> DictMap a delDict m cls tys = delTcApp m (classTyCon cls) tys @@ -2587,7 +2586,7 @@ addDict m cls tys item = insertTcApp m (classTyCon cls) tys item addDictsByClass :: DictMap Ct -> Class -> Bag Ct -> DictMap Ct addDictsByClass m cls items - = addToUDFM_Directly m (getUnique cls) (foldr add emptyTM items) + = extendDTyConEnv m (classTyCon cls) (foldr add emptyTM items) where add ct@(CDictCan { cc_tyargs = tys }) tm = insertTM tys ct tm add ct _ = pprPanic "addDictsByClass" (ppr ct) @@ -2634,8 +2633,8 @@ findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a] -- We use this to check for derived interactions with built-in type-function -- constructors. findFunEqsByTyCon m tc - | Just tm <- lookupUDFM m tc = foldTM (:) tm [] - | otherwise = [] + | Just tm <- lookupDTyConEnv m tc = foldTM (:) tm [] + | otherwise = [] foldFunEqs :: (a -> b -> b) -> FunEqMap a -> b -> b foldFunEqs = foldTcAppMap View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2115585d3cf8665d225b2c7111d8857e593b79d5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2115585d3cf8665d225b2c7111d8857e593b79d5 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 Sun Nov 8 03:57:36 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Sat, 07 Nov 2020 22:57:36 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Remove mention of CFunEqCan from rebasing Message-ID: <5fa76cb03d1cc_10ee3ffb8ce8e7306423d8@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: a97a29b2 by Richard Eisenberg at 2020-11-07T22:57:23-05:00 Remove mention of CFunEqCan from rebasing - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -2432,7 +2432,7 @@ foldIrreds k irreds z = foldr k z irreds Note [Use loose types in inert set] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Whenever we are looking up an inert dictionary (CDictCan) or function -equality (CFunEqCan), we use a TcAppMap, which uses the Unique of the +equality (CEqCan), we use a TcAppMap, which uses the Unique of the class/type family tycon and then a trie which maps the arguments. This trie does *not* need to match the kinds of the arguments; this Note explains why. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a97a29b2f471d15fbfbc6572debdbde4c056e637 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a97a29b2f471d15fbfbc6572debdbde4c056e637 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 Sun Nov 8 14:43:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 08 Nov 2020 09:43:30 -0500 Subject: [Git][ghc/ghc][wip/tsan/all] 132 commits: Parser regression tests, close #12862 #12446 Message-ID: <5fa80412aa126_10ee3ffbc42584c46748ba@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tsan/all at Glasgow Haskell Compiler / GHC Commits: e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 13707ac1 by Ben Gamari at 2020-11-08T09:32:22-05:00 SMP.h: Add C11-style atomic operations - - - - - 4fdcb23c by Ben Gamari at 2020-11-08T09:40:20-05:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - 9843e80b by Ben Gamari at 2020-11-08T09:40:20-05:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - d05aa054 by Ben Gamari at 2020-11-08T09:40:20-05:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - 3f3fc00c by Ben Gamari at 2020-11-08T09:40:20-05:00 rts/Task: Make comments proper Notes - - - - - 69fa87bb by Ben Gamari at 2020-11-08T09:40:20-05:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - 6e1440f8 by Ben Gamari at 2020-11-08T09:40:20-05:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 662aade5 by Ben Gamari at 2020-11-08T09:40:20-05:00 rts/ClosureMaros: Use relaxed atomics - - - - - 2f1b08f5 by Ben Gamari at 2020-11-08T09:40:20-05:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - 751d094b by Ben Gamari at 2020-11-08T09:40:20-05:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - 5c1e8015 by Ben Gamari at 2020-11-08T09:40:20-05:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - df8c2abb by Ben Gamari at 2020-11-08T09:40:52-05:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - adc9fa09 by Ben Gamari at 2020-11-08T09:40:52-05:00 rts: Annotate benign race in waitForCapability - - - - - f77310e3 by Ben Gamari at 2020-11-08T09:40:52-05:00 rts: Clarify locking behavior of releaseCapability_ - - - - - b6c0e9d1 by Ben Gamari at 2020-11-08T09:40:52-05:00 rts: Add assertions for task ownership of capabilities - - - - - d4a858b0 by Ben Gamari at 2020-11-08T09:40:52-05:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 2a0b44ef by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Mitigate races in capability interruption logic - - - - - b099f2dc by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - 9efa169f by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 1bfdc2ad by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 4ef6b40f by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - b403f575 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Eliminate data races on pending_sync - - - - - f416d1d1 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - 22dd4f3e by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Avoid data races in message handling - - - - - c5154ab1 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - 1c656731 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/ThreadPaused: Avoid data races - - - - - 1673f4e5 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Schedule: Eliminate data races in run queue management - - - - - 6207b94b by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Eliminate shutdown data race on task counters - - - - - 6d5a70f9 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - d0b5dede by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Messages: Annotate benign race - - - - - f96cf570 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/RaiseAsync: Synchronize what_next read - - - - - 35253584 by Ben Gamari at 2020-11-08T09:40:53-05:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - a0445cad by Ben Gamari at 2020-11-08T09:40:53-05:00 Disable flawed assertion - - - - - cdc05f91 by Ben Gamari at 2020-11-08T09:40:53-05:00 Document schedulePushWork race - - - - - e1ae10d4 by Ben Gamari at 2020-11-08T09:40:53-05:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - 6c3c646c by Ben Gamari at 2020-11-08T09:40:53-05:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 40157768 by Ben Gamari at 2020-11-08T09:41:10-05:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - e990a1f6 by GHC GitLab CI at 2020-11-08T09:41:10-05:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - 8684e662 by GHC GitLab CI at 2020-11-08T09:41:10-05:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - 3d41230c by Ben Gamari at 2020-11-08T09:41:10-05:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - a164b12f by Ben Gamari at 2020-11-08T09:41:10-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - 0b3c2e45 by Ben Gamari at 2020-11-08T09:41:10-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 958796a2 by Ben Gamari at 2020-11-08T09:41:10-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 1be57065 by Ben Gamari at 2020-11-08T09:41:10-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 299c516c by Ben Gamari at 2020-11-08T09:41:10-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - b4acdabc by Ben Gamari at 2020-11-08T09:41:10-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 42409217 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/BlockAlloc: Use relaxed operations - - - - - c00f55d3 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - c7097264 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 0ffcb040 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/Storage: Use atomics - - - - - 24865cb4 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/Updates: Use proper atomic operations - - - - - ce181c57 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - fd4d4cd1 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/GC: Use atomics - - - - - baa322e4 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - bd0fb1d2 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/Storage: Accept races on heap size counters - - - - - 26e8e670 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - 40d7aa8a by GHC GitLab CI at 2020-11-08T09:41:41-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 7f1ebbf4 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - 688373b0 by Ben Gamari at 2020-11-08T09:41:41-05:00 rts: Use relaxed ordering on spinlock counters - - - - - a0d2713c by Ben Gamari at 2020-11-08T09:41:41-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 6f05d266 by Ben Gamari at 2020-11-08T09:41:41-05:00 Strengthen ordering in releaseGCThreads - - - - - 06665ca2 by Ben Gamari at 2020-11-08T09:41:48-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - adac9ad3 by Ben Gamari at 2020-11-08T09:41:54-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 296de125 by Ben Gamari at 2020-11-08T09:41:54-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - 5e3d99c2 by GHC GitLab CI at 2020-11-08T09:41:54-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 1061b8e9 by Ben Gamari at 2020-11-08T09:41:59-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 41a40d25 by Ben Gamari at 2020-11-08T09:41:59-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - 9c096a37 by Ben Gamari at 2020-11-08T09:42:03-05:00 Mitigate data races in event manager startup/shutdown - - - - - 06d604a2 by Ben Gamari at 2020-11-08T09:42:12-05:00 rts: Accept benign races in Proftimer - - - - - 0aeea61f by Ben Gamari at 2020-11-08T09:42:12-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 5e333a8e by Ben Gamari at 2020-11-08T09:42:36-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - 07d0e7a9 by Ben Gamari at 2020-11-08T09:42:36-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 747aef01 by Ben Gamari at 2020-11-08T09:42:50-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 7640556b by Ben Gamari at 2020-11-08T09:42:50-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 05d737a2 by Ben Gamari at 2020-11-08T09:42:50-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - 30476e1b by Ben Gamari at 2020-11-08T09:43:19-05:00 Merge branches 'wip/tsan/sched', 'wip/tsan/ci', 'wip/tsan/storage', 'wip/tsan/wsdeque', 'wip/tsan/misc', 'wip/tsan/stm', 'wip/tsan/event-mgr', 'wip/tsan/timer' and 'wip/tsan/stats' into wip/tsan/all - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07e82ba52228580cfbd90ff031e657acbecc715b...30476e1b940bbe494a08b8cb2b20a895dc8f4d75 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/07e82ba52228580cfbd90ff031e657acbecc715b...30476e1b940bbe494a08b8cb2b20a895dc8f4d75 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 Sun Nov 8 16:01:23 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Sun, 08 Nov 2020 11:01:23 -0500 Subject: [Git][ghc/ghc][wip/T18599] Make progress adding syntax for projection updates. Message-ID: <5fa816533b639_10ee3ffb976535d8677863@gitlab.haskell.org.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: bcab57b7 by Shayne Fletcher at 2020-11-08T11:00:49-05:00 Make progress adding syntax for projection updates. - - - - - 4 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - record-dot-syntax-test.sh Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -457,6 +457,7 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + -- | Record field selection. -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. @@ -471,6 +472,22 @@ data HsExpr p , gf_getField :: LHsExpr p -- Equivalent 'getField' term. } + -- Record update. + -- Expressions of these cases arise only when the RecordDotSyntax + -- langauge extensions is enabled. + + -- We call this RecordDotUpd in sympathy with RecordUpd. + + -- e.g. a{foo.bar.baz=1, quux} = RecordDotUpd { + -- rdupd_ext=noExtField, rdupd_expr=a, rdupd_updates=[...], rdupd_setField=setField@"quux" (setField@"foo"...a... 1) quux + -- }, + -- | RecordDotUpd + -- { rdupd_ext :: XRecordDotUpd + -- , rdupd_expr :: LHsExpr GhcPs + -- , rdupd_updates :: [LHsProjUpdate GhcPs (LHsExpr GhcPs)] + -- , rdupd_setField :: LHsExpr GhcPs -- Equivalent 'setField' term. + -- } + -- | Record field selector. -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. ===================================== compiler/GHC/Parser.y ===================================== @@ -3235,7 +3235,8 @@ fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - -- addAnnotation (gl (fbindToRecField $1)) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } @@ -3260,7 +3261,7 @@ fbind :: { forall b. DisambECP b => PV (Fbind b) } | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp { do $5 <- unECP $5 - fmap Pbind $ mkHsFieldUpdaterPV (comb2 $1 $5) ($1 : reverse $3) $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 } -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer @@ -3275,7 +3276,7 @@ fbind :: { forall b. DisambECP b => PV (Fbind b) } addError l $ text "For this to work, enable NamedFieldPuns." var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) - fmap Pbind $ mkHsFieldUpdaterPV l fields var + fmap Pbind $ mkHsProjUpdatePV l fields var } fieldToUpdate :: { [Located FastString] } ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,7 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( - mkGetField, mkProjection, mkFieldUpdater, isGetField, Fbind(..), -- RecordDot + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -153,16 +153,49 @@ import Data.Kind ( Type ) #include "HsVersions.h" -data Fbind b = - Fbind (LHsRecField GhcPs (Located b)) | Pbind (Located (Located b -> Located b)) - -fbindsToEithers :: [Fbind b] -> [Either (LHsRecField GhcPs (Located b)) (Located (Located b -> Located b))] +-- e.g. "foo.bar.baz = 42" is +-- ProjBind { +-- pb_fIELDS=["foo","bar","baz"] +-- , pb_exp=42 +-- , pb_func=\a -> setField@"foo" a .... 42 +-- } +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + , pb_func :: arg -> arg + } +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] fbindsToEithers = fmap fbindToEither where - fbindToEither :: Fbind b -> Either (LHsRecField GhcPs (Located b)) (Located (Located b -> Located b)) + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) fbindToEither (Fbind x) = Left x fbindToEither (Pbind x) = Right x +-- Next fix mkRdrRecordUpd' to return one of these. +-- RecordDotUpdate { +-- rdupd_ext :: XRecordDotUpdate +-- , rdupd_expr :: LHsExpr GhcPs +-- , rdupd_updates :: [LHsRecUpdProj GhcPs] +-- , rupd_setField :: LHsExpr GhcPs -- The equivalent setField term. +-- } +-- + {- ********************************************************************** Construction functions for Rdr stuff @@ -1397,7 +1430,7 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) -- | This can only be satified by expressions. - mkHsFieldUpdaterPV :: SrcSpan -> [Located FastString] -> Located b -> PV (Located (Located b -> Located b)) + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1525,7 +1558,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) - mkHsFieldUpdaterPV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1593,7 +1626,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return - mkHsFieldUpdaterPV l fields arg = return $ mkFieldUpdater l fields arg + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1681,7 +1714,7 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e - mkHsFieldUpdaterPV l _ _ = + mkHsProjUpdatePV l _ _ = addFatalError l $ text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ @@ -2376,7 +2409,7 @@ mkRecConstrOrUpdate dot exp _ (fs,dd) | otherwise = mkRdrRecordUpd' dot exp fs mkRdrRecordUpd' :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) -mkRdrRecordUpd' dot exp@(L lexp _) fbinds = +mkRdrRecordUpd' dot exp@(L _ _) fbinds = if not dot then do let (fs, ps) = partitionEithers $ fbindsToEithers fbinds @@ -2388,16 +2421,15 @@ mkRdrRecordUpd' dot exp@(L lexp _) fbinds = panic "mkRdrRecordUpd': The impossible happened!" else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) else - return $ foldl' fieldUpdate (unLoc exp) fbinds + return $ foldl' fieldUpdate (unLoc exp) (toProjUpdates fbinds) where - fieldUpdate :: HsExpr GhcPs -> Fbind (HsExpr GhcPs) -> HsExpr GhcPs - fieldUpdate acc f = - case f of - -- Remember to sort out issues with location info here. - Fbind field -> - let updField = fmap mk_rec_upd_field field - in unLoc $ foldl' mkSetField (noLoc acc) [updField] - Pbind (L _ fieldUpdater) -> unLoc (fieldUpdater (noLoc acc)) + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc (L _ pu) = unLoc ((pb_func pu) (noLoc acc)) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -3020,9 +3052,9 @@ mkProjection loc maybeRhs fIELD = mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b --- mkFieldUpdater calculates functions representing dot notation record updates. -mkFieldUpdater :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> Located (LHsExpr GhcPs -> LHsExpr GhcPs) -mkFieldUpdater -- e.g {foo.bar.baz.quux = 43} +-- mkProjUpdate calculates functions representing dot notation record updates. +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate -- e.g {foo.bar.baz.quux = 43} l fIELDS -- [foo, bar, baz, quux] arg -- This is 'texp' (43 in the example). @@ -3034,17 +3066,19 @@ mkFieldUpdater -- e.g {foo.bar.baz.quux = 43} ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] } - in L l $ \a -> foldl' mkSet' arg (zips a) + in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) where mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) --- Called from mkRdrRecordUpd. -mkSetField :: LHsExpr GhcPs -> LHsRecUpdField GhcPs -> LHsExpr GhcPs -mkSetField e (L _ (HsRecField occ arg _)) = - let (loc, f) = field occ in mkSet e (L loc (fsLit f)) (val arg) +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) where + (loc, f) = field occ + val :: LHsExpr GhcPs -> LHsExpr GhcPs val arg = if isPun arg then mkVar $ snd (field occ) else arg @@ -3057,7 +3091,3 @@ mkSetField e (L _ (HsRecField occ arg _)) = field = \case L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) - -applyFieldUpdates :: LHsExpr GhcPs -> [LHsExpr GhcPs -> LHsExpr GhcPs] -> P (LHsExpr GhcPs) -applyFieldUpdates a updates = return $ foldl' apply a updates - where apply r update = update r ===================================== record-dot-syntax-test.sh ===================================== @@ -15,7 +15,7 @@ tests=( \ test () { printf "make test TEST=$%s\n" $1 - make test TEST=$1 + make test TEST=$1 > /dev/null } for t in "${tests[@]}" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bcab57b7f4e598af68bfa3ecd1395f87f2676fe7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bcab57b7f4e598af68bfa3ecd1395f87f2676fe7 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 Sun Nov 8 16:16:45 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 08 Nov 2020 11:16:45 -0500 Subject: [Git][ghc/ghc][master] 87 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa819ed63200_10eeed21f8c6898fc@gitlab.haskell.org.mail> Ben Gamari pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 30 changed files: - .gitlab-ci.yml - configure.ac - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - + hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/Rts.h - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - + includes/rts/TSANUtils.h - includes/rts/storage/ClosureMacros.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - + rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Schedule.h - rts/Sparks.c - + rts/SpinLock.c - rts/StablePtr.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1d2c1f3246b3740589a59bdf7648c13de47c32b...638f38c50e80a19275f3a06535a0dd8130a17a53 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b1d2c1f3246b3740589a59bdf7648c13de47c32b...638f38c50e80a19275f3a06535a0dd8130a17a53 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 Sun Nov 8 17:09:14 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 08 Nov 2020 12:09:14 -0500 Subject: [Git][ghc/ghc][master] Fix haddock submodule Message-ID: <5fa8263a9ea79_10ee3ffb94dbdfb070021c@gitlab.haskell.org.mail> Ben Gamari pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 1 changed file: - utils/haddock Changes: ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 3cce1bdee8c61bb6daa089059e12435178f50770 +Subproject commit ad9cbad7312a64e6757c32bd9488c55ba4f2fec9 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/22888798d224f96202480595fc49bc5c4b2f8328 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/22888798d224f96202480595fc49bc5c4b2f8328 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 Mon Nov 9 00:13:48 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sun, 08 Nov 2020 19:13:48 -0500 Subject: [Git][ghc/ghc][wip/T18914] 89 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa889bc84cc5_10ee3ffbc95a85847259d3@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 638e08ac by Ryan Scott at 2020-11-08T19:12:06-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Hs/Type.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/Instance.hs - configure.ac - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - + hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/Rts.h - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - + includes/rts/TSANUtils.h - includes/rts/storage/ClosureMacros.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - + rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5da55a2d057cf2a534d316b620c3670f4a0b771...638e08ac0cfa6e1f5336a2d2ba72d2826d858f54 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5da55a2d057cf2a534d316b620c3670f4a0b771...638e08ac0cfa6e1f5336a2d2ba72d2826d858f54 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 Mon Nov 9 02:30:06 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Sun, 08 Nov 2020 21:30:06 -0500 Subject: [Git][ghc/ghc][wip/T18599] Simplify type Message-ID: <5fa8a9aeb502c_10ee3ffb9474ba74729968@gitlab.haskell.org.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 77f0052e by Shayne Fletcher at 2020-11-08T21:29:55-05:00 Simplify type - - - - - 1 changed file: - compiler/GHC/Parser/PostProcess.hs Changes: ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -3073,7 +3073,7 @@ mkProjUpdate -- e.g {foo.bar.baz.quux = 43} mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) -- Transform a regular record field update into a projection update. -recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = mkProjUpdate l [L loc (fsLit f)] (val arg) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/77f0052e00eae4f562254a6fcf49bfb4a80e407c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/77f0052e00eae4f562254a6fcf49bfb4a80e407c 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 Mon Nov 9 03:13:58 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Sun, 08 Nov 2020 22:13:58 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 95 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa8b3f695c86_10ee3ffb8d1039c0730317@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 15c871cb by Moritz Angermann at 2020-11-09T03:13:11+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 25 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Data/EnumSet.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/47c730496002bd4cb4bcbddf7416482a02556c50...15c871cb3e706b5861ee80be5af7d1255d3ae46f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/47c730496002bd4cb4bcbddf7416482a02556c50...15c871cb3e706b5861ee80be5af7d1255d3ae46f 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 Mon Nov 9 04:26:20 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Sun, 08 Nov 2020 23:26:20 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] 43 commits: hadrian: Don't quote metric baseline argument Message-ID: <5fa8c4ec16740_10ee3ffb8d8e5d64733611@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 344a7ca1 by Daniel Rogozin at 2020-11-09T07:25:59+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1688d5a8639338653e59e8591f3a3b90817d35f...344a7ca168963b0037129cb63b748023c8d9900a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1688d5a8639338653e59e8591f3a3b90817d35f...344a7ca168963b0037129cb63b748023c8d9900a 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 Mon Nov 9 04:28:07 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Sun, 08 Nov 2020 23:28:07 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] 89 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa8c557227d9_10ee3ffbaf758808734528@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - ef21bcc3 by Daniel Rogozin at 2020-11-09T07:27:44+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - configure.ac - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/344a7ca168963b0037129cb63b748023c8d9900a...ef21bcc39b676b405776d33b61a0996b29881c23 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/344a7ca168963b0037129cb63b748023c8d9900a...ef21bcc39b676b405776d33b61a0996b29881c23 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 Mon Nov 9 04:32:53 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Sun, 08 Nov 2020 23:32:53 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fa8c675f032d_10ee3ffb98bda9107354e@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 2c1793a2 by Daniel Rogozin at 2020-11-09T07:32:20+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs - libraries/template-haskell/Language/Haskell/TH/Lib.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2c1793a288cbf22dfd368526f93c6ab504d90257 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2c1793a288cbf22dfd368526f93c6ab504d90257 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 Mon Nov 9 06:08:18 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Mon, 09 Nov 2020 01:08:18 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fa8dcd292519_10ee3ffbad70a7047398fb@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: f492e34e by Daniel Rogozin at 2020-11-09T09:07:47+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f492e34e4b8e7f1a6707e3f34c3f03e6c250f86c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f492e34e4b8e7f1a6707e3f34c3f03e6c250f86c 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 Mon Nov 9 06:20:19 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Mon, 09 Nov 2020 01:20:19 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fa8dfa36ec32_10ee10d5d120740732@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: d6bec836 by Daniel Rogozin at 2020-11-09T09:19:43+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d6bec8360396aae267338c54ee23c600aa31eebd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d6bec8360396aae267338c54ee23c600aa31eebd 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 Mon Nov 9 07:12:48 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Mon, 09 Nov 2020 02:12:48 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fa8ebf053367_10ee3ffbae09955474329f@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: ff0a359e by Daniel Rogozin at 2020-11-09T10:12:15+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ff0a359e95c30e67f1a63c243c1510295ddbbebb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ff0a359e95c30e67f1a63c243c1510295ddbbebb 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 Mon Nov 9 08:44:55 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Mon, 09 Nov 2020 03:44:55 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fa90187a8793_10ee3ffbac090be07461e0@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 656cc70e by Daniel Rogozin at 2020-11-09T11:44:33+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/656cc70e20e2cde873081228402ef317e5999b57 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/656cc70e20e2cde873081228402ef317e5999b57 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 Mon Nov 9 11:05:02 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Mon, 09 Nov 2020 06:05:02 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_gc_roots] Add rts_listThreads and rts_listMiscRoots to RtsAPI.h Message-ID: <5fa9225ea8157_10ee10e225887634b@gitlab.haskell.org.mail> David Eichmann pushed to branch wip/ghc-debug_gc_roots at Glasgow Haskell Compiler / GHC Commits: b624c806 by David Eichmann at 2020-11-09T11:02:32+00:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 6 changed files: - includes/RtsAPI.h - rts/RtsAPI.c - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -17,8 +17,10 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" +#include "rts/Types.h" #include "rts/EventLogWriter.h" + /* * Running the scheduler */ @@ -566,6 +568,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== rts/RtsAPI.c ===================================== @@ -15,6 +15,7 @@ #include "Prelude.h" #include "Schedule.h" #include "Capability.h" +#include "StableName.h" #include "StablePtr.h" #include "Threads.h" #include "Weak.h" @@ -809,6 +810,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +874,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b624c806746d6b375ade398a13695f5e2294b083 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b624c806746d6b375ade398a13695f5e2294b083 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 Mon Nov 9 13:00:50 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Mon, 09 Nov 2020 08:00:50 -0500 Subject: [Git][ghc/ghc][wip/T18891] 89 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa93d82bb719_10ee3ffbacfe124877742c@gitlab.haskell.org.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - df83bf7b by Simon Peyton Jones at 2020-11-09T13:00:20+00:00 Fix kind inference for data types. Again. This patch improves kcConDecls, when we are inferring the kind of a data type decl. Fixes #18891 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - configure.ac - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - + hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/Rts.h - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - + includes/rts/TSANUtils.h - includes/rts/storage/ClosureMacros.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - + rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Schedule.h - rts/Sparks.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae91a8279e2ece465a1b174da90c972c9027e218...df83bf7bf5ab3bc9e3bb9fac5c91e37064d68b5f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ae91a8279e2ece465a1b174da90c972c9027e218...df83bf7bf5ab3bc9e3bb9fac5c91e37064d68b5f 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 Mon Nov 9 14:10:56 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Mon, 09 Nov 2020 09:10:56 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T10504 Message-ID: <5fa94df02218f_10eea7438e4811816@gitlab.haskell.org.mail> Ryan Scott pushed new branch wip/T10504 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T10504 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 Mon Nov 9 16:10:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 11:10:30 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/backports Message-ID: <5fa969f67697a_10ee3ffb941761308448d2@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/backports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports 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 Mon Nov 9 16:27:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 11:27:12 -0500 Subject: [Git][ghc/ghc][wip/backports] 15 commits: winio: Fix unused variables warnings Message-ID: <5fa96de0cd309_10ee634d89c854580@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/backports at Glasgow Haskell Compiler / GHC Commits: ed1699b2 by Tamar Christina at 2020-11-09T11:11:52-05:00 winio: Fix unused variables warnings (cherry picked from commit cb1f755c6fb77f140aee11fdc7b4da04dd5dcd02) - - - - - 0736b4e3 by Simon Peyton Jones at 2020-11-09T11:13:57-05:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion (cherry picked from commit 0b3d23afcad8bc14f2ba69b8dbe05c314e6e7b29) - - - - - 6c1cf280 by Tamar Christina at 2020-11-09T11:17:24-05:00 winio: simplify logic remove optimization step. (cherry picked from commit 412018c1214a19649e0ccfff73e80a0622635dd5) - - - - - 57a79fc5 by Sylvain Henry at 2020-11-09T11:18:36-05:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 (cherry picked from commit e393f213f5ccff4fd6034d5294e51aa5a2720890) - - - - - fd5305c4 by David Beacham at 2020-11-09T11:19:16-05:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog (cherry picked from commit 9ad51bc9d2ad9168abad271f715ce73d3562218a) - - - - - 55f677ea by Sylvain Henry at 2020-11-09T11:21:24-05:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a (cherry picked from commit 17d2f0a886f9f56ea408d2dd8b7f054021da19a4) - - - - - 1ce75069 by Vladislav Zavialov at 2020-11-09T11:21:52-05:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. (cherry picked from commit bf2411a3c198cb2df93a9e0aa0c3b8297f47058d) - - - - - 2888486f by Ben Gamari at 2020-11-09T11:22:20-05:00 Bump win32-tarballs version to 0.3 This should fix #18774. (cherry picked from commit e5c7c9c8578de1248826c21ebd08e475d094a552) - - - - - 74d25509 by Ben Gamari at 2020-11-09T11:22:32-05:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. (cherry picked from commit a848d52748c09a27ed5bef0fb039c51656bebdf1) - - - - - 8506ae3f by Tamar Christina at 2020-11-09T11:22:56-05:00 winio: fixed bytestring reading interface. (cherry picked from commit 0fd3d360cab977e00fb6d90d0519962227b029bb) - - - - - c95752a3 by Tamar Christina at 2020-11-09T11:23:26-05:00 winio: fixed more data error. (cherry picked from commit dfaef1cae7a4a0cb8783933274dae7f39d7165a0) - - - - - b5f0b0f2 by Tamar Christina at 2020-11-09T11:23:42-05:00 winio: fix array splat (cherry picked from commit 6f0243ae5b359124936a8ff3dd0a287df3d7aca2) - - - - - f02cea02 by Tamar Christina at 2020-11-09T11:23:49-05:00 winio: fixed timeouts non-threaded. (cherry picked from commit c832f7e2a9314cfd61257cb161b1795b612d12b5) - - - - - 9ac19401 by Andreas Klebinger at 2020-11-09T11:24:12-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) - - - - - e57ea51e by Alan Zimmerman at 2020-11-09T11:26:02-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 (cherry picked from commit 616bec0dee67ae4841c4e60e9406cc9c63358223) - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Flatten.hs - configure.ac - libraries/base/Data/Maybe.hs - libraries/base/Data/Ord.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/Event/Windows.hsc - libraries/base/GHC/IO/Handle/Text.hs - libraries/base/GHC/IO/Windows/Handle.hsc - libraries/base/changelog.md - libraries/base/tests/IO/all.T - + libraries/base/tests/IO/bytestringread001.hs - + libraries/base/tests/IO/bytestringread001.stdout - mk/get-win32-tarballs.py - rts/win32/AsyncWinIO.c - rts/win32/AsyncWinIO.h - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bba8f79c7e933c312ca251469b99d0ac99954e16...e57ea51ec6d774d9c86feac171e6a8c4a73aacb2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bba8f79c7e933c312ca251469b99d0ac99954e16...e57ea51ec6d774d9c86feac171e6a8c4a73aacb2 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 Mon Nov 9 17:09:46 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 12:09:46 -0500 Subject: [Git][ghc/ghc][wip/bump-time] 114 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa977dac30bf_10ee3ffbad5d8a34857569@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - ad2e5f6d by Ben Gamari at 2020-11-09T12:08:50-05:00 Bump time submodule to 1.11 Closes #18847. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6fe6d014faa71dea36a38bf366ef2e8402e3bd0d...ad2e5f6d3700807855b7cd32246be6278e89e20d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6fe6d014faa71dea36a38bf366ef2e8402e3bd0d...ad2e5f6d3700807855b7cd32246be6278e89e20d 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 Mon Nov 9 17:50:03 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 09 Nov 2020 12:50:03 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 3 commits: Fix ghc/alloc regression in T18304 Message-ID: <5fa9814b8cdcd_10ee3ffbadcd5cc488755@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 87756685 by Sebastian Graf at 2020-11-06T10:45:54+01:00 Fix ghc/alloc regression in T18304 - - - - - 6c1a0862 by Sebastian Graf at 2020-11-06T20:40:14+01:00 Preserve changes - - - - - cd8d2efd by Sebastian Graf at 2020-11-09T18:48:09+01:00 Change Outputable instance + big refactor of GHC.Types.Demand - - - - - 12 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Types/Demand.hs - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92100176af696871b868ac41dad94de09a73c70b...cd8d2efd3eb41d92171df7a01f3e23ffbf082520 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/92100176af696871b868ac41dad94de09a73c70b...cd8d2efd3eb41d92171df7a01f3e23ffbf082520 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 Mon Nov 9 18:01:35 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 09 Nov 2020 13:01:35 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] Remove weird test output Message-ID: <5fa983ff74be6_10ee3ffbad45c41c8937b@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 3b7672d9 by Sebastian Graf at 2020-11-09T19:01:25+01:00 Remove weird test output - - - - - 2 changed files: - compiler/GHC/Types/Demand.hs - − testsuite/tests/ghci/scripts/ghci014.stderr Changes: ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -1682,12 +1682,12 @@ seqStrictSig (StrictSig ty) = seqDmdType ty -} instance Outputable Card where - ppr C_00 = char 'a' + ppr C_00 = char 'A' ppr C_01 = char '1' - ppr C_0N = char 'u' - ppr C_11 = char 's' - ppr C_1N = char 'm' - ppr C_10 = char 'b' + ppr C_0N = char 'U' + ppr C_11 = char 'S' + ppr C_1N = char 'M' + ppr C_10 = char 'B' instance Outputable Demand where ppr dmd@(n :* sd) ===================================== testsuite/tests/ghci/scripts/ghci014.stderr deleted ===================================== @@ -1,1968 +0,0 @@ - -ghci014.hs:2:1: error: - Could not find module ‘Test.QuickCheck.Batch’ - Use -v (or `:set -v` in ghci) to see a list of the files searched for. - -:2:1: error: Variable not in scope: do_test - -:3:1: error: Variable not in scope: do_test - -:4:1: error: Variable not in scope: do_test - -:5:1: error: Variable not in scope: do_test - -:6:1: error: Variable not in scope: do_test - -:7:1: error: Variable not in scope: do_test - -:8:1: error: Variable not in scope: do_test - -:9:1: error: Variable not in scope: do_test - -:10:1: error: Variable not in scope: do_test - -:11:1: error: Variable not in scope: do_test - -:12:1: error: Variable not in scope: do_test - -:13:1: error: Variable not in scope: do_test - -:14:1: error: Variable not in scope: do_test - -:15:1: error: Variable not in scope: do_test - -:16:1: error: Variable not in scope: do_test - -:17:1: error: Variable not in scope: do_test - -:18:1: error: Variable not in scope: do_test - -:19:1: error: Variable not in scope: do_test - -:20:1: error: Variable not in scope: do_test - -:21:1: error: Variable not in scope: do_test - -:22:1: error: Variable not in scope: do_test - -:23:1: error: Variable not in scope: do_test - -:24:1: error: Variable not in scope: do_test - -:25:1: error: Variable not in scope: do_test - -:26:1: error: Variable not in scope: do_test - -:27:1: error: Variable not in scope: do_test - -:28:1: error: Variable not in scope: do_test - -:29:1: error: Variable not in scope: do_test - -:30:1: error: Variable not in scope: do_test - -:31:1: error: Variable not in scope: do_test - -:32:1: error: Variable not in scope: do_test - -:33:1: error: Variable not in scope: do_test - -:34:1: error: Variable not in scope: do_test - -:35:1: error: Variable not in scope: do_test - -:36:1: error: Variable not in scope: do_test - -:37:1: error: Variable not in scope: do_test - -:38:1: error: Variable not in scope: do_test - -:39:1: error: Variable not in scope: do_test - -:40:1: error: Variable not in scope: do_test - -:41:1: error: Variable not in scope: do_test - -:42:1: error: Variable not in scope: do_test - -:43:1: error: Variable not in scope: do_test - -:44:1: error: Variable not in scope: do_test - -:45:1: error: Variable not in scope: do_test - -:46:1: error: Variable not in scope: do_test - -:47:1: error: Variable not in scope: do_test - -:48:1: error: Variable not in scope: do_test - -:49:1: error: Variable not in scope: do_test - -:50:1: error: Variable not in scope: do_test - -:51:1: error: Variable not in scope: do_test - -:52:1: error: Variable not in scope: do_test - -:53:1: error: Variable not in scope: do_test - -:54:1: error: Variable not in scope: do_test - -:55:1: error: Variable not in scope: do_test - -:56:1: error: Variable not in scope: do_test - -:57:1: error: Variable not in scope: do_test - -:58:1: error: Variable not in scope: do_test - -:59:1: error: Variable not in scope: do_test - -:60:1: error: Variable not in scope: do_test - -:61:1: error: Variable not in scope: do_test - -:62:1: error: Variable not in scope: do_test - -:63:1: error: Variable not in scope: do_test - -:64:1: error: Variable not in scope: do_test - -:65:1: error: Variable not in scope: do_test - -:66:1: error: Variable not in scope: do_test - -:67:1: error: Variable not in scope: do_test - -:68:1: error: Variable not in scope: do_test - -:69:1: error: Variable not in scope: do_test - -:70:1: error: Variable not in scope: do_test - -:71:1: error: Variable not in scope: do_test - -:72:1: error: Variable not in scope: do_test - -:73:1: error: Variable not in scope: do_test - -:74:1: error: Variable not in scope: do_test - -:75:1: error: Variable not in scope: do_test - -:76:1: error: Variable not in scope: do_test - -:77:1: error: Variable not in scope: do_test - -:78:1: error: Variable not in scope: do_test - -:79:1: error: Variable not in scope: do_test - -:80:1: error: Variable not in scope: do_test - -:81:1: error: Variable not in scope: do_test - -:82:1: error: Variable not in scope: do_test - -:83:1: error: Variable not in scope: do_test - -:84:1: error: Variable not in scope: do_test - -:85:1: error: Variable not in scope: do_test - -:86:1: error: Variable not in scope: do_test - -:87:1: error: Variable not in scope: do_test - -:88:1: error: Variable not in scope: do_test - -:89:1: error: Variable not in scope: do_test - -:90:1: error: Variable not in scope: do_test - -:91:1: error: Variable not in scope: do_test - -:92:1: error: Variable not in scope: do_test - -:93:1: error: Variable not in scope: do_test - -:94:1: error: Variable not in scope: do_test - -:95:1: error: Variable not in scope: do_test - -:96:1: error: Variable not in scope: do_test - -:97:1: error: Variable not in scope: do_test - -:98:1: error: Variable not in scope: do_test - -:99:1: error: Variable not in scope: do_test - -:100:1: error: Variable not in scope: do_test - -:101:1: error: Variable not in scope: do_test - -:102:1: error: Variable not in scope: do_test - -:103:1: error: Variable not in scope: do_test - -:104:1: error: Variable not in scope: do_test - -:105:1: error: Variable not in scope: do_test - -:106:1: error: Variable not in scope: do_test - -:107:1: error: Variable not in scope: do_test - -:108:1: error: Variable not in scope: do_test - -:109:1: error: Variable not in scope: do_test - -:110:1: error: Variable not in scope: do_test - -:111:1: error: Variable not in scope: do_test - -:112:1: error: Variable not in scope: do_test - -:113:1: error: Variable not in scope: do_test - -:114:1: error: Variable not in scope: do_test - -:115:1: error: Variable not in scope: do_test - -:116:1: error: Variable not in scope: do_test - -:117:1: error: Variable not in scope: do_test - -:118:1: error: Variable not in scope: do_test - -:119:1: error: Variable not in scope: do_test - -:120:1: error: Variable not in scope: do_test - -:121:1: error: Variable not in scope: do_test - -:122:1: error: Variable not in scope: do_test - -:123:1: error: Variable not in scope: do_test - -:124:1: error: Variable not in scope: do_test - -:125:1: error: Variable not in scope: do_test - -:126:1: error: Variable not in scope: do_test - -:127:1: error: Variable not in scope: do_test - -:128:1: error: Variable not in scope: do_test - -:129:1: error: Variable not in scope: do_test - -:130:1: error: Variable not in scope: do_test - -:131:1: error: Variable not in scope: do_test - -:132:1: error: Variable not in scope: do_test - -:133:1: error: Variable not in scope: do_test - -:134:1: error: Variable not in scope: do_test - -:135:1: error: Variable not in scope: do_test - -:136:1: error: Variable not in scope: do_test - -:137:1: error: Variable not in scope: do_test - -:138:1: error: Variable not in scope: do_test - -:139:1: error: Variable not in scope: do_test - -:140:1: error: Variable not in scope: do_test - -:141:1: error: Variable not in scope: do_test - -:142:1: error: Variable not in scope: do_test - -:143:1: error: Variable not in scope: do_test - -:144:1: error: Variable not in scope: do_test - -:145:1: error: Variable not in scope: do_test - -:146:1: error: Variable not in scope: do_test - -:147:1: error: Variable not in scope: do_test - -:148:1: error: Variable not in scope: do_test - -:149:1: error: Variable not in scope: do_test - -:150:1: error: Variable not in scope: do_test - -:151:1: error: Variable not in scope: do_test - -:152:1: error: Variable not in scope: do_test - -:153:1: error: Variable not in scope: do_test - -:154:1: error: Variable not in scope: do_test - -:155:1: error: Variable not in scope: do_test - -:156:1: error: Variable not in scope: do_test - -:157:1: error: Variable not in scope: do_test - -:158:1: error: Variable not in scope: do_test - -:159:1: error: Variable not in scope: do_test - -:160:1: error: Variable not in scope: do_test - -:161:1: error: Variable not in scope: do_test - -:162:1: error: Variable not in scope: do_test - -:163:1: error: Variable not in scope: do_test - -:164:1: error: Variable not in scope: do_test - -:165:1: error: Variable not in scope: do_test - -:166:1: error: Variable not in scope: do_test - -:167:1: error: Variable not in scope: do_test - -:168:1: error: Variable not in scope: do_test - -:169:1: error: Variable not in scope: do_test - -:170:1: error: Variable not in scope: do_test - -:171:1: error: Variable not in scope: do_test - -:172:1: error: Variable not in scope: do_test - -:173:1: error: Variable not in scope: do_test - -:174:1: error: Variable not in scope: do_test - -:175:1: error: Variable not in scope: do_test - -:176:1: error: Variable not in scope: do_test - -:177:1: error: Variable not in scope: do_test - -:178:1: error: Variable not in scope: do_test - -:179:1: error: Variable not in scope: do_test - -:180:1: error: Variable not in scope: do_test - -:181:1: error: Variable not in scope: do_test - -:182:1: error: Variable not in scope: do_test - -:183:1: error: Variable not in scope: do_test - -:184:1: error: Variable not in scope: do_test - -:185:1: error: Variable not in scope: do_test - -:186:1: error: Variable not in scope: do_test - -:187:1: error: Variable not in scope: do_test - -:188:1: error: Variable not in scope: do_test - -:189:1: error: Variable not in scope: do_test - -:190:1: error: Variable not in scope: do_test - -:191:1: error: Variable not in scope: do_test - -:192:1: error: Variable not in scope: do_test - -:193:1: error: Variable not in scope: do_test - -:194:1: error: Variable not in scope: do_test - -:195:1: error: Variable not in scope: do_test - -:196:1: error: Variable not in scope: do_test - -:197:1: error: Variable not in scope: do_test - -:198:1: error: Variable not in scope: do_test - -:199:1: error: Variable not in scope: do_test - -:200:1: error: Variable not in scope: do_test - -:201:1: error: Variable not in scope: do_test - -:202:1: error: Variable not in scope: do_test - -:203:1: error: Variable not in scope: do_test - -:204:1: error: Variable not in scope: do_test - -:205:1: error: Variable not in scope: do_test - -:206:1: error: Variable not in scope: do_test - -:207:1: error: Variable not in scope: do_test - -:208:1: error: Variable not in scope: do_test - -:209:1: error: Variable not in scope: do_test - -:210:1: error: Variable not in scope: do_test - -:211:1: error: Variable not in scope: do_test - -:212:1: error: Variable not in scope: do_test - -:213:1: error: Variable not in scope: do_test - -:214:1: error: Variable not in scope: do_test - -:215:1: error: Variable not in scope: do_test - -:216:1: error: Variable not in scope: do_test - -:217:1: error: Variable not in scope: do_test - -:218:1: error: Variable not in scope: do_test - -:219:1: error: Variable not in scope: do_test - -:220:1: error: Variable not in scope: do_test - -:221:1: error: Variable not in scope: do_test - -:222:1: error: Variable not in scope: do_test - -:223:1: error: Variable not in scope: do_test - -:224:1: error: Variable not in scope: do_test - -:225:1: error: Variable not in scope: do_test - -:226:1: error: Variable not in scope: do_test - -:227:1: error: Variable not in scope: do_test - -:228:1: error: Variable not in scope: do_test - -:229:1: error: Variable not in scope: do_test - -:230:1: error: Variable not in scope: do_test - -:231:1: error: Variable not in scope: do_test - -:232:1: error: Variable not in scope: do_test - -:233:1: error: Variable not in scope: do_test - -:234:1: error: Variable not in scope: do_test - -:235:1: error: Variable not in scope: do_test - -:236:1: error: Variable not in scope: do_test - -:237:1: error: Variable not in scope: do_test - -:238:1: error: Variable not in scope: do_test - -:239:1: error: Variable not in scope: do_test - -:240:1: error: Variable not in scope: do_test - -:241:1: error: Variable not in scope: do_test - -:242:1: error: Variable not in scope: do_test - -:243:1: error: Variable not in scope: do_test - -:244:1: error: Variable not in scope: do_test - -:245:1: error: Variable not in scope: do_test - -:246:1: error: Variable not in scope: do_test - -:247:1: error: Variable not in scope: do_test - -:248:1: error: Variable not in scope: do_test - -:249:1: error: Variable not in scope: do_test - -:250:1: error: Variable not in scope: do_test - -:251:1: error: Variable not in scope: do_test - -:252:1: error: Variable not in scope: do_test - -:253:1: error: Variable not in scope: do_test - -:254:1: error: Variable not in scope: do_test - -:255:1: error: Variable not in scope: do_test - -:256:1: error: Variable not in scope: do_test - -:257:1: error: Variable not in scope: do_test - -:258:1: error: Variable not in scope: do_test - -:259:1: error: Variable not in scope: do_test - -:260:1: error: Variable not in scope: do_test - -:261:1: error: Variable not in scope: do_test - -:262:1: error: Variable not in scope: do_test - -:263:1: error: Variable not in scope: do_test - -:264:1: error: Variable not in scope: do_test - -:265:1: error: Variable not in scope: do_test - -:266:1: error: Variable not in scope: do_test - -:267:1: error: Variable not in scope: do_test - -:268:1: error: Variable not in scope: do_test - -:269:1: error: Variable not in scope: do_test - -:270:1: error: Variable not in scope: do_test - -:271:1: error: Variable not in scope: do_test - -:272:1: error: Variable not in scope: do_test - -:273:1: error: Variable not in scope: do_test - -:274:1: error: Variable not in scope: do_test - -:275:1: error: Variable not in scope: do_test - -:276:1: error: Variable not in scope: do_test - -:277:1: error: Variable not in scope: do_test - -:278:1: error: Variable not in scope: do_test - -:279:1: error: Variable not in scope: do_test - -:280:1: error: Variable not in scope: do_test - -:281:1: error: Variable not in scope: do_test - -:282:1: error: Variable not in scope: do_test - -:283:1: error: Variable not in scope: do_test - -:284:1: error: Variable not in scope: do_test - -:285:1: error: Variable not in scope: do_test - -:286:1: error: Variable not in scope: do_test - -:287:1: error: Variable not in scope: do_test - -:288:1: error: Variable not in scope: do_test - -:289:1: error: Variable not in scope: do_test - -:290:1: error: Variable not in scope: do_test - -:291:1: error: Variable not in scope: do_test - -:292:1: error: Variable not in scope: do_test - -:293:1: error: Variable not in scope: do_test - -:294:1: error: Variable not in scope: do_test - -:295:1: error: Variable not in scope: do_test - -:296:1: error: Variable not in scope: do_test - -:297:1: error: Variable not in scope: do_test - -:298:1: error: Variable not in scope: do_test - -:299:1: error: Variable not in scope: do_test - -:300:1: error: Variable not in scope: do_test - -:301:1: error: Variable not in scope: do_test - -:302:1: error: Variable not in scope: do_test - -:303:1: error: Variable not in scope: do_test - -:304:1: error: Variable not in scope: do_test - -:305:1: error: Variable not in scope: do_test - -:306:1: error: Variable not in scope: do_test - -:307:1: error: Variable not in scope: do_test - -:308:1: error: Variable not in scope: do_test - -:309:1: error: Variable not in scope: do_test - -:310:1: error: Variable not in scope: do_test - -:311:1: error: Variable not in scope: do_test - -:312:1: error: Variable not in scope: do_test - -:313:1: error: Variable not in scope: do_test - -:314:1: error: Variable not in scope: do_test - -:315:1: error: Variable not in scope: do_test - -:316:1: error: Variable not in scope: do_test - -:317:1: error: Variable not in scope: do_test - -:318:1: error: Variable not in scope: do_test - -:319:1: error: Variable not in scope: do_test - -:320:1: error: Variable not in scope: do_test - -:321:1: error: Variable not in scope: do_test - -:322:1: error: Variable not in scope: do_test - -:323:1: error: Variable not in scope: do_test - -:324:1: error: Variable not in scope: do_test - -:325:1: error: Variable not in scope: do_test - -:326:1: error: Variable not in scope: do_test - -:327:1: error: Variable not in scope: do_test - -:328:1: error: Variable not in scope: do_test - -:329:1: error: Variable not in scope: do_test - -:330:1: error: Variable not in scope: do_test - -:331:1: error: Variable not in scope: do_test - -:332:1: error: Variable not in scope: do_test - -:333:1: error: Variable not in scope: do_test - -:334:1: error: Variable not in scope: do_test - -:335:1: error: Variable not in scope: do_test - -:336:1: error: Variable not in scope: do_test - -:337:1: error: Variable not in scope: do_test - -:338:1: error: Variable not in scope: do_test - -:339:1: error: Variable not in scope: do_test - -:340:1: error: Variable not in scope: do_test - -:341:1: error: Variable not in scope: do_test - -:342:1: error: Variable not in scope: do_test - -:343:1: error: Variable not in scope: do_test - -:344:1: error: Variable not in scope: do_test - -:345:1: error: Variable not in scope: do_test - -:346:1: error: Variable not in scope: do_test - -:347:1: error: Variable not in scope: do_test - -:348:1: error: Variable not in scope: do_test - -:349:1: error: Variable not in scope: do_test - -:350:1: error: Variable not in scope: do_test - -:351:1: error: Variable not in scope: do_test - -:352:1: error: Variable not in scope: do_test - -:353:1: error: Variable not in scope: do_test - -:354:1: error: Variable not in scope: do_test - -:355:1: error: Variable not in scope: do_test - -:356:1: error: Variable not in scope: do_test - -:357:1: error: Variable not in scope: do_test - -:358:1: error: Variable not in scope: do_test - -:359:1: error: Variable not in scope: do_test - -:360:1: error: Variable not in scope: do_test - -:361:1: error: Variable not in scope: do_test - -:362:1: error: Variable not in scope: do_test - -:363:1: error: Variable not in scope: do_test - -:364:1: error: Variable not in scope: do_test - -:365:1: error: Variable not in scope: do_test - -:366:1: error: Variable not in scope: do_test - -:367:1: error: Variable not in scope: do_test - -:368:1: error: Variable not in scope: do_test - -:369:1: error: Variable not in scope: do_test - -:370:1: error: Variable not in scope: do_test - -:371:1: error: Variable not in scope: do_test - -:372:1: error: Variable not in scope: do_test - -:373:1: error: Variable not in scope: do_test - -:374:1: error: Variable not in scope: do_test - -:375:1: error: Variable not in scope: do_test - -:376:1: error: Variable not in scope: do_test - -:377:1: error: Variable not in scope: do_test - -:378:1: error: Variable not in scope: do_test - -:379:1: error: Variable not in scope: do_test - -:380:1: error: Variable not in scope: do_test - -:381:1: error: Variable not in scope: do_test - -:382:1: error: Variable not in scope: do_test - -:383:1: error: Variable not in scope: do_test - -:384:1: error: Variable not in scope: do_test - -:385:1: error: Variable not in scope: do_test - -:386:1: error: Variable not in scope: do_test - -:387:1: error: Variable not in scope: do_test - -:388:1: error: Variable not in scope: do_test - -:389:1: error: Variable not in scope: do_test - -:390:1: error: Variable not in scope: do_test - -:391:1: error: Variable not in scope: do_test - -:392:1: error: Variable not in scope: do_test - -:393:1: error: Variable not in scope: do_test - -:394:1: error: Variable not in scope: do_test - -:395:1: error: Variable not in scope: do_test - -:396:1: error: Variable not in scope: do_test - -:397:1: error: Variable not in scope: do_test - -:398:1: error: Variable not in scope: do_test - -:399:1: error: Variable not in scope: do_test - -:400:1: error: Variable not in scope: do_test - -:401:1: error: Variable not in scope: do_test - -:402:1: error: Variable not in scope: do_test - -:403:1: error: Variable not in scope: do_test - -:404:1: error: Variable not in scope: do_test - -:405:1: error: Variable not in scope: do_test - -:406:1: error: Variable not in scope: do_test - -:407:1: error: Variable not in scope: do_test - -:408:1: error: Variable not in scope: do_test - -:409:1: error: Variable not in scope: do_test - -:410:1: error: Variable not in scope: do_test - -:411:1: error: Variable not in scope: do_test - -:412:1: error: Variable not in scope: do_test - -:413:1: error: Variable not in scope: do_test - -:414:1: error: Variable not in scope: do_test - -:415:1: error: Variable not in scope: do_test - -:416:1: error: Variable not in scope: do_test - -:417:1: error: Variable not in scope: do_test - -:418:1: error: Variable not in scope: do_test - -:419:1: error: Variable not in scope: do_test - -:420:1: error: Variable not in scope: do_test - -:421:1: error: Variable not in scope: do_test - -:422:1: error: Variable not in scope: do_test - -:423:1: error: Variable not in scope: do_test - -:424:1: error: Variable not in scope: do_test - -:425:1: error: Variable not in scope: do_test - -:426:1: error: Variable not in scope: do_test - -:427:1: error: Variable not in scope: do_test - -:428:1: error: Variable not in scope: do_test - -:429:1: error: Variable not in scope: do_test - -:430:1: error: Variable not in scope: do_test - -:431:1: error: Variable not in scope: do_test - -:432:1: error: Variable not in scope: do_test - -:433:1: error: Variable not in scope: do_test - -:434:1: error: Variable not in scope: do_test - -:435:1: error: Variable not in scope: do_test - -:436:1: error: Variable not in scope: do_test - -:437:1: error: Variable not in scope: do_test - -:438:1: error: Variable not in scope: do_test - -:439:1: error: Variable not in scope: do_test - -:440:1: error: Variable not in scope: do_test - -:441:1: error: Variable not in scope: do_test - -:442:1: error: Variable not in scope: do_test - -:443:1: error: Variable not in scope: do_test - -:444:1: error: Variable not in scope: do_test - -:445:1: error: Variable not in scope: do_test - -:446:1: error: Variable not in scope: do_test - -:447:1: error: Variable not in scope: do_test - -:448:1: error: Variable not in scope: do_test - -:449:1: error: Variable not in scope: do_test - -:450:1: error: Variable not in scope: do_test - -:451:1: error: Variable not in scope: do_test - -:452:1: error: Variable not in scope: do_test - -:453:1: error: Variable not in scope: do_test - -:454:1: error: Variable not in scope: do_test - -:455:1: error: Variable not in scope: do_test - -:456:1: error: Variable not in scope: do_test - -:457:1: error: Variable not in scope: do_test - -:458:1: error: Variable not in scope: do_test - -:459:1: error: Variable not in scope: do_test - -:460:1: error: Variable not in scope: do_test - -:461:1: error: Variable not in scope: do_test - -:462:1: error: Variable not in scope: do_test - -:463:1: error: Variable not in scope: do_test - -:464:1: error: Variable not in scope: do_test - -:465:1: error: Variable not in scope: do_test - -:466:1: error: Variable not in scope: do_test - -:467:1: error: Variable not in scope: do_test - -:468:1: error: Variable not in scope: do_test - -:469:1: error: Variable not in scope: do_test - -:470:1: error: Variable not in scope: do_test - -:471:1: error: Variable not in scope: do_test - -:472:1: error: Variable not in scope: do_test - -:473:1: error: Variable not in scope: do_test - -:474:1: error: Variable not in scope: do_test - -:475:1: error: Variable not in scope: do_test - -:476:1: error: Variable not in scope: do_test - -:477:1: error: Variable not in scope: do_test - -:478:1: error: Variable not in scope: do_test - -:479:1: error: Variable not in scope: do_test - -:480:1: error: Variable not in scope: do_test - -:481:1: error: Variable not in scope: do_test - -:482:1: error: Variable not in scope: do_test - -:483:1: error: Variable not in scope: do_test - -:484:1: error: Variable not in scope: do_test - -:485:1: error: Variable not in scope: do_test - -:486:1: error: Variable not in scope: do_test - -:487:1: error: Variable not in scope: do_test - -:488:1: error: Variable not in scope: do_test - -:489:1: error: Variable not in scope: do_test - -:490:1: error: Variable not in scope: do_test - -:491:1: error: Variable not in scope: do_test - -:492:1: error: Variable not in scope: do_test - -:493:1: error: Variable not in scope: do_test - -:494:1: error: Variable not in scope: do_test - -:495:1: error: Variable not in scope: do_test - -:496:1: error: Variable not in scope: do_test - -:497:1: error: Variable not in scope: do_test - -:498:1: error: Variable not in scope: do_test - -:499:1: error: Variable not in scope: do_test - -:500:1: error: Variable not in scope: do_test - -:501:1: error: Variable not in scope: do_test - -:502:1: error: Variable not in scope: do_test - -:503:1: error: Variable not in scope: do_test - -:504:1: error: Variable not in scope: do_test - -:505:1: error: Variable not in scope: do_test - -:506:1: error: Variable not in scope: do_test - -:507:1: error: Variable not in scope: do_test - -:508:1: error: Variable not in scope: do_test - -:509:1: error: Variable not in scope: do_test - -:510:1: error: Variable not in scope: do_test - -:511:1: error: Variable not in scope: do_test - -:512:1: error: Variable not in scope: do_test - -:513:1: error: Variable not in scope: do_test - -:514:1: error: Variable not in scope: do_test - -:515:1: error: Variable not in scope: do_test - -:516:1: error: Variable not in scope: do_test - -:517:1: error: Variable not in scope: do_test - -:518:1: error: Variable not in scope: do_test - -:519:1: error: Variable not in scope: do_test - -:520:1: error: Variable not in scope: do_test - -:521:1: error: Variable not in scope: do_test - -:522:1: error: Variable not in scope: do_test - -:523:1: error: Variable not in scope: do_test - -:524:1: error: Variable not in scope: do_test - -:525:1: error: Variable not in scope: do_test - -:526:1: error: Variable not in scope: do_test - -:527:1: error: Variable not in scope: do_test - -:528:1: error: Variable not in scope: do_test - -:529:1: error: Variable not in scope: do_test - -:530:1: error: Variable not in scope: do_test - -:531:1: error: Variable not in scope: do_test - -:532:1: error: Variable not in scope: do_test - -:533:1: error: Variable not in scope: do_test - -:534:1: error: Variable not in scope: do_test - -:535:1: error: Variable not in scope: do_test - -:536:1: error: Variable not in scope: do_test - -:537:1: error: Variable not in scope: do_test - -:538:1: error: Variable not in scope: do_test - -:539:1: error: Variable not in scope: do_test - -:540:1: error: Variable not in scope: do_test - -:541:1: error: Variable not in scope: do_test - -:542:1: error: Variable not in scope: do_test - -:543:1: error: Variable not in scope: do_test - -:544:1: error: Variable not in scope: do_test - -:545:1: error: Variable not in scope: do_test - -:546:1: error: Variable not in scope: do_test - -:547:1: error: Variable not in scope: do_test - -:548:1: error: Variable not in scope: do_test - -:549:1: error: Variable not in scope: do_test - -:550:1: error: Variable not in scope: do_test - -:551:1: error: Variable not in scope: do_test - -:552:1: error: Variable not in scope: do_test - -:553:1: error: Variable not in scope: do_test - -:554:1: error: Variable not in scope: do_test - -:555:1: error: Variable not in scope: do_test - -:556:1: error: Variable not in scope: do_test - -:557:1: error: Variable not in scope: do_test - -:558:1: error: Variable not in scope: do_test - -:559:1: error: Variable not in scope: do_test - -:560:1: error: Variable not in scope: do_test - -:561:1: error: Variable not in scope: do_test - -:562:1: error: Variable not in scope: do_test - -:563:1: error: Variable not in scope: do_test - -:564:1: error: Variable not in scope: do_test - -:565:1: error: Variable not in scope: do_test - -:566:1: error: Variable not in scope: do_test - -:567:1: error: Variable not in scope: do_test - -:568:1: error: Variable not in scope: do_test - -:569:1: error: Variable not in scope: do_test - -:570:1: error: Variable not in scope: do_test - -:571:1: error: Variable not in scope: do_test - -:572:1: error: Variable not in scope: do_test - -:573:1: error: Variable not in scope: do_test - -:574:1: error: Variable not in scope: do_test - -:575:1: error: Variable not in scope: do_test - -:576:1: error: Variable not in scope: do_test - -:577:1: error: Variable not in scope: do_test - -:578:1: error: Variable not in scope: do_test - -:579:1: error: Variable not in scope: do_test - -:580:1: error: Variable not in scope: do_test - -:581:1: error: Variable not in scope: do_test - -:582:1: error: Variable not in scope: do_test - -:583:1: error: Variable not in scope: do_test - -:584:1: error: Variable not in scope: do_test - -:585:1: error: Variable not in scope: do_test - -:586:1: error: Variable not in scope: do_test - -:587:1: error: Variable not in scope: do_test - -:588:1: error: Variable not in scope: do_test - -:589:1: error: Variable not in scope: do_test - -:590:1: error: Variable not in scope: do_test - -:591:1: error: Variable not in scope: do_test - -:592:1: error: Variable not in scope: do_test - -:593:1: error: Variable not in scope: do_test - -:594:1: error: Variable not in scope: do_test - -:595:1: error: Variable not in scope: do_test - -:596:1: error: Variable not in scope: do_test - -:597:1: error: Variable not in scope: do_test - -:598:1: error: Variable not in scope: do_test - -:599:1: error: Variable not in scope: do_test - -:600:1: error: Variable not in scope: do_test - -:601:1: error: Variable not in scope: do_test - -:602:1: error: Variable not in scope: do_test - -:603:1: error: Variable not in scope: do_test - -:604:1: error: Variable not in scope: do_test - -:605:1: error: Variable not in scope: do_test - -:606:1: error: Variable not in scope: do_test - -:607:1: error: Variable not in scope: do_test - -:608:1: error: Variable not in scope: do_test - -:609:1: error: Variable not in scope: do_test - -:610:1: error: Variable not in scope: do_test - -:611:1: error: Variable not in scope: do_test - -:612:1: error: Variable not in scope: do_test - -:613:1: error: Variable not in scope: do_test - -:614:1: error: Variable not in scope: do_test - -:615:1: error: Variable not in scope: do_test - -:616:1: error: Variable not in scope: do_test - -:617:1: error: Variable not in scope: do_test - -:618:1: error: Variable not in scope: do_test - -:619:1: error: Variable not in scope: do_test - -:620:1: error: Variable not in scope: do_test - -:621:1: error: Variable not in scope: do_test - -:622:1: error: Variable not in scope: do_test - -:623:1: error: Variable not in scope: do_test - -:624:1: error: Variable not in scope: do_test - -:625:1: error: Variable not in scope: do_test - -:626:1: error: Variable not in scope: do_test - -:627:1: error: Variable not in scope: do_test - -:628:1: error: Variable not in scope: do_test - -:629:1: error: Variable not in scope: do_test - -:630:1: error: Variable not in scope: do_test - -:631:1: error: Variable not in scope: do_test - -:632:1: error: Variable not in scope: do_test - -:633:1: error: Variable not in scope: do_test - -:634:1: error: Variable not in scope: do_test - -:635:1: error: Variable not in scope: do_test - -:636:1: error: Variable not in scope: do_test - -:637:1: error: Variable not in scope: do_test - -:638:1: error: Variable not in scope: do_test - -:639:1: error: Variable not in scope: do_test - -:640:1: error: Variable not in scope: do_test - -:641:1: error: Variable not in scope: do_test - -:642:1: error: Variable not in scope: do_test - -:643:1: error: Variable not in scope: do_test - -:644:1: error: Variable not in scope: do_test - -:645:1: error: Variable not in scope: do_test - -:646:1: error: Variable not in scope: do_test - -:647:1: error: Variable not in scope: do_test - -:648:1: error: Variable not in scope: do_test - -:649:1: error: Variable not in scope: do_test - -:650:1: error: Variable not in scope: do_test - -:651:1: error: Variable not in scope: do_test - -:652:1: error: Variable not in scope: do_test - -:653:1: error: Variable not in scope: do_test - -:654:1: error: Variable not in scope: do_test - -:655:1: error: Variable not in scope: do_test - -:656:1: error: Variable not in scope: do_test - -:657:1: error: Variable not in scope: do_test - -:658:1: error: Variable not in scope: do_test - -:659:1: error: Variable not in scope: do_test - -:660:1: error: Variable not in scope: do_test - -:661:1: error: Variable not in scope: do_test - -:662:1: error: Variable not in scope: do_test - -:663:1: error: Variable not in scope: do_test - -:664:1: error: Variable not in scope: do_test - -:665:1: error: Variable not in scope: do_test - -:666:1: error: Variable not in scope: do_test - -:667:1: error: Variable not in scope: do_test - -:668:1: error: Variable not in scope: do_test - -:669:1: error: Variable not in scope: do_test - -:670:1: error: Variable not in scope: do_test - -:671:1: error: Variable not in scope: do_test - -:672:1: error: Variable not in scope: do_test - -:673:1: error: Variable not in scope: do_test - -:674:1: error: Variable not in scope: do_test - -:675:1: error: Variable not in scope: do_test - -:676:1: error: Variable not in scope: do_test - -:677:1: error: Variable not in scope: do_test - -:678:1: error: Variable not in scope: do_test - -:679:1: error: Variable not in scope: do_test - -:680:1: error: Variable not in scope: do_test - -:681:1: error: Variable not in scope: do_test - -:682:1: error: Variable not in scope: do_test - -:683:1: error: Variable not in scope: do_test - -:684:1: error: Variable not in scope: do_test - -:685:1: error: Variable not in scope: do_test - -:686:1: error: Variable not in scope: do_test - -:687:1: error: Variable not in scope: do_test - -:688:1: error: Variable not in scope: do_test - -:689:1: error: Variable not in scope: do_test - -:690:1: error: Variable not in scope: do_test - -:691:1: error: Variable not in scope: do_test - -:692:1: error: Variable not in scope: do_test - -:693:1: error: Variable not in scope: do_test - -:694:1: error: Variable not in scope: do_test - -:695:1: error: Variable not in scope: do_test - -:696:1: error: Variable not in scope: do_test - -:697:1: error: Variable not in scope: do_test - -:698:1: error: Variable not in scope: do_test - -:699:1: error: Variable not in scope: do_test - -:700:1: error: Variable not in scope: do_test - -:701:1: error: Variable not in scope: do_test - -:702:1: error: Variable not in scope: do_test - -:703:1: error: Variable not in scope: do_test - -:704:1: error: Variable not in scope: do_test - -:705:1: error: Variable not in scope: do_test - -:706:1: error: Variable not in scope: do_test - -:707:1: error: Variable not in scope: do_test - -:708:1: error: Variable not in scope: do_test - -:709:1: error: Variable not in scope: do_test - -:710:1: error: Variable not in scope: do_test - -:711:1: error: Variable not in scope: do_test - -:712:1: error: Variable not in scope: do_test - -:713:1: error: Variable not in scope: do_test - -:714:1: error: Variable not in scope: do_test - -:715:1: error: Variable not in scope: do_test - -:716:1: error: Variable not in scope: do_test - -:717:1: error: Variable not in scope: do_test - -:718:1: error: Variable not in scope: do_test - -:719:1: error: Variable not in scope: do_test - -:720:1: error: Variable not in scope: do_test - -:721:1: error: Variable not in scope: do_test - -:722:1: error: Variable not in scope: do_test - -:723:1: error: Variable not in scope: do_test - -:724:1: error: Variable not in scope: do_test - -:725:1: error: Variable not in scope: do_test - -:726:1: error: Variable not in scope: do_test - -:727:1: error: Variable not in scope: do_test - -:728:1: error: Variable not in scope: do_test - -:729:1: error: Variable not in scope: do_test - -:730:1: error: Variable not in scope: do_test - -:731:1: error: Variable not in scope: do_test - -:732:1: error: Variable not in scope: do_test - -:733:1: error: Variable not in scope: do_test - -:734:1: error: Variable not in scope: do_test - -:735:1: error: Variable not in scope: do_test - -:736:1: error: Variable not in scope: do_test - -:737:1: error: Variable not in scope: do_test - -:738:1: error: Variable not in scope: do_test - -:739:1: error: Variable not in scope: do_test - -:740:1: error: Variable not in scope: do_test - -:741:1: error: Variable not in scope: do_test - -:742:1: error: Variable not in scope: do_test - -:743:1: error: Variable not in scope: do_test - -:744:1: error: Variable not in scope: do_test - -:745:1: error: Variable not in scope: do_test - -:746:1: error: Variable not in scope: do_test - -:747:1: error: Variable not in scope: do_test - -:748:1: error: Variable not in scope: do_test - -:749:1: error: Variable not in scope: do_test - -:750:1: error: Variable not in scope: do_test - -:751:1: error: Variable not in scope: do_test - -:752:1: error: Variable not in scope: do_test - -:753:1: error: Variable not in scope: do_test - -:754:1: error: Variable not in scope: do_test - -:755:1: error: Variable not in scope: do_test - -:756:1: error: Variable not in scope: do_test - -:757:1: error: Variable not in scope: do_test - -:758:1: error: Variable not in scope: do_test - -:759:1: error: Variable not in scope: do_test - -:760:1: error: Variable not in scope: do_test - -:761:1: error: Variable not in scope: do_test - -:762:1: error: Variable not in scope: do_test - -:763:1: error: Variable not in scope: do_test - -:764:1: error: Variable not in scope: do_test - -:765:1: error: Variable not in scope: do_test - -:766:1: error: Variable not in scope: do_test - -:767:1: error: Variable not in scope: do_test - -:768:1: error: Variable not in scope: do_test - -:769:1: error: Variable not in scope: do_test - -:770:1: error: Variable not in scope: do_test - -:771:1: error: Variable not in scope: do_test - -:772:1: error: Variable not in scope: do_test - -:773:1: error: Variable not in scope: do_test - -:774:1: error: Variable not in scope: do_test - -:775:1: error: Variable not in scope: do_test - -:776:1: error: Variable not in scope: do_test - -:777:1: error: Variable not in scope: do_test - -:778:1: error: Variable not in scope: do_test - -:779:1: error: Variable not in scope: do_test - -:780:1: error: Variable not in scope: do_test - -:781:1: error: Variable not in scope: do_test - -:782:1: error: Variable not in scope: do_test - -:783:1: error: Variable not in scope: do_test - -:784:1: error: Variable not in scope: do_test - -:785:1: error: Variable not in scope: do_test - -:786:1: error: Variable not in scope: do_test - -:787:1: error: Variable not in scope: do_test - -:788:1: error: Variable not in scope: do_test - -:789:1: error: Variable not in scope: do_test - -:790:1: error: Variable not in scope: do_test - -:791:1: error: Variable not in scope: do_test - -:792:1: error: Variable not in scope: do_test - -:793:1: error: Variable not in scope: do_test - -:794:1: error: Variable not in scope: do_test - -:795:1: error: Variable not in scope: do_test - -:796:1: error: Variable not in scope: do_test - -:797:1: error: Variable not in scope: do_test - -:798:1: error: Variable not in scope: do_test - -:799:1: error: Variable not in scope: do_test - -:800:1: error: Variable not in scope: do_test - -:801:1: error: Variable not in scope: do_test - -:802:1: error: Variable not in scope: do_test - -:803:1: error: Variable not in scope: do_test - -:804:1: error: Variable not in scope: do_test - -:805:1: error: Variable not in scope: do_test - -:806:1: error: Variable not in scope: do_test - -:807:1: error: Variable not in scope: do_test - -:808:1: error: Variable not in scope: do_test - -:809:1: error: Variable not in scope: do_test - -:810:1: error: Variable not in scope: do_test - -:811:1: error: Variable not in scope: do_test - -:812:1: error: Variable not in scope: do_test - -:813:1: error: Variable not in scope: do_test - -:814:1: error: Variable not in scope: do_test - -:815:1: error: Variable not in scope: do_test - -:816:1: error: Variable not in scope: do_test - -:817:1: error: Variable not in scope: do_test - -:818:1: error: Variable not in scope: do_test - -:819:1: error: Variable not in scope: do_test - -:820:1: error: Variable not in scope: do_test - -:821:1: error: Variable not in scope: do_test - -:822:1: error: Variable not in scope: do_test - -:823:1: error: Variable not in scope: do_test - -:824:1: error: Variable not in scope: do_test - -:825:1: error: Variable not in scope: do_test - -:826:1: error: Variable not in scope: do_test - -:827:1: error: Variable not in scope: do_test - -:828:1: error: Variable not in scope: do_test - -:829:1: error: Variable not in scope: do_test - -:830:1: error: Variable not in scope: do_test - -:831:1: error: Variable not in scope: do_test - -:832:1: error: Variable not in scope: do_test - -:833:1: error: Variable not in scope: do_test - -:834:1: error: Variable not in scope: do_test - -:835:1: error: Variable not in scope: do_test - -:836:1: error: Variable not in scope: do_test - -:837:1: error: Variable not in scope: do_test - -:838:1: error: Variable not in scope: do_test - -:839:1: error: Variable not in scope: do_test - -:840:1: error: Variable not in scope: do_test - -:841:1: error: Variable not in scope: do_test - -:842:1: error: Variable not in scope: do_test - -:843:1: error: Variable not in scope: do_test - -:844:1: error: Variable not in scope: do_test - -:845:1: error: Variable not in scope: do_test - -:846:1: error: Variable not in scope: do_test - -:847:1: error: Variable not in scope: do_test - -:848:1: error: Variable not in scope: do_test - -:849:1: error: Variable not in scope: do_test - -:850:1: error: Variable not in scope: do_test - -:851:1: error: Variable not in scope: do_test - -:852:1: error: Variable not in scope: do_test - -:853:1: error: Variable not in scope: do_test - -:854:1: error: Variable not in scope: do_test - -:855:1: error: Variable not in scope: do_test - -:856:1: error: Variable not in scope: do_test - -:857:1: error: Variable not in scope: do_test - -:858:1: error: Variable not in scope: do_test - -:859:1: error: Variable not in scope: do_test - -:860:1: error: Variable not in scope: do_test - -:861:1: error: Variable not in scope: do_test - -:862:1: error: Variable not in scope: do_test - -:863:1: error: Variable not in scope: do_test - -:864:1: error: Variable not in scope: do_test - -:865:1: error: Variable not in scope: do_test - -:866:1: error: Variable not in scope: do_test - -:867:1: error: Variable not in scope: do_test - -:868:1: error: Variable not in scope: do_test - -:869:1: error: Variable not in scope: do_test - -:870:1: error: Variable not in scope: do_test - -:871:1: error: Variable not in scope: do_test - -:872:1: error: Variable not in scope: do_test - -:873:1: error: Variable not in scope: do_test - -:874:1: error: Variable not in scope: do_test - -:875:1: error: Variable not in scope: do_test - -:876:1: error: Variable not in scope: do_test - -:877:1: error: Variable not in scope: do_test - -:878:1: error: Variable not in scope: do_test - -:879:1: error: Variable not in scope: do_test - -:880:1: error: Variable not in scope: do_test - -:881:1: error: Variable not in scope: do_test - -:882:1: error: Variable not in scope: do_test - -:883:1: error: Variable not in scope: do_test - -:884:1: error: Variable not in scope: do_test - -:885:1: error: Variable not in scope: do_test - -:886:1: error: Variable not in scope: do_test - -:887:1: error: Variable not in scope: do_test - -:888:1: error: Variable not in scope: do_test - -:889:1: error: Variable not in scope: do_test - -:890:1: error: Variable not in scope: do_test - -:891:1: error: Variable not in scope: do_test - -:892:1: error: Variable not in scope: do_test - -:893:1: error: Variable not in scope: do_test - -:894:1: error: Variable not in scope: do_test - -:895:1: error: Variable not in scope: do_test - -:896:1: error: Variable not in scope: do_test - -:897:1: error: Variable not in scope: do_test - -:898:1: error: Variable not in scope: do_test - -:899:1: error: Variable not in scope: do_test - -:900:1: error: Variable not in scope: do_test - -:901:1: error: Variable not in scope: do_test - -:902:1: error: Variable not in scope: do_test - -:903:1: error: Variable not in scope: do_test - -:904:1: error: Variable not in scope: do_test - -:905:1: error: Variable not in scope: do_test - -:906:1: error: Variable not in scope: do_test - -:907:1: error: Variable not in scope: do_test - -:908:1: error: Variable not in scope: do_test - -:909:1: error: Variable not in scope: do_test - -:910:1: error: Variable not in scope: do_test - -:911:1: error: Variable not in scope: do_test - -:912:1: error: Variable not in scope: do_test - -:913:1: error: Variable not in scope: do_test - -:914:1: error: Variable not in scope: do_test - -:915:1: error: Variable not in scope: do_test - -:916:1: error: Variable not in scope: do_test - -:917:1: error: Variable not in scope: do_test - -:918:1: error: Variable not in scope: do_test - -:919:1: error: Variable not in scope: do_test - -:920:1: error: Variable not in scope: do_test - -:921:1: error: Variable not in scope: do_test - -:922:1: error: Variable not in scope: do_test - -:923:1: error: Variable not in scope: do_test - -:924:1: error: Variable not in scope: do_test - -:925:1: error: Variable not in scope: do_test - -:926:1: error: Variable not in scope: do_test - -:927:1: error: Variable not in scope: do_test - -:928:1: error: Variable not in scope: do_test - -:929:1: error: Variable not in scope: do_test - -:930:1: error: Variable not in scope: do_test - -:931:1: error: Variable not in scope: do_test - -:932:1: error: Variable not in scope: do_test - -:933:1: error: Variable not in scope: do_test - -:934:1: error: Variable not in scope: do_test - -:935:1: error: Variable not in scope: do_test - -:936:1: error: Variable not in scope: do_test - -:937:1: error: Variable not in scope: do_test - -:938:1: error: Variable not in scope: do_test - -:939:1: error: Variable not in scope: do_test - -:940:1: error: Variable not in scope: do_test - -:941:1: error: Variable not in scope: do_test - -:942:1: error: Variable not in scope: do_test - -:943:1: error: Variable not in scope: do_test - -:944:1: error: Variable not in scope: do_test - -:945:1: error: Variable not in scope: do_test - -:946:1: error: Variable not in scope: do_test - -:947:1: error: Variable not in scope: do_test - -:948:1: error: Variable not in scope: do_test - -:949:1: error: Variable not in scope: do_test - -:950:1: error: Variable not in scope: do_test - -:951:1: error: Variable not in scope: do_test - -:952:1: error: Variable not in scope: do_test - -:953:1: error: Variable not in scope: do_test - -:954:1: error: Variable not in scope: do_test - -:955:1: error: Variable not in scope: do_test - -:956:1: error: Variable not in scope: do_test - -:957:1: error: Variable not in scope: do_test - -:958:1: error: Variable not in scope: do_test - -:959:1: error: Variable not in scope: do_test - -:960:1: error: Variable not in scope: do_test - -:961:1: error: Variable not in scope: do_test - -:962:1: error: Variable not in scope: do_test - -:963:1: error: Variable not in scope: do_test - -:964:1: error: Variable not in scope: do_test - -:965:1: error: Variable not in scope: do_test - -:966:1: error: Variable not in scope: do_test - -:967:1: error: Variable not in scope: do_test - -:968:1: error: Variable not in scope: do_test - -:969:1: error: Variable not in scope: do_test - -:970:1: error: Variable not in scope: do_test - -:971:1: error: Variable not in scope: do_test - -:972:1: error: Variable not in scope: do_test - -:973:1: error: Variable not in scope: do_test - -:974:1: error: Variable not in scope: do_test - -:975:1: error: Variable not in scope: do_test - -:976:1: error: Variable not in scope: do_test - -:977:1: error: Variable not in scope: do_test - -:978:1: error: Variable not in scope: do_test - -:979:1: error: Variable not in scope: do_test - -:980:1: error: Variable not in scope: do_test - -:981:1: error: Variable not in scope: do_test - -:982:1: error: Variable not in scope: do_test - -:983:1: error: Variable not in scope: do_test View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b7672d985eee8affbc6cbe2ca07942b6fc27c52 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b7672d985eee8affbc6cbe2ca07942b6fc27c52 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 Mon Nov 9 18:19:31 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 09 Nov 2020 13:19:31 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] Update test outputs Message-ID: <5fa988337294b_10ee108edd24903572@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: c887ca0d by Sebastian Graf at 2020-11-09T19:19:23+01:00 Update test outputs - - - - - 28 changed files: - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr - testsuite/tests/arityanal/should_compile/T18793.stderr - testsuite/tests/numeric/should_compile/T7116.stdout - testsuite/tests/simplCore/should_compile/T13143.stderr - testsuite/tests/simplCore/should_compile/T13543.stderr - testsuite/tests/simplCore/should_compile/T3717.stderr - testsuite/tests/simplCore/should_compile/T3772.stdout - testsuite/tests/simplCore/should_compile/T4908.stderr - testsuite/tests/simplCore/should_compile/T4930.stderr - testsuite/tests/simplCore/should_compile/spec-inline.stderr - testsuite/tests/stranal/should_compile/T10694.stderr - testsuite/tests/stranal/should_compile/T18903.stderr - testsuite/tests/stranal/sigs/BottomFromInnerLambda.stderr - testsuite/tests/stranal/sigs/CaseBinderCPR.stderr - testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr - testsuite/tests/stranal/sigs/HyperStrUse.stderr - testsuite/tests/stranal/sigs/NewtypeArity.stderr - testsuite/tests/stranal/sigs/T12370.stderr - testsuite/tests/stranal/sigs/T13380f.stderr - testsuite/tests/stranal/sigs/T17932.stderr - testsuite/tests/stranal/sigs/T5075.stderr - testsuite/tests/stranal/sigs/T8598.stderr - testsuite/tests/stranal/sigs/UnsatFun.stderr Changes: ===================================== testsuite/tests/arityanal/should_compile/Arity01.stderr ===================================== @@ -47,7 +47,7 @@ F1.s1 = 3 s :: forall {t1} {t2}. Num t1 => (t1 -> t2) -> t2 [GblId, Arity=2, - Str=<1(A,A,A,A,A,A,1C1(U))>, + Str=<1P(A,A,A,A,A,A,1C1(U))>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (@t) (@t1) ($dNum [Occ=Once1] :: Num t) (f [Occ=Once1!] :: t -> t1) -> f (fromInteger @t $dNum F1.s1)}] s = \ (@t) (@t1) ($dNum :: Num t) (f :: t -> t1) -> f (fromInteger @t $dNum F1.s1) ===================================== testsuite/tests/arityanal/should_compile/Arity03.stderr ===================================== @@ -18,7 +18,7 @@ end Rec } fac [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1!] :: Int) -> case w of { GHC.Types.I# ww1 [Occ=Once1] -> case F3.$wfac ww1 of ww2 [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww2 } }}] @@ -28,7 +28,7 @@ fac = \ (w :: Int) -> case w of { GHC.Types.I# ww1 -> case F3.$wfac ww1 of ww2 { f3 :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True) Tmpl= fac}] ===================================== testsuite/tests/arityanal/should_compile/Arity04.stderr ===================================== @@ -6,7 +6,7 @@ Result size of Tidy Core = {terms: 39, types: 24, coercions: 0, joins: 0/0} f4g :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (y [Occ=Once1!] :: Int) -> case y of { GHC.Types.I# x [Occ=Once1] -> GHC.Types.I# (GHC.Prim.+# x 1#) }}] @@ -33,7 +33,7 @@ end Rec } f4h [InlPrag=[2]] :: (Int -> Int) -> Int -> Int [GblId, Arity=2, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1] :: Int -> Int) (w1 [Occ=Once1!] :: Int) -> case w1 of { GHC.Types.I# ww1 [Occ=Once1] -> F4.$wf4h w ww1 }}] f4h = \ (w :: Int -> Int) (w1 :: Int) -> case w1 of { GHC.Types.I# ww1 -> F4.$wf4h w ww1 } ===================================== testsuite/tests/arityanal/should_compile/Arity05.stderr ===================================== @@ -11,7 +11,7 @@ F5.f5g1 = 1 f5g :: forall {a} {t}. Num a => (t -> a) -> t -> a [GblId, Arity=3, - Str=<1C1(U)>, + Str=<1C1(U)>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=3,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@t) ($dNum :: Num a) (h [Occ=Once1!] :: t -> a) (z [Occ=Once1] :: t) -> + @a $dNum (h z) (fromInteger @a $dNum F5.f5g1)}] f5g = \ (@a) (@t) ($dNum :: Num a) (h :: t -> a) (z :: t) -> + @a $dNum (h z) (fromInteger @a $dNum F5.f5g1) @@ -25,7 +25,7 @@ F5.$wf5h = \ (@a) (@t) (ww :: a -> a -> a) (ww1 :: Integer -> a) (w :: t -> a) ( f5h [InlPrag=[2]] :: forall {a} {t}. Num a => (t -> a) -> t -> (t -> a) -> a [GblId, Arity=4, - Str=<1C1(U)><1C1(U)>, + Str=<1C1(U)><1C1(U)>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@t) (w [Occ=Once1!] :: Num a) (w1 [Occ=Once1] :: t -> a) (w2 [Occ=Once1] :: t) (w3 [Occ=Once1] :: t -> a) -> case w of { GHC.Num.C:Num ww1 [Occ=Once1] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] ww7 [Occ=Once1] -> F5.$wf5h @a @t ww1 ww7 w1 w2 w3 }}] f5h = \ (@a) (@t) (w :: Num a) (w1 :: t -> a) (w2 :: t) (w3 :: t -> a) -> case w of { GHC.Num.C:Num ww1 ww2 ww3 ww4 ww5 ww6 ww7 -> F5.$wf5h @a @t ww1 ww7 w1 w2 w3 } ===================================== testsuite/tests/arityanal/should_compile/Arity11.stderr ===================================== @@ -35,7 +35,7 @@ end Rec } -- RHS size: {terms: 52, types: 28, coercions: 0, joins: 0/5} F11.$wfib [InlPrag=[2]] :: forall {a} {p}. (a -> a -> Bool) -> (Num a, Num p) => a -> p -[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 460 0}] +[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 460 0}] F11.$wfib = \ (@a) (@p) (ww :: a -> a -> Bool) (w :: Num a) (w1 :: Num p) (w2 :: a) -> let { @@ -73,7 +73,7 @@ F11.$wfib fib [InlPrag=[2]] :: forall {a} {p}. (Eq a, Num a, Num p) => a -> p [GblId, Arity=4, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@p) (w [Occ=Once1!] :: Eq a) (w1 [Occ=Once1] :: Num a) (w2 [Occ=Once1] :: Num p) (w3 [Occ=Once1] :: a) -> case w of { GHC.Classes.C:Eq ww1 [Occ=Once1] _ [Occ=Dead] -> F11.$wfib @a @p ww1 w1 w2 w3 }}] fib = \ (@a) (@p) (w :: Eq a) (w1 :: Num a) (w2 :: Num p) (w3 :: a) -> case w of { GHC.Classes.C:Eq ww1 ww2 -> F11.$wfib @a @p ww1 w1 w2 w3 } ===================================== testsuite/tests/arityanal/should_compile/Arity14.stderr ===================================== @@ -18,7 +18,7 @@ F14.f2 = 1 -- RHS size: {terms: 35, types: 24, coercions: 0, joins: 0/3} F14.$wf14 [InlPrag=[2]] :: forall {t}. (t -> t -> Bool) -> Num t => t -> t -> t -> t -[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 90 0 0] 300 0}] +[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 90 0 0] 300 0}] F14.$wf14 = \ (@t) (ww :: t -> t -> Bool) (w :: Num t) (w1 :: t) (w2 :: t) -> let { @@ -45,7 +45,7 @@ F14.$wf14 f14 [InlPrag=[2]] :: forall {t}. (Ord t, Num t) => t -> t -> t -> t [GblId, Arity=4, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@t) (w [Occ=Once1!] :: Ord t) (w1 [Occ=Once1] :: Num t) (w2 [Occ=Once1] :: t) (w3 [Occ=Once1] :: t) -> case w of { GHC.Classes.C:Ord _ [Occ=Dead] _ [Occ=Dead] ww3 [Occ=Once1] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] _ [Occ=Dead] -> F14.$wf14 @t ww3 w1 w2 w3 }}] f14 = \ (@t) (w :: Ord t) (w1 :: Num t) (w2 :: t) (w3 :: t) -> case w of { GHC.Classes.C:Ord ww1 ww2 ww3 ww4 ww5 ww6 ww7 ww8 -> F14.$wf14 @t ww3 w1 w2 w3 } ===================================== testsuite/tests/arityanal/should_compile/T18793.stderr ===================================== @@ -4,14 +4,14 @@ Result size of Tidy Core = {terms: 81, types: 74, coercions: 0, joins: 0/0} -- RHS size: {terms: 20, types: 13, coercions: 0, joins: 0/0} T18793.$wstuff [InlPrag=NOINLINE] :: Int -> (# Int, [Int] #) -[GblId, Arity=1, Str=, Unf=OtherCon []] +[GblId, Arity=1, Str=, Unf=OtherCon []] T18793.$wstuff = \ (w :: Int) -> (# w, GHC.Types.: @Int (case w of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 1#) }) (GHC.Types.: @Int (case w of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 2#) }) (GHC.Types.[] @Int)) #) -- RHS size: {terms: 8, types: 11, coercions: 0, joins: 0/0} stuff [InlPrag=[final]] :: Int -> [Int] [GblId, Arity=1, - Str=, + Str=, Cpr=m2, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1] :: Int) -> case T18793.$wstuff w of { (# ww1 [Occ=Once1], ww2 [Occ=Once1] #) -> GHC.Types.: @Int ww1 ww2 }}] @@ -39,7 +39,7 @@ end Rec } T18793.f_go1 [InlPrag=[2]] :: [Int] -> Int -> Int [GblId, Arity=2, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (w [Occ=Once1] :: [Int]) (w1 [Occ=Once1!] :: Int) -> case w1 of { GHC.Types.I# ww1 [Occ=Once1] -> case T18793.$wgo1 w ww1 of ww2 [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww2 } }}] @@ -59,7 +59,7 @@ T18793.f1 = case T18793.$wstuff T18793.f2 of { (# ww1, ww2 #) -> GHC.Types.: @In f :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=False) Tmpl= \ (eta [Occ=Once1] :: Int) -> T18793.f_go1 T18793.f1 eta}] ===================================== testsuite/tests/numeric/should_compile/T7116.stdout ===================================== @@ -43,7 +43,7 @@ T7116.$trModule dr :: Double -> Double [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, @@ -60,7 +60,7 @@ dr dl :: Double -> Double [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, @@ -73,7 +73,7 @@ dl = dr fr :: Float -> Float [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, @@ -92,7 +92,7 @@ fr fl :: Float -> Float [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, ===================================== testsuite/tests/simplCore/should_compile/T13143.stderr ===================================== @@ -89,7 +89,7 @@ end Rec } g [InlPrag=[2]] :: Bool -> Bool -> Int -> Int [GblId, Arity=3, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, ===================================== testsuite/tests/simplCore/should_compile/T13543.stderr ===================================== @@ -1,8 +1,8 @@ ==================== Strictness signatures ==================== Foo.$trModule: -Foo.f: -Foo.g: +Foo.f: +Foo.g: @@ -15,7 +15,7 @@ Foo.g: m1 ==================== Strictness signatures ==================== Foo.$trModule: -Foo.f: -Foo.g: +Foo.f: +Foo.g: ===================================== testsuite/tests/simplCore/should_compile/T3717.stderr ===================================== @@ -56,7 +56,7 @@ end Rec } foo [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, ===================================== testsuite/tests/simplCore/should_compile/T3772.stdout ===================================== @@ -65,7 +65,7 @@ T3772.$wfoo foo [InlPrag=[final]] :: Int -> () [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) ===================================== testsuite/tests/simplCore/should_compile/T4908.stderr ===================================== @@ -59,7 +59,7 @@ end Rec } T4908.$wf [InlPrag=[2]] :: Int# -> (Int, Int) -> Bool [GblId, Arity=2, - Str=<1(A,1(1U))>, + Str=<1P(A,1P(1U))>, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 20] 101 20}] T4908.$wf @@ -81,7 +81,7 @@ T4908.$wf f [InlPrag=[2]] :: Int -> (Int, Int) -> Bool [GblId, Arity=2, - Str=<1(A,1(1U))>, + Str=<1P(A,1P(1U))>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) ===================================== testsuite/tests/simplCore/should_compile/T4930.stderr ===================================== @@ -56,7 +56,7 @@ end Rec } foo [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, ===================================== testsuite/tests/simplCore/should_compile/spec-inline.stderr ===================================== @@ -143,7 +143,7 @@ Roman.foo1 = GHC.Maybe.Just @Int Roman.foo2 foo :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, ===================================== testsuite/tests/stranal/should_compile/T10694.stderr ===================================== @@ -4,32 +4,32 @@ Result size of Tidy Core = {terms: 74, types: 65, coercions: 0, joins: 0/4} -- RHS size: {terms: 39, types: 25, coercions: 0, joins: 0/4} T10694.$wpm [InlPrag=NOINLINE] :: Int -> Int -> (# Int, Int #) -[GblId, Arity=2, Str=, Unf=OtherCon []] +[GblId, Arity=2, Str=, Unf=OtherCon []] T10694.$wpm = \ (w :: Int) (w1 :: Int) -> let { - lvl :: Int + l :: Int [LclId] - lvl = case w of { GHC.Types.I# x -> case w1 of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } } } in + l = case w of { GHC.Types.I# x -> case w1 of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } } } in let { - lvl1 :: Int + l1 :: Int [LclId] - lvl1 = case w of { GHC.Types.I# x -> case w1 of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.-# x y) } } } in + l1 = case w of { GHC.Types.I# x -> case w1 of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.-# x y) } } } in let { - l :: [Int] + l2 :: [Int] [LclId, Unf=OtherCon []] - l = GHC.Types.: @Int lvl1 (GHC.Types.[] @Int) } in + l2 = GHC.Types.: @Int l1 (GHC.Types.[] @Int) } in let { - l1 :: [Int] + l3 :: [Int] [LclId, Unf=OtherCon []] - l1 = GHC.Types.: @Int lvl l } in - (# GHC.List.$w!! @Int l1 0#, GHC.List.$w!! @Int l1 1# #) + l3 = GHC.Types.: @Int l l2 } in + (# GHC.List.$w!! @Int l3 0#, GHC.List.$w!! @Int l3 1# #) -- RHS size: {terms: 10, types: 11, coercions: 0, joins: 0/0} pm [InlPrag=[final]] :: Int -> Int -> (Int, Int) [GblId, Arity=2, - Str=, + Str=, Cpr=m1, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) @@ -41,7 +41,7 @@ pm = \ (w :: Int) (w1 :: Int) -> case T10694.$wpm w w1 of { (# ww1, ww2 #) -> (w m :: Int -> Int -> Int [GblId, Arity=2, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False) Tmpl= \ (x [Occ=Once1] :: Int) (y [Occ=Once1] :: Int) -> case pm x y of { (_ [Occ=Dead], mr [Occ=Once1]) -> mr }}] ===================================== testsuite/tests/stranal/should_compile/T18903.stderr ===================================== @@ -57,13 +57,13 @@ T18903.h2 = GHC.Types.I# -2# T18903.$wh [InlPrag=[2]] :: GHC.Prim.Int# -> Int [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [70] 262 10}] T18903.$wh = \ (ww :: GHC.Prim.Int#) -> let { - $wg [InlPrag=NOINLINE, Dmd=1C1((1(U),S(U)))] + $wg [InlPrag=NOINLINE, Dmd=1C1(P(1P(U),SP(U)))] :: GHC.Prim.Int# -> (# Int, Int #) [LclId, Arity=1, Str=, Unf=OtherCon []] $wg @@ -96,7 +96,7 @@ T18903.$wh h [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) ===================================== testsuite/tests/stranal/sigs/BottomFromInnerLambda.stderr ===================================== @@ -1,8 +1,8 @@ ==================== Strictness signatures ==================== BottomFromInnerLambda.$trModule: -BottomFromInnerLambda.expensive: -BottomFromInnerLambda.f: +BottomFromInnerLambda.expensive: +BottomFromInnerLambda.f: @@ -15,7 +15,7 @@ BottomFromInnerLambda.f: ==================== Strictness signatures ==================== BottomFromInnerLambda.$trModule: -BottomFromInnerLambda.expensive: -BottomFromInnerLambda.f: +BottomFromInnerLambda.expensive: +BottomFromInnerLambda.f: ===================================== testsuite/tests/stranal/sigs/CaseBinderCPR.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Strictness signatures ==================== CaseBinderCPR.$trModule: -CaseBinderCPR.f_list_cmp: +CaseBinderCPR.f_list_cmp: @@ -13,6 +13,6 @@ CaseBinderCPR.f_list_cmp: m1 ==================== Strictness signatures ==================== CaseBinderCPR.$trModule: -CaseBinderCPR.f_list_cmp: +CaseBinderCPR.f_list_cmp: ===================================== testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr ===================================== @@ -9,7 +9,7 @@ DmdAnalGADTs.f: DmdAnalGADTs.f': DmdAnalGADTs.g: DmdAnalGADTs.hasCPR: -DmdAnalGADTs.hasStrSig: +DmdAnalGADTs.hasStrSig: @@ -37,6 +37,6 @@ DmdAnalGADTs.f: DmdAnalGADTs.f': DmdAnalGADTs.g: DmdAnalGADTs.hasCPR: -DmdAnalGADTs.hasStrSig: +DmdAnalGADTs.hasStrSig: ===================================== testsuite/tests/stranal/sigs/HyperStrUse.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Strictness signatures ==================== HyperStrUse.$trModule: -HyperStrUse.f: +HyperStrUse.f: @@ -13,6 +13,6 @@ HyperStrUse.f: m1 ==================== Strictness signatures ==================== HyperStrUse.$trModule: -HyperStrUse.f: +HyperStrUse.f: ===================================== testsuite/tests/stranal/sigs/NewtypeArity.stderr ===================================== @@ -3,8 +3,8 @@ Test.$tc'MkT: Test.$tcT: Test.$trModule: -Test.t: -Test.t2: +Test.t: +Test.t2: @@ -21,7 +21,7 @@ Test.t2: m1 Test.$tc'MkT: Test.$tcT: Test.$trModule: -Test.t: -Test.t2: +Test.t: +Test.t2: ===================================== testsuite/tests/stranal/sigs/T12370.stderr ===================================== @@ -1,8 +1,8 @@ ==================== Strictness signatures ==================== T12370.$trModule: -T12370.bar: -T12370.foo: +T12370.bar: +T12370.foo: @@ -15,7 +15,7 @@ T12370.foo: m1 ==================== Strictness signatures ==================== T12370.$trModule: -T12370.bar: -T12370.foo: +T12370.bar: +T12370.foo: ===================================== testsuite/tests/stranal/sigs/T13380f.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Strictness signatures ==================== T13380f.$trModule: -T13380f.f: -T13380f.g: <1(U)> -T13380f.h: <1(U)> +T13380f.f: +T13380f.g: <1P(U)> +T13380f.h: <1P(U)> T13380f.interruptibleCall: T13380f.safeCall: T13380f.unsafeCall: @@ -23,9 +23,9 @@ T13380f.unsafeCall: ==================== Strictness signatures ==================== T13380f.$trModule: -T13380f.f: -T13380f.g: <1(U)> -T13380f.h: <1(U)> +T13380f.f: +T13380f.g: <1P(U)> +T13380f.h: <1P(U)> T13380f.interruptibleCall: T13380f.safeCall: T13380f.unsafeCall: ===================================== testsuite/tests/stranal/sigs/T17932.stderr ===================================== @@ -5,7 +5,7 @@ T17932.$tc'X: T17932.$tcOptions: T17932.$tcX: T17932.$trModule: -T17932.flags: +T17932.flags: @@ -25,6 +25,6 @@ T17932.$tc'X: T17932.$tcOptions: T17932.$tcX: T17932.$trModule: -T17932.flags: +T17932.flags: ===================================== testsuite/tests/stranal/sigs/T5075.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Strictness signatures ==================== T5075.$trModule: -T5075.loop: +T5075.loop: @@ -13,6 +13,6 @@ T5075.loop: ==================== Strictness signatures ==================== T5075.$trModule: -T5075.loop: +T5075.loop: ===================================== testsuite/tests/stranal/sigs/T8598.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Strictness signatures ==================== T8598.$trModule: -T8598.fun: +T8598.fun: @@ -13,6 +13,6 @@ T8598.fun: m1 ==================== Strictness signatures ==================== T8598.$trModule: -T8598.fun: +T8598.fun: ===================================== testsuite/tests/stranal/sigs/UnsatFun.stderr ===================================== @@ -1,10 +1,10 @@ ==================== Strictness signatures ==================== UnsatFun.$trModule: -UnsatFun.f: b -UnsatFun.g: b -UnsatFun.g': <1(U)> -UnsatFun.g3: +UnsatFun.f: b +UnsatFun.g: b +UnsatFun.g': <1P(U)> +UnsatFun.g3: UnsatFun.h: UnsatFun.h2: <1C1(U)> UnsatFun.h3: @@ -25,10 +25,10 @@ UnsatFun.h3: m1 ==================== Strictness signatures ==================== UnsatFun.$trModule: -UnsatFun.f: b -UnsatFun.g: b -UnsatFun.g': <1(U)> -UnsatFun.g3: +UnsatFun.f: b +UnsatFun.g: b +UnsatFun.g': <1P(U)> +UnsatFun.g3: UnsatFun.h: UnsatFun.h2: <1C1(U)> UnsatFun.h3: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c887ca0d764e30a1c86ce6e4ec011b7a7e3dd407 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c887ca0d764e30a1c86ce6e4ec011b7a7e3dd407 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 Mon Nov 9 19:05:17 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Mon, 09 Nov 2020 14:05:17 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T17186 Message-ID: <5fa992ede24f7_10ee3ffbab1228d492124@gitlab.haskell.org.mail> Richard Eisenberg pushed new branch wip/T17186 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T17186 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 Mon Nov 9 19:15:28 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 14:15:28 -0500 Subject: [Git][ghc/ghc][wip/backports] 13 commits: Fix `instance Bounded a => Bounded (Down a)` (#18716) Message-ID: <5fa99550785ee_10eecd3e97c926396@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/backports at Glasgow Haskell Compiler / GHC Commits: e49c8923 by David Beacham at 2020-11-09T14:15:13-05:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog (cherry picked from commit 9ad51bc9d2ad9168abad271f715ce73d3562218a) - - - - - fb544de7 by Sylvain Henry at 2020-11-09T14:15:15-05:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a (cherry picked from commit 17d2f0a886f9f56ea408d2dd8b7f054021da19a4) - - - - - fa671e75 by Vladislav Zavialov at 2020-11-09T14:15:15-05:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. (cherry picked from commit bf2411a3c198cb2df93a9e0aa0c3b8297f47058d) - - - - - e5f73b99 by Ben Gamari at 2020-11-09T14:15:15-05:00 Bump win32-tarballs version to 0.3 This should fix #18774. (cherry picked from commit e5c7c9c8578de1248826c21ebd08e475d094a552) - - - - - 063d174f by Ben Gamari at 2020-11-09T14:15:15-05:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. (cherry picked from commit a848d52748c09a27ed5bef0fb039c51656bebdf1) - - - - - da266403 by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fixed bytestring reading interface. (cherry picked from commit 0fd3d360cab977e00fb6d90d0519962227b029bb) - - - - - c4fa35fa by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fixed more data error. (cherry picked from commit dfaef1cae7a4a0cb8783933274dae7f39d7165a0) - - - - - 556c2356 by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fix array splat (cherry picked from commit 6f0243ae5b359124936a8ff3dd0a287df3d7aca2) - - - - - c3a8c0bf by Tamar Christina at 2020-11-09T14:15:16-05:00 winio: fixed timeouts non-threaded. (cherry picked from commit c832f7e2a9314cfd61257cb161b1795b612d12b5) - - - - - e615aa85 by Andreas Klebinger at 2020-11-09T14:15:16-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) - - - - - 25a24e5d by Alan Zimmerman at 2020-11-09T14:15:16-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 (cherry picked from commit 616bec0dee67ae4841c4e60e9406cc9c63358223) - - - - - 2b3af303 by Ben Gamari at 2020-11-09T14:15:16-05:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. (cherry picked from commit 6434c2e35122886ad28a861cb857fa47bcc7e82d) - - - - - 06e7aed0 by Ben Gamari at 2020-11-09T14:15:16-05:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows (cherry picked from commit d76224c29a78ab962d86b9a1a92cde73e41b6479) - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser/PostProcess.hs - configure.ac - libraries/base/Data/Ord.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/IO/Handle/Text.hs - libraries/base/GHC/IO/Windows/Handle.hsc - libraries/base/changelog.md - libraries/base/tests/IO/all.T - + libraries/base/tests/IO/bytestringread001.hs - + libraries/base/tests/IO/bytestringread001.stdout - mk/get-win32-tarballs.py - rts/RtsSymbols.c - rts/win32/AsyncWinIO.c - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm - + testsuite/tests/deSugar/should_run/T18151x.hs - + testsuite/tests/deSugar/should_run/T18151x.stdout - testsuite/tests/deSugar/should_run/all.T - testsuite/tests/ghci/scripts/T9293.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci024.stdout-mingw32 - testsuite/tests/ghci/scripts/ghci057.stdout-mingw32 - + testsuite/tests/linear/should_fail/T18888.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e57ea51ec6d774d9c86feac171e6a8c4a73aacb2...06e7aed000ff172a2c14030d93011a96d01b2c27 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e57ea51ec6d774d9c86feac171e6a8c4a73aacb2...06e7aed000ff172a2c14030d93011a96d01b2c27 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 Mon Nov 9 21:23:45 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 16:23:45 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5fa9b36193941_10ee3ffb97c66a9c982380@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: a763b7e6 by Ben Gamari at 2020-11-09T16:23:36-05:00 Bump time submodule to 1.11 Closes #18847. - - - - - 4 changed files: - libraries/directory - libraries/hpc - libraries/time - libraries/unix Changes: ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a763b7e6f955be7579de88f24cf09001c2183cf7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a763b7e6f955be7579de88f24cf09001c2183cf7 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 Mon Nov 9 23:17:59 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 18:17:59 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5fa9ce274abaa_10eeeb3d5a41011691@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: a50a3057 by Ben Gamari at 2020-11-09T18:17:44-05:00 Bump time submodule to 1.11 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 5 changed files: - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix Changes: ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a50a30577626c1da258ec0257d22099d59c06e96 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a50a30577626c1da258ec0257d22099d59c06e96 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 Mon Nov 9 23:45:58 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 09 Nov 2020 18:45:58 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 95 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa9d4b68662c_10eeded785010206ef@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d31fec99 by Ben Gamari at 2020-11-09T18:45:44-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 89683bd0 by Sylvain Henry at 2020-11-09T18:45:49-05:00 Export SPEC from GHC.Exts (#13681) - - - - - c354a461 by David Eichmann at 2020-11-09T18:45:50-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 27 changed files: - .gitlab-ci.yml - compiler/GHC/Core/Coercion.hs - compiler/GHC/Data/EnumSet.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Usage.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Linker/Dynamic.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Platform/Ways.hs - compiler/GHC/Rename/HsType.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7bb2827dd28814ba86850d027b25136c3fe886ff...c354a4618876a89af7942dbf435f3da1f73a70d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7bb2827dd28814ba86850d027b25136c3fe886ff...c354a4618876a89af7942dbf435f3da1f73a70d0 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 Tue Nov 10 00:17:34 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 19:17:34 -0500 Subject: [Git][ghc/ghc][wip/backports] 2 commits: testsuite: Update output for T18888_datakinds Message-ID: <5fa9dc1e921bf_10ee3ffbd59275f010271d3@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/backports at Glasgow Haskell Compiler / GHC Commits: 918157d5 by Ben Gamari at 2020-11-09T19:17:08-05:00 testsuite: Update output for T18888_datakinds - - - - - 7fcca77f by Ben Gamari at 2020-11-09T19:17:13-05:00 testsuite: Update output for T12427a - - - - - 2 changed files: - testsuite/tests/linear/should_fail/T18888_datakinds.stderr - testsuite/tests/typecheck/should_compile/T12427a.stderr Changes: ===================================== testsuite/tests/linear/should_fail/T18888_datakinds.stderr ===================================== @@ -1,5 +1,5 @@ -T18888_datakinds.hs:5:9: - Expected kind ‘GHC.Types.Multiplicity’, - but ‘001’ has kind ‘GHC.Num.Natural.Natural’ - In the type signature: f :: a %001 -> b +T18888_datakinds.hs:5:9: error: + • Expected kind ‘GHC.Types.Multiplicity’, + but ‘001’ has kind ‘GHC.Types.Nat’ + • In the type signature: f :: a %001 -> b ===================================== testsuite/tests/typecheck/should_compile/T12427a.stderr ===================================== @@ -2,9 +2,16 @@ T12427a.hs:17:29: error: • Couldn't match expected type ‘p’ with actual type ‘(forall b. [b] -> [b]) -> Int’ + ‘p’ is untouchable + inside the constraints: () + bound by a pattern with constructor: + T1 :: forall a. a -> ((forall b. [b] -> [b]) -> Int) -> T, + in a case alternative + at T12427a.hs:17:19-24 ‘p’ is a rigid type variable bound by the inferred type of h11 :: T -> p at T12427a.hs:17:1-29 + Possible fix: add a type signature for ‘h11’ • In the expression: v In a case alternative: T1 _ v -> v In the expression: case y of { T1 _ v -> v } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06e7aed000ff172a2c14030d93011a96d01b2c27...7fcca77f1b3d315b95de2acc76bdac3512a522ff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06e7aed000ff172a2c14030d93011a96d01b2c27...7fcca77f1b3d315b95de2acc76bdac3512a522ff 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 Tue Nov 10 00:20:04 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 19:20:04 -0500 Subject: [Git][ghc/ghc][wip/unloading] 117 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa9dcb451c53_10ee3ffbade021b0102904e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/unloading at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - befe4a8e by Ömer Sinan Ağacan at 2020-11-09T19:19:57-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 79f42070 by Ray Shih at 2020-11-09T19:19:57-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7470273c by GHC GitLab CI at 2020-11-09T19:19:57-05:00 rts: Introduce highMemDynamic - - - - - b9ca5fd9 by GHC GitLab CI at 2020-11-09T19:19:57-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/Specialise.hs - compiler/GHC/Core/Opt/StaticArgs.hs - compiler/GHC/Core/TyCon/Env.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e686c380d92cf2e57847f4e6d1bc80f38575bf98...b9ca5fd987c82b0fb4124765875942360a9f87bd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e686c380d92cf2e57847f4e6d1bc80f38575bf98...b9ca5fd987c82b0fb4124765875942360a9f87bd 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 Tue Nov 10 00:30:51 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 19:30:51 -0500 Subject: [Git][ghc/ghc][wip/local-symbols-2] 117 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa9df3b6cbda_10ee3ffb9532742410338a2@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/local-symbols-2 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 288d65eb by Ben Gamari at 2020-11-09T19:30:00-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - adbb8dbf by Ben Gamari at 2020-11-09T19:30:00-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - 0dfac9ef by Ben Gamari at 2020-11-09T19:30:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 48dd03d3 by Ben Gamari at 2020-11-09T19:30:10-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d43f05ca139076d33befc5bf41f51e702d38bd54...48dd03d380ca4ff0f2a6ebf8678d1ae819858f61 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d43f05ca139076d33befc5bf41f51e702d38bd54...48dd03d380ca4ff0f2a6ebf8678d1ae819858f61 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 Tue Nov 10 00:46:21 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 19:46:21 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5fa9e2dda248d_10eecd03ed0103816f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: cb242c35 by Ben Gamari at 2020-11-09T19:46:13-05:00 Bump time submodule to 1.11 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 6 changed files: - compiler/ghc.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb242c350fa1bdaecc877567a01639d8c7b78097 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb242c350fa1bdaecc877567a01639d8c7b78097 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 Tue Nov 10 01:39:52 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 20:39:52 -0500 Subject: [Git][ghc/ghc][wip/local-symbols-2] 3 commits: Move this_module into NCGConfig Message-ID: <5fa9ef6845276_10ee3ffb94f16f60104285e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/local-symbols-2 at Glasgow Haskell Compiler / GHC Commits: fcca924a by Ben Gamari at 2020-11-09T20:39:43-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - a8fc9b7c by Ben Gamari at 2020-11-09T20:39:43-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 221aa82a by Ben Gamari at 2020-11-09T20:39:43-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - 12 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - testsuite/tests/regalloc/regalloc_unit_tests.hs Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -118,6 +118,7 @@ module GHC.Cmm.CLabel ( LabelStyle (..), pprDebugCLabel, pprCLabel, + ppInternalProcLabel, -- * Others dynamicLinkerLabelInfo, @@ -1082,8 +1083,8 @@ isLocalCLabel this_mod lbl = -- that data resides in a DLL or not. [Win32 only.] -- @labelDynamic@ returns @True@ if the label is located -- in a DLL, be it a data reference or not. -labelDynamic :: NCGConfig -> Module -> CLabel -> Bool -labelDynamic config this_mod lbl = +labelDynamic :: NCGConfig -> CLabel -> Bool +labelDynamic config lbl = case lbl of -- is the RTS in a DLL or not? RtsLabel _ -> @@ -1136,6 +1137,7 @@ labelDynamic config this_mod lbl = externalDynamicRefs = ncgExternalDynamicRefs config platform = ncgPlatform config os = platformOS platform + this_mod = ncgThisModule config this_unit = toUnitId (moduleUnit this_mod) @@ -1359,6 +1361,39 @@ pprCLabel platform sty lbl = CmmLabel _ _ fs CmmRet -> maybe_underscore $ ftext fs <> text "_ret" CmmLabel _ _ fs CmmClosure -> maybe_underscore $ ftext fs <> text "_closure" +-- Note [Internal proc labels] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Some tools (e.g. the `perf` utility on Linux) rely on the symbol table +-- for resolution of function names. To help these tools we provide the +-- (enabled by default) -fexpose-all-symbols flag which causes GHC to produce +-- symbols even for symbols with are internal to a module (although such +-- symbols will have only local linkage). +-- +-- Note that these labels are *not* referred to by code. They are strictly for +-- diagnostics purposes. +-- +-- To avoid confusion, it is desireable to add a module-qualifier to the +-- symbol name. However, the Name type's Internal constructor doesn't carry +-- knowledge of the current Module. Consequently, we have to pass this around +-- explicitly. + +-- | Generate a label for a procedure internal to a module (if +-- 'Opt_ExposeAllSymbols' is enabled). +-- See Note [Internal proc labels]. +ppInternalProcLabel :: Module -- ^ the current module + -> CLabel + -> Maybe SDoc -- ^ the internal proc label +ppInternalProcLabel this_mod (IdLabel nm _ flavour) + | isInternalName nm + = Just + $ text "_" <> ppr this_mod + <> char '_' + <> ztext (zEncodeFS (occNameFS (occName nm))) + <> char '_' + <> pprUniqueAlways (getUnique nm) + <> ppIdFlavor flavour +ppInternalProcLabel _ _ = Nothing ppIdFlavor :: IdLabelInfo -> SDoc ppIdFlavor x = pp_cSEP <> case x of ===================================== compiler/GHC/Cmm/Info/Build.hs ===================================== @@ -946,7 +946,8 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do topSRT <- get let - config = initNCGConfig dflags + this_mod = thisModule topSRT + config = initNCGConfig dflags this_mod profile = targetProfile dflags platform = profilePlatform profile srtMap = moduleSRTMap topSRT @@ -1019,8 +1020,6 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do in state{ moduleSRTMap = srt_map } - this_mod = thisModule topSRT - allStaticData = all (\(CAFLabel clbl) -> Set.member clbl static_data) caf_lbls @@ -1048,7 +1047,7 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do -- when dynamic linking is used we cannot guarantee that the offset -- between the SRT and the info table will fit in the offset field. -- Consequently we build a singleton SRT in this case. - not (labelDynamic config this_mod lbl) + not (labelDynamic config lbl) -- MachO relocations can't express offsets between compilation units at -- all, so we are always forced to build a singleton SRT in this case. ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -152,11 +152,11 @@ nativeCodeGen :: forall a . DynFlags -> Module -> ModLocation -> Handle -> UniqS -> Stream IO RawCmmGroup a -> IO a nativeCodeGen dflags this_mod modLoc h us cmms - = let config = initNCGConfig dflags + = let config = initNCGConfig dflags this_mod platform = ncgPlatform config nCG' :: ( OutputableP Platform statics, Outputable jumpDest, Instruction instr) => NcgImpl statics instr jumpDest -> IO a - nCG' ncgImpl = nativeCodeGen' dflags config this_mod modLoc ncgImpl h us cmms + nCG' ncgImpl = nativeCodeGen' dflags config modLoc ncgImpl h us cmms in case platformArch platform of ArchX86 -> nCG' (X86.ncgX86 config) ArchX86_64 -> nCG' (X86.ncgX86_64 config) @@ -221,20 +221,20 @@ See also Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock". nativeCodeGen' :: (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a -nativeCodeGen' dflags config this_mod modLoc ncgImpl h us cmms +nativeCodeGen' dflags config modLoc ncgImpl h us cmms = do -- BufHandle is a performance hack. We could hide it inside -- Pretty if it weren't for the fact that we do lots of little -- printDocs here (in order to do codegen in constant space). bufh <- newBufHandle h let ngs0 = NGS [] [] [] [] [] [] emptyUFM mapEmpty - (ngs, us', a) <- cmmNativeGenStream dflags config this_mod modLoc ncgImpl bufh us + (ngs, us', a) <- cmmNativeGenStream dflags config modLoc ncgImpl bufh us cmms ngs0 _ <- finishNativeGen dflags config modLoc bufh us' ngs return a @@ -300,7 +300,7 @@ finishNativeGen dflags config modLoc bufh@(BufHandle _ _ h) us ngs cmmNativeGenStream :: (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> BufHandle -> UniqSupply @@ -308,7 +308,7 @@ cmmNativeGenStream :: (OutputableP Platform statics, Outputable jumpDest, Instru -> NativeGenAcc statics instr -> IO (NativeGenAcc statics instr, UniqSupply, a) -cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs +cmmNativeGenStream dflags config modLoc ncgImpl h us cmm_stream ngs = do r <- Stream.runStream cmm_stream case r of Left a -> @@ -330,7 +330,7 @@ cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs dbgMap = debugToMap ndbgs -- Generate native code - (ngs',us') <- cmmNativeGens dflags config this_mod modLoc ncgImpl h + (ngs',us') <- cmmNativeGens dflags config modLoc ncgImpl h dbgMap us cmms ngs 0 -- Link native code information into debug blocks @@ -345,7 +345,7 @@ cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs let ngs'' = ngs' { ngs_debug = ngs_debug ngs' ++ ldbgs, ngs_labels = [] } return (us', ngs'') - cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us' + cmmNativeGenStream dflags config modLoc ncgImpl h us' cmm_stream' ngs'' where ncglabel = text "NCG" @@ -356,7 +356,7 @@ cmmNativeGens :: forall statics instr jumpDest. (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> BufHandle -> LabelMap DebugBlock @@ -366,7 +366,7 @@ cmmNativeGens :: forall statics instr jumpDest. -> Int -> IO (NativeGenAcc statics instr, UniqSupply) -cmmNativeGens dflags config this_mod modLoc ncgImpl h dbgMap = go +cmmNativeGens dflags config modLoc ncgImpl h dbgMap = go where go :: UniqSupply -> [RawCmmDecl] -> NativeGenAcc statics instr -> Int @@ -379,7 +379,7 @@ cmmNativeGens dflags config this_mod modLoc ncgImpl h dbgMap = go let fileIds = ngs_dwarfFiles ngs (us', fileIds', native, imports, colorStats, linearStats, unwinds) <- {-# SCC "cmmNativeGen" #-} - cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap + cmmNativeGen dflags modLoc ncgImpl us fileIds dbgMap cmm count -- Generate .file directives for every new file that has been @@ -433,7 +433,7 @@ emitNativeCode dflags config h sdoc = do cmmNativeGen :: forall statics instr jumpDest. (Instruction instr, OutputableP Platform statics, Outputable jumpDest) => DynFlags - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> UniqSupply -> DwarfFiles @@ -449,7 +449,7 @@ cmmNativeGen , LabelMap [UnwindPoint] -- unwinding information for blocks ) -cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count +cmmNativeGen dflags modLoc ncgImpl us fileIds dbgMap cmm count = do let config = ncgConfig ncgImpl let platform = ncgPlatform config @@ -467,7 +467,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- cmm to cmm optimisations let (opt_cmm, imports) = {-# SCC "cmmToCmm" #-} - cmmToCmm config this_mod fixed_cmm + cmmToCmm config fixed_cmm dumpIfSet_dyn dflags Opt_D_dump_opt_cmm "Optimised Cmm" FormatCMM @@ -479,7 +479,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- generate native code from cmm let ((native, lastMinuteImports, fileIds', nativeCfgWeights), usGen) = {-# SCC "genMachCode" #-} - initUs us $ genMachCode config this_mod modLoc + initUs us $ genMachCode config modLoc (cmmTopCodeGen ncgImpl) fileIds dbgMap opt_cmm cmmCfg @@ -914,7 +914,7 @@ apply_mapping ncgImpl ufm (CmmProc info lbl live (ListGraph blocks)) genMachCode :: NCGConfig - -> Module -> ModLocation + -> ModLocation -> (RawCmmDecl -> NatM [NatCmmDecl statics instr]) -> DwarfFiles -> LabelMap DebugBlock @@ -927,9 +927,9 @@ genMachCode , CFG ) -genMachCode config this_mod modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg +genMachCode config modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg = do { initial_us <- getUniqueSupplyM - ; let initial_st = mkNatM_State initial_us 0 config this_mod + ; let initial_st = mkNatM_State initial_us 0 config modLoc fileIds dbgMap cmm_cfg (new_tops, final_st) = initNat initial_st (cmmTopCodeGen cmm_top) final_delta = natm_delta final_st @@ -966,10 +966,10 @@ Ideas for other things we could do (put these in Hoopl please!): temp assignments, and certain assigns to mem...) -} -cmmToCmm :: NCGConfig -> Module -> RawCmmDecl -> (RawCmmDecl, [CLabel]) -cmmToCmm _ _ top@(CmmData _ _) = (top, []) -cmmToCmm config this_mod (CmmProc info lbl live graph) - = runCmmOpt config this_mod $ +cmmToCmm :: NCGConfig -> RawCmmDecl -> (RawCmmDecl, [CLabel]) +cmmToCmm _ top@(CmmData _ _) = (top, []) +cmmToCmm config (CmmProc info lbl live graph) + = runCmmOpt config (ncgThisModule config) $ do blocks' <- mapM cmmBlockConFold (toBlockList graph) return $ CmmProc info lbl live (ofBlockList (g_entry graph) blocks') @@ -986,24 +986,23 @@ pattern OptMResult x y = (# x, y #) data OptMResult a = OptMResult !a ![CLabel] deriving (Functor) #endif -newtype CmmOptM a = CmmOptM (NCGConfig -> Module -> [CLabel] -> OptMResult a) +newtype CmmOptM a = CmmOptM (NCGConfig -> [CLabel] -> OptMResult a) deriving (Functor) instance Applicative CmmOptM where - pure x = CmmOptM $ \_ _ imports -> OptMResult x imports + pure x = CmmOptM $ \_ imports -> OptMResult x imports (<*>) = ap instance Monad CmmOptM where (CmmOptM f) >>= g = - CmmOptM $ \config this_mod imports0 -> - case f config this_mod imports0 of + CmmOptM $ \config imports0 -> + case f config imports0 of OptMResult x imports1 -> case g x of - CmmOptM g' -> g' config this_mod imports1 + CmmOptM g' -> g' config imports1 instance CmmMakeDynamicReferenceM CmmOptM where addImport = addImportCmmOpt - getThisModule = CmmOptM $ \_ this_mod imports -> OptMResult this_mod imports addImportCmmOpt :: CLabel -> CmmOptM () addImportCmmOpt lbl = CmmOptM $ \_ _ imports -> OptMResult () (lbl:imports) @@ -1011,9 +1010,9 @@ addImportCmmOpt lbl = CmmOptM $ \_ _ imports -> OptMResult () (lbl:imports) getCmmOptConfig :: CmmOptM NCGConfig getCmmOptConfig = CmmOptM $ \config _ imports -> OptMResult config imports -runCmmOpt :: NCGConfig -> Module -> CmmOptM a -> (a, [CLabel]) -runCmmOpt config this_mod (CmmOptM f) = - case f config this_mod [] of +runCmmOpt :: NCGConfig -> CmmOptM a -> (a, [CLabel]) +runCmmOpt config (CmmOptM f) = + case f config [] of OptMResult result imports -> (result, imports) cmmBlockConFold :: CmmBlock -> CmmOptM CmmBlock @@ -1143,9 +1142,10 @@ cmmExprNative referenceKind expr = do -> return other -- | Initialize the native code generator configuration from the DynFlags -initNCGConfig :: DynFlags -> NCGConfig -initNCGConfig dflags = NCGConfig +initNCGConfig :: DynFlags -> Module -> NCGConfig +initNCGConfig dflags this_mod = NCGConfig { ncgPlatform = targetPlatform dflags + , ncgThisModule = this_mod , ncgAsmContext = initSDocContext dflags (PprCode AsmStyle) , ncgProcAlignment = cmmProcAlignment dflags , ncgExternalDynamicRefs = gopt Opt_ExternalDynamicRefs dflags @@ -1190,5 +1190,6 @@ initNCGConfig dflags = NCGConfig , ncgDwarfEnabled = debugLevel dflags > 0 , ncgDwarfUnwindings = debugLevel dflags >= 1 , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. + , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags } ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -11,12 +11,14 @@ import GHC.Prelude import GHC.Platform import GHC.Cmm.Type (Width(..)) import GHC.CmmToAsm.CFG.Weight +import GHC.Unit.Module (Module) import GHC.Utils.Outputable -- | Native code generator configuration data NCGConfig = NCGConfig { ncgPlatform :: !Platform -- ^ Target platform , ncgAsmContext :: !SDocContext -- ^ Context for ASM code generation + , ncgThisModule :: !Module -- ^ The name of the module we are currently compiling , ncgProcAlignment :: !(Maybe Int) -- ^ Mandatory proc alignment , ncgExternalDynamicRefs :: !Bool -- ^ Generate code to link against dynamic libraries , ncgPIC :: !Bool -- ^ Enable Position-Independent Code @@ -37,6 +39,7 @@ data NCGConfig = NCGConfig , ncgDwarfEnabled :: !Bool -- ^ Enable Dwarf generation , ncgDwarfUnwindings :: !Bool -- ^ Enable unwindings , ncgDwarfStripBlockInfo :: !Bool -- ^ Strip out block information from generated Dwarf + , ncgExposeInternalSymbols :: !Bool -- ^ Expose symbol table entries for internal symbols } -- | Return Word size ===================================== compiler/GHC/CmmToAsm/Monad.hs ===================================== @@ -80,6 +80,8 @@ data NcgImpl statics instr jumpDest = NcgImpl { canShortcut :: instr -> Maybe jumpDest, shortcutStatics :: (BlockId -> Maybe jumpDest) -> statics -> statics, shortcutJump :: (BlockId -> Maybe jumpDest) -> instr -> instr, + -- | 'Module' is only for printing internal labels. See Note [Internal proc + -- labels] in CLabel. pprNatCmmDecl :: NatCmmDecl statics instr -> SDoc, maxSpillSlots :: Int, allocatableRegs :: [RealReg], @@ -107,7 +109,6 @@ data NatM_State natm_imports :: [(CLabel)], natm_pic :: Maybe Reg, natm_config :: NCGConfig, - natm_this_module :: Module, natm_modloc :: ModLocation, natm_fileid :: DwarfFiles, natm_debug_map :: LabelMap DebugBlock, @@ -125,9 +126,9 @@ newtype NatM result = NatM (NatM_State -> (result, NatM_State)) unNat :: NatM a -> NatM_State -> (a, NatM_State) unNat (NatM a) = a -mkNatM_State :: UniqSupply -> Int -> NCGConfig -> Module -> ModLocation -> +mkNatM_State :: UniqSupply -> Int -> NCGConfig -> ModLocation -> DwarfFiles -> LabelMap DebugBlock -> CFG -> NatM_State -mkNatM_State us delta config this_mod +mkNatM_State us delta config = \loc dwf dbg cfg -> NatM_State { natm_us = us @@ -135,7 +136,6 @@ mkNatM_State us delta config this_mod , natm_imports = [] , natm_pic = Nothing , natm_config = config - , natm_this_module = this_mod , natm_modloc = loc , natm_fileid = dwf , natm_debug_map = dbg @@ -198,10 +198,11 @@ getCfgWeights = NatM $ \ st -> (ncgCfgWeights (natm_config st), st) setDeltaNat :: Int -> NatM () setDeltaNat delta = NatM $ \ st -> ((), st {natm_delta = delta}) - getThisModuleNat :: NatM Module -getThisModuleNat = NatM $ \ st -> (natm_this_module st, st) +getThisModuleNat = NatM $ \ st -> (ncgThisModule $ natm_config st, st) +instance HasModule NatM where + getModule = getThisModuleNat addImportNat :: CLabel -> NatM () addImportNat imp ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -65,7 +65,6 @@ import GHC.Cmm import GHC.Cmm.CLabel import GHC.Types.Basic -import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Utils.Panic @@ -95,11 +94,9 @@ data ReferenceKind class Monad m => CmmMakeDynamicReferenceM m where addImport :: CLabel -> m () - getThisModule :: m Module instance CmmMakeDynamicReferenceM NatM where addImport = addImportNat - getThisModule = getThisModuleNat cmmMakeDynamicReference :: CmmMakeDynamicReferenceM m @@ -113,13 +110,11 @@ cmmMakeDynamicReference config referenceKind lbl = return $ CmmLit $ CmmLabel lbl -- already processed it, pass through | otherwise - = do this_mod <- getThisModule - let platform = ncgPlatform config + = do let platform = ncgPlatform config case howToAccessLabel config (platformArch platform) (platformOS platform) - this_mod referenceKind lbl of AccessViaStub -> do @@ -208,7 +203,7 @@ data LabelAccessStyle | AccessViaSymbolPtr | AccessDirectly -howToAccessLabel :: NCGConfig -> Arch -> OS -> Module -> ReferenceKind -> CLabel -> LabelAccessStyle +howToAccessLabel :: NCGConfig -> Arch -> OS -> ReferenceKind -> CLabel -> LabelAccessStyle -- Windows -- In Windows speak, a "module" is a set of objects linked into the @@ -231,7 +226,7 @@ howToAccessLabel :: NCGConfig -> Arch -> OS -> Module -> ReferenceKind -> CLabel -- into the same .exe file. In this case we always access symbols directly, -- and never use __imp_SYMBOL. -- -howToAccessLabel config _ OSMinGW32 this_mod _ lbl +howToAccessLabel config _arch OSMinGW32 _kind lbl -- Assume all symbols will be in the same PE, so just access them directly. | not (ncgExternalDynamicRefs config) @@ -239,7 +234,7 @@ howToAccessLabel config _ OSMinGW32 this_mod _ lbl -- If the target symbol is in another PE we need to access it via the -- appropriate __imp_SYMBOL pointer. - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr -- Target symbol is in the same PE as the caller, so just access it directly. @@ -255,9 +250,9 @@ howToAccessLabel config _ OSMinGW32 this_mod _ lbl -- It is always possible to access something indirectly, -- even when it's not necessary. -- -howToAccessLabel config arch OSDarwin this_mod DataReference lbl +howToAccessLabel config arch OSDarwin DataReference lbl -- data access to a dynamic library goes via a symbol pointer - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr -- when generating PIC code, all cross-module data references must @@ -276,21 +271,21 @@ howToAccessLabel config arch OSDarwin this_mod DataReference lbl | otherwise = AccessDirectly -howToAccessLabel config arch OSDarwin this_mod JumpReference lbl +howToAccessLabel config arch OSDarwin JumpReference lbl -- dyld code stubs don't work for tailcalls because the -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: | arch == ArchX86 || arch == ArchX86_64 - , labelDynamic config this_mod lbl + , labelDynamic config lbl = AccessViaSymbolPtr -howToAccessLabel config arch OSDarwin this_mod _ lbl +howToAccessLabel config arch OSDarwin _kind lbl -- Code stubs are the usual method of choice for imported code; -- not needed on x86_64 because Apple's new linker, ld64, generates -- them automatically. | arch /= ArchX86_64 - , labelDynamic config this_mod lbl + , labelDynamic config lbl = AccessViaStub | otherwise @@ -301,7 +296,7 @@ howToAccessLabel config arch OSDarwin this_mod _ lbl -- AIX -- quite simple (for now) -howToAccessLabel _config _arch OSAIX _this_mod kind _lbl +howToAccessLabel _config _arch OSAIX kind _lbl = case kind of DataReference -> AccessViaSymbolPtr CallReference -> AccessDirectly @@ -318,7 +313,7 @@ howToAccessLabel _config _arch OSAIX _this_mod kind _lbl -- from position independent code. It is also required from the main program -- when dynamic libraries containing Haskell code are used. -howToAccessLabel _ (ArchPPC_64 _) os _ kind _ +howToAccessLabel _config (ArchPPC_64 _) os kind _lbl | osElfTarget os = case kind of -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC @@ -330,7 +325,7 @@ howToAccessLabel _ (ArchPPC_64 _) os _ kind _ -- regular calls are handled by the runtime linker _ -> AccessDirectly -howToAccessLabel config _ os _ _ _ +howToAccessLabel config _arch os _kind _lbl -- no PIC -> the dynamic linker does everything for us; -- if we don't dynamically link to Haskell code, -- it actually manages to do so without messing things up. @@ -339,11 +334,11 @@ howToAccessLabel config _ os _ _ _ not (ncgExternalDynamicRefs config) = AccessDirectly -howToAccessLabel config arch os this_mod DataReference lbl +howToAccessLabel config arch os DataReference lbl | osElfTarget os = case () of -- A dynamic label needs to be accessed via a symbol pointer. - _ | labelDynamic config this_mod lbl + _ | labelDynamic config lbl -> AccessViaSymbolPtr -- For PowerPC32 -fPIC, we have to access even static data @@ -369,25 +364,25 @@ howToAccessLabel config arch os this_mod DataReference lbl -- (AccessDirectly, because we get an implicit symbol stub) -- and calling functions from PIC code on non-i386 platforms (via a symbol stub) -howToAccessLabel config arch os this_mod CallReference lbl +howToAccessLabel config arch os CallReference lbl | osElfTarget os - , labelDynamic config this_mod lbl && not (ncgPIC config) + , labelDynamic config lbl && not (ncgPIC config) = AccessDirectly | osElfTarget os , arch /= ArchX86 - , labelDynamic config this_mod lbl + , labelDynamic config lbl , ncgPIC config = AccessViaStub -howToAccessLabel config _ os this_mod _ lbl +howToAccessLabel config _arch os _kind lbl | osElfTarget os - = if labelDynamic config this_mod lbl + = if labelDynamic config lbl then AccessViaSymbolPtr else AccessDirectly -- all other platforms -howToAccessLabel config _ _ _ _ _ +howToAccessLabel config _arch _os _kind _lbl | not (ncgPIC config) = AccessDirectly ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -90,6 +90,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = -- special case for code without info table: pprSectionAlign config (Section Text lbl) $$ pprProcAlignment config $$ + pprProcLabel config lbl $$ pprLabel platform lbl $$ -- blocks guaranteed not null, so label needed vcat (map (pprBasicBlock config top_info) blocks) $$ (if ncgDwarfEnabled config @@ -99,6 +100,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = Just (CmmStaticsRaw info_lbl _) -> pprSectionAlign config (Section Text info_lbl) $$ pprProcAlignment config $$ + pprProcLabel config lbl $$ (if platformHasSubsectionsViaSymbols platform then pdoc platform (mkDeadStripPreventer info_lbl) <> char ':' else empty) $$ @@ -114,6 +116,15 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = else empty) $$ pprSizeDecl platform info_lbl +-- | Output an internal proc label. See Note [Internal proc labels] in CLabel. +pprProcLabel :: NCGConfig -> CLabel -> SDoc +pprProcLabel config lbl + | ncgExposeInternalSymbols config + , Just lbl' <- ppInternalProcLabel (ncgThisModule config) lbl + = lbl' <> char ':' + | otherwise + = empty + -- | Output the ELF .size directive. pprSizeDecl :: Platform -> CLabel -> SDoc pprSizeDecl platform lbl ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -274,6 +274,7 @@ data GeneralFlag -- forwards all -L flags to the collect2 command without using a -- response file and as such breaking apart. | Opt_SingleLibFolder + | Opt_ExposeInternalSymbols | Opt_KeepCAFs | Opt_KeepGoing | Opt_ByteCode ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -376,7 +376,6 @@ import qualified GHC.LanguageExtensions as LangExt -- ----------------------------------------------------------------------------- -- DynFlags - -- | Used to differentiate the scope an include needs to apply to. -- We have to split the include paths to avoid accidentally forcing recursive -- includes since -I overrides the system search paths. See #14312. @@ -3417,6 +3416,7 @@ fFlagsDeps = [ flagSpec "error-spans" Opt_ErrorSpans, flagSpec "excess-precision" Opt_ExcessPrecision, flagSpec "expose-all-unfoldings" Opt_ExposeAllUnfoldings, + flagSpec "expose-internal-symbols" Opt_ExposeInternalSymbols, flagSpec "external-dynamic-refs" Opt_ExternalDynamicRefs, flagSpec "external-interpreter" Opt_ExternalInterpreter, flagSpec "flat-cache" Opt_FlatCache, @@ -4419,7 +4419,13 @@ setVerbosity :: Maybe Int -> DynP () setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 }) setDebugLevel :: Maybe Int -> DynP () -setDebugLevel mb_n = upd (\dfs -> dfs{ debugLevel = mb_n `orElse` 2 }) +setDebugLevel mb_n = + upd (\dfs -> exposeSyms $ dfs{ debugLevel = n }) + where + n = mb_n `orElse` 2 + exposeSyms + | n > 2 = setGeneralFlag' Opt_ExposeInternalSymbols + | otherwise = id data PkgDbRef = GlobalPkgDb ===================================== docs/users_guide/debug-info.rst ===================================== @@ -14,6 +14,7 @@ useable by most UNIX debugging tools. :category: debugging :since: 7.10, numeric levels since 8.0 + :implies: :ghc-flag:`-fexpose-internal-symbols` when ⟨n⟩ >= 2. Emit debug information in object code. Currently only DWARF debug information is supported on x86-64 and i386. Currently debug levels 0 ===================================== docs/users_guide/phases.rst ===================================== @@ -720,6 +720,20 @@ Options affecting code generation all target platforms. See the :ghc-flag:`--print-object-splitting-supported` flag to check whether your GHC supports object splitting. +.. ghc-flag:: -fexpose-internal-symbols + :shortdesc: Produce symbols for all functions, including internal functions. + :type: dynamic + :category: codegen + + Request that GHC emits verbose symbol tables which include local symbols + for module-internal functions. These can be useful for tools like + :ref:`perf ` but increase object file sizes. + This is implied by :ghc-flag:`-g2 <-g>` and above. + + :ghc-flag:`-fno-expose-internal-symbols <-fexpose-internal-symbols>` + suppresses all non-global symbol table entries, resulting in smaller object + file sizes at the expense of debuggability. + .. _options-linker: Options affecting linking ===================================== testsuite/tests/regalloc/regalloc_unit_tests.hs ===================================== @@ -106,7 +106,7 @@ compileCmmForRegAllocStats :: IO [( Maybe [Color.RegAllocStats (Alignment, RawCmmStatics) X86.Instr.Instr] , Maybe [Linear.RegAllocStats])] compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do - let ncgImpl = ncgImplF (initNCGConfig dflags) + let ncgImpl = ncgImplF (initNCGConfig dflags thisMod) hscEnv <- newHscEnv dflags -- parse the cmm file and output any warnings or errors @@ -126,7 +126,7 @@ compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do -- compile and discard the generated code, returning regalloc stats mapM (\ (count, thisCmm) -> - cmmNativeGen dflags thisMod thisModLoc ncgImpl + cmmNativeGen dflags thisModLoc ncgImpl usb dwarfFileIds dbgMap thisCmm count >>= (\(_, _, _, _, colorStats, linearStats, _) -> -- scrub unneeded output from cmmNativeGen View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/48dd03d380ca4ff0f2a6ebf8678d1ae819858f61...221aa82af64d3d40bcd8c341c13677acb50cb476 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/48dd03d380ca4ff0f2a6ebf8678d1ae819858f61...221aa82af64d3d40bcd8c341c13677acb50cb476 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 Tue Nov 10 01:48:47 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 20:48:47 -0500 Subject: [Git][ghc/ghc][wip/T17609] 111 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fa9f17f624c6_10ee3ffbc4d82250106014e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 7dd803e6 by Ben Gamari at 2020-11-09T20:48:42-05:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - ab96a4ad by Ben Gamari at 2020-11-09T20:48:42-05:00 Add Note cross-reference for unique tag allocations - - - - - 29 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Data/EnumSet.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Foreign/Decl.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b037879d83f6751e5b4a48ec14952217626385af...ab96a4ad5eec76235d1512d8e64ee5a013862a6a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b037879d83f6751e5b4a48ec14952217626385af...ab96a4ad5eec76235d1512d8e64ee5a013862a6a 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 Tue Nov 10 01:59:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 20:59:25 -0500 Subject: [Git][ghc/ghc][wip/local-symbols-2] 3 commits: Move this_module into NCGConfig Message-ID: <5fa9f3fd613d4_10ee3ffb97843f141061473@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/local-symbols-2 at Glasgow Haskell Compiler / GHC Commits: e458aa6f by Ben Gamari at 2020-11-09T20:59:15-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - 90e5fbf2 by Ben Gamari at 2020-11-09T20:59:15-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 151f6f6f by Ben Gamari at 2020-11-09T20:59:15-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - 12 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - testsuite/tests/regalloc/regalloc_unit_tests.hs Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -118,6 +118,7 @@ module GHC.Cmm.CLabel ( LabelStyle (..), pprDebugCLabel, pprCLabel, + ppInternalProcLabel, -- * Others dynamicLinkerLabelInfo, @@ -1082,8 +1083,8 @@ isLocalCLabel this_mod lbl = -- that data resides in a DLL or not. [Win32 only.] -- @labelDynamic@ returns @True@ if the label is located -- in a DLL, be it a data reference or not. -labelDynamic :: NCGConfig -> Module -> CLabel -> Bool -labelDynamic config this_mod lbl = +labelDynamic :: NCGConfig -> CLabel -> Bool +labelDynamic config lbl = case lbl of -- is the RTS in a DLL or not? RtsLabel _ -> @@ -1136,6 +1137,7 @@ labelDynamic config this_mod lbl = externalDynamicRefs = ncgExternalDynamicRefs config platform = ncgPlatform config os = platformOS platform + this_mod = ncgThisModule config this_unit = toUnitId (moduleUnit this_mod) @@ -1359,6 +1361,39 @@ pprCLabel platform sty lbl = CmmLabel _ _ fs CmmRet -> maybe_underscore $ ftext fs <> text "_ret" CmmLabel _ _ fs CmmClosure -> maybe_underscore $ ftext fs <> text "_closure" +-- Note [Internal proc labels] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Some tools (e.g. the `perf` utility on Linux) rely on the symbol table +-- for resolution of function names. To help these tools we provide the +-- (enabled by default) -fexpose-all-symbols flag which causes GHC to produce +-- symbols even for symbols with are internal to a module (although such +-- symbols will have only local linkage). +-- +-- Note that these labels are *not* referred to by code. They are strictly for +-- diagnostics purposes. +-- +-- To avoid confusion, it is desireable to add a module-qualifier to the +-- symbol name. However, the Name type's Internal constructor doesn't carry +-- knowledge of the current Module. Consequently, we have to pass this around +-- explicitly. + +-- | Generate a label for a procedure internal to a module (if +-- 'Opt_ExposeAllSymbols' is enabled). +-- See Note [Internal proc labels]. +ppInternalProcLabel :: Module -- ^ the current module + -> CLabel + -> Maybe SDoc -- ^ the internal proc label +ppInternalProcLabel this_mod (IdLabel nm _ flavour) + | isInternalName nm + = Just + $ text "_" <> ppr this_mod + <> char '_' + <> ztext (zEncodeFS (occNameFS (occName nm))) + <> char '_' + <> pprUniqueAlways (getUnique nm) + <> ppIdFlavor flavour +ppInternalProcLabel _ _ = Nothing ppIdFlavor :: IdLabelInfo -> SDoc ppIdFlavor x = pp_cSEP <> case x of ===================================== compiler/GHC/Cmm/Info/Build.hs ===================================== @@ -946,7 +946,8 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do topSRT <- get let - config = initNCGConfig dflags + this_mod = thisModule topSRT + config = initNCGConfig dflags this_mod profile = targetProfile dflags platform = profilePlatform profile srtMap = moduleSRTMap topSRT @@ -1019,8 +1020,6 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do in state{ moduleSRTMap = srt_map } - this_mod = thisModule topSRT - allStaticData = all (\(CAFLabel clbl) -> Set.member clbl static_data) caf_lbls @@ -1048,7 +1047,7 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do -- when dynamic linking is used we cannot guarantee that the offset -- between the SRT and the info table will fit in the offset field. -- Consequently we build a singleton SRT in this case. - not (labelDynamic config this_mod lbl) + not (labelDynamic config lbl) -- MachO relocations can't express offsets between compilation units at -- all, so we are always forced to build a singleton SRT in this case. ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -152,11 +152,11 @@ nativeCodeGen :: forall a . DynFlags -> Module -> ModLocation -> Handle -> UniqS -> Stream IO RawCmmGroup a -> IO a nativeCodeGen dflags this_mod modLoc h us cmms - = let config = initNCGConfig dflags + = let config = initNCGConfig dflags this_mod platform = ncgPlatform config nCG' :: ( OutputableP Platform statics, Outputable jumpDest, Instruction instr) => NcgImpl statics instr jumpDest -> IO a - nCG' ncgImpl = nativeCodeGen' dflags config this_mod modLoc ncgImpl h us cmms + nCG' ncgImpl = nativeCodeGen' dflags config modLoc ncgImpl h us cmms in case platformArch platform of ArchX86 -> nCG' (X86.ncgX86 config) ArchX86_64 -> nCG' (X86.ncgX86_64 config) @@ -221,20 +221,20 @@ See also Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock". nativeCodeGen' :: (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a -nativeCodeGen' dflags config this_mod modLoc ncgImpl h us cmms +nativeCodeGen' dflags config modLoc ncgImpl h us cmms = do -- BufHandle is a performance hack. We could hide it inside -- Pretty if it weren't for the fact that we do lots of little -- printDocs here (in order to do codegen in constant space). bufh <- newBufHandle h let ngs0 = NGS [] [] [] [] [] [] emptyUFM mapEmpty - (ngs, us', a) <- cmmNativeGenStream dflags config this_mod modLoc ncgImpl bufh us + (ngs, us', a) <- cmmNativeGenStream dflags config modLoc ncgImpl bufh us cmms ngs0 _ <- finishNativeGen dflags config modLoc bufh us' ngs return a @@ -300,7 +300,7 @@ finishNativeGen dflags config modLoc bufh@(BufHandle _ _ h) us ngs cmmNativeGenStream :: (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> BufHandle -> UniqSupply @@ -308,7 +308,7 @@ cmmNativeGenStream :: (OutputableP Platform statics, Outputable jumpDest, Instru -> NativeGenAcc statics instr -> IO (NativeGenAcc statics instr, UniqSupply, a) -cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs +cmmNativeGenStream dflags config modLoc ncgImpl h us cmm_stream ngs = do r <- Stream.runStream cmm_stream case r of Left a -> @@ -330,7 +330,7 @@ cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs dbgMap = debugToMap ndbgs -- Generate native code - (ngs',us') <- cmmNativeGens dflags config this_mod modLoc ncgImpl h + (ngs',us') <- cmmNativeGens dflags config modLoc ncgImpl h dbgMap us cmms ngs 0 -- Link native code information into debug blocks @@ -345,7 +345,7 @@ cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs let ngs'' = ngs' { ngs_debug = ngs_debug ngs' ++ ldbgs, ngs_labels = [] } return (us', ngs'') - cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us' + cmmNativeGenStream dflags config modLoc ncgImpl h us' cmm_stream' ngs'' where ncglabel = text "NCG" @@ -356,7 +356,7 @@ cmmNativeGens :: forall statics instr jumpDest. (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> BufHandle -> LabelMap DebugBlock @@ -366,7 +366,7 @@ cmmNativeGens :: forall statics instr jumpDest. -> Int -> IO (NativeGenAcc statics instr, UniqSupply) -cmmNativeGens dflags config this_mod modLoc ncgImpl h dbgMap = go +cmmNativeGens dflags config modLoc ncgImpl h dbgMap = go where go :: UniqSupply -> [RawCmmDecl] -> NativeGenAcc statics instr -> Int @@ -379,7 +379,7 @@ cmmNativeGens dflags config this_mod modLoc ncgImpl h dbgMap = go let fileIds = ngs_dwarfFiles ngs (us', fileIds', native, imports, colorStats, linearStats, unwinds) <- {-# SCC "cmmNativeGen" #-} - cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap + cmmNativeGen dflags modLoc ncgImpl us fileIds dbgMap cmm count -- Generate .file directives for every new file that has been @@ -433,7 +433,7 @@ emitNativeCode dflags config h sdoc = do cmmNativeGen :: forall statics instr jumpDest. (Instruction instr, OutputableP Platform statics, Outputable jumpDest) => DynFlags - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> UniqSupply -> DwarfFiles @@ -449,7 +449,7 @@ cmmNativeGen , LabelMap [UnwindPoint] -- unwinding information for blocks ) -cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count +cmmNativeGen dflags modLoc ncgImpl us fileIds dbgMap cmm count = do let config = ncgConfig ncgImpl let platform = ncgPlatform config @@ -467,7 +467,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- cmm to cmm optimisations let (opt_cmm, imports) = {-# SCC "cmmToCmm" #-} - cmmToCmm config this_mod fixed_cmm + cmmToCmm config fixed_cmm dumpIfSet_dyn dflags Opt_D_dump_opt_cmm "Optimised Cmm" FormatCMM @@ -479,7 +479,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- generate native code from cmm let ((native, lastMinuteImports, fileIds', nativeCfgWeights), usGen) = {-# SCC "genMachCode" #-} - initUs us $ genMachCode config this_mod modLoc + initUs us $ genMachCode config modLoc (cmmTopCodeGen ncgImpl) fileIds dbgMap opt_cmm cmmCfg @@ -914,7 +914,7 @@ apply_mapping ncgImpl ufm (CmmProc info lbl live (ListGraph blocks)) genMachCode :: NCGConfig - -> Module -> ModLocation + -> ModLocation -> (RawCmmDecl -> NatM [NatCmmDecl statics instr]) -> DwarfFiles -> LabelMap DebugBlock @@ -927,9 +927,9 @@ genMachCode , CFG ) -genMachCode config this_mod modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg +genMachCode config modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg = do { initial_us <- getUniqueSupplyM - ; let initial_st = mkNatM_State initial_us 0 config this_mod + ; let initial_st = mkNatM_State initial_us 0 config modLoc fileIds dbgMap cmm_cfg (new_tops, final_st) = initNat initial_st (cmmTopCodeGen cmm_top) final_delta = natm_delta final_st @@ -966,10 +966,10 @@ Ideas for other things we could do (put these in Hoopl please!): temp assignments, and certain assigns to mem...) -} -cmmToCmm :: NCGConfig -> Module -> RawCmmDecl -> (RawCmmDecl, [CLabel]) -cmmToCmm _ _ top@(CmmData _ _) = (top, []) -cmmToCmm config this_mod (CmmProc info lbl live graph) - = runCmmOpt config this_mod $ +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') @@ -986,34 +986,33 @@ pattern OptMResult x y = (# x, y #) data OptMResult a = OptMResult !a ![CLabel] deriving (Functor) #endif -newtype CmmOptM a = CmmOptM (NCGConfig -> Module -> [CLabel] -> OptMResult a) +newtype CmmOptM a = CmmOptM (NCGConfig -> [CLabel] -> OptMResult a) deriving (Functor) instance Applicative CmmOptM where - pure x = CmmOptM $ \_ _ imports -> OptMResult x imports + pure x = CmmOptM $ \_ imports -> OptMResult x imports (<*>) = ap instance Monad CmmOptM where (CmmOptM f) >>= g = - CmmOptM $ \config this_mod imports0 -> - case f config this_mod imports0 of + CmmOptM $ \config imports0 -> + case f config imports0 of OptMResult x imports1 -> case g x of - CmmOptM g' -> g' config this_mod imports1 + CmmOptM g' -> g' config imports1 instance CmmMakeDynamicReferenceM CmmOptM where addImport = addImportCmmOpt - getThisModule = CmmOptM $ \_ this_mod imports -> OptMResult this_mod imports addImportCmmOpt :: CLabel -> CmmOptM () -addImportCmmOpt lbl = CmmOptM $ \_ _ imports -> OptMResult () (lbl:imports) +addImportCmmOpt lbl = CmmOptM $ \_ imports -> OptMResult () (lbl:imports) getCmmOptConfig :: CmmOptM NCGConfig -getCmmOptConfig = CmmOptM $ \config _ imports -> OptMResult config imports +getCmmOptConfig = CmmOptM $ \config imports -> OptMResult config imports -runCmmOpt :: NCGConfig -> Module -> CmmOptM a -> (a, [CLabel]) -runCmmOpt config this_mod (CmmOptM f) = - case f config this_mod [] of +runCmmOpt :: NCGConfig -> CmmOptM a -> (a, [CLabel]) +runCmmOpt config (CmmOptM f) = + case f config [] of OptMResult result imports -> (result, imports) cmmBlockConFold :: CmmBlock -> CmmOptM CmmBlock @@ -1143,9 +1142,10 @@ cmmExprNative referenceKind expr = do -> return other -- | Initialize the native code generator configuration from the DynFlags -initNCGConfig :: DynFlags -> NCGConfig -initNCGConfig dflags = NCGConfig +initNCGConfig :: DynFlags -> Module -> NCGConfig +initNCGConfig dflags this_mod = NCGConfig { ncgPlatform = targetPlatform dflags + , ncgThisModule = this_mod , ncgAsmContext = initSDocContext dflags (PprCode AsmStyle) , ncgProcAlignment = cmmProcAlignment dflags , ncgExternalDynamicRefs = gopt Opt_ExternalDynamicRefs dflags @@ -1190,5 +1190,6 @@ initNCGConfig dflags = NCGConfig , ncgDwarfEnabled = debugLevel dflags > 0 , ncgDwarfUnwindings = debugLevel dflags >= 1 , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. + , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags } ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -11,12 +11,14 @@ import GHC.Prelude import GHC.Platform import GHC.Cmm.Type (Width(..)) import GHC.CmmToAsm.CFG.Weight +import GHC.Unit.Module (Module) import GHC.Utils.Outputable -- | Native code generator configuration data NCGConfig = NCGConfig { ncgPlatform :: !Platform -- ^ Target platform , ncgAsmContext :: !SDocContext -- ^ Context for ASM code generation + , ncgThisModule :: !Module -- ^ The name of the module we are currently compiling , ncgProcAlignment :: !(Maybe Int) -- ^ Mandatory proc alignment , ncgExternalDynamicRefs :: !Bool -- ^ Generate code to link against dynamic libraries , ncgPIC :: !Bool -- ^ Enable Position-Independent Code @@ -37,6 +39,7 @@ data NCGConfig = NCGConfig , ncgDwarfEnabled :: !Bool -- ^ Enable Dwarf generation , ncgDwarfUnwindings :: !Bool -- ^ Enable unwindings , ncgDwarfStripBlockInfo :: !Bool -- ^ Strip out block information from generated Dwarf + , ncgExposeInternalSymbols :: !Bool -- ^ Expose symbol table entries for internal symbols } -- | Return Word size ===================================== compiler/GHC/CmmToAsm/Monad.hs ===================================== @@ -80,6 +80,8 @@ data NcgImpl statics instr jumpDest = NcgImpl { canShortcut :: instr -> Maybe jumpDest, shortcutStatics :: (BlockId -> Maybe jumpDest) -> statics -> statics, shortcutJump :: (BlockId -> Maybe jumpDest) -> instr -> instr, + -- | 'Module' is only for printing internal labels. See Note [Internal proc + -- labels] in CLabel. pprNatCmmDecl :: NatCmmDecl statics instr -> SDoc, maxSpillSlots :: Int, allocatableRegs :: [RealReg], @@ -107,7 +109,6 @@ data NatM_State natm_imports :: [(CLabel)], natm_pic :: Maybe Reg, natm_config :: NCGConfig, - natm_this_module :: Module, natm_modloc :: ModLocation, natm_fileid :: DwarfFiles, natm_debug_map :: LabelMap DebugBlock, @@ -125,9 +126,9 @@ newtype NatM result = NatM (NatM_State -> (result, NatM_State)) unNat :: NatM a -> NatM_State -> (a, NatM_State) unNat (NatM a) = a -mkNatM_State :: UniqSupply -> Int -> NCGConfig -> Module -> ModLocation -> +mkNatM_State :: UniqSupply -> Int -> NCGConfig -> ModLocation -> DwarfFiles -> LabelMap DebugBlock -> CFG -> NatM_State -mkNatM_State us delta config this_mod +mkNatM_State us delta config = \loc dwf dbg cfg -> NatM_State { natm_us = us @@ -135,7 +136,6 @@ mkNatM_State us delta config this_mod , natm_imports = [] , natm_pic = Nothing , natm_config = config - , natm_this_module = this_mod , natm_modloc = loc , natm_fileid = dwf , natm_debug_map = dbg @@ -198,10 +198,11 @@ getCfgWeights = NatM $ \ st -> (ncgCfgWeights (natm_config st), st) setDeltaNat :: Int -> NatM () setDeltaNat delta = NatM $ \ st -> ((), st {natm_delta = delta}) - getThisModuleNat :: NatM Module -getThisModuleNat = NatM $ \ st -> (natm_this_module st, st) +getThisModuleNat = NatM $ \ st -> (ncgThisModule $ natm_config st, st) +instance HasModule NatM where + getModule = getThisModuleNat addImportNat :: CLabel -> NatM () addImportNat imp ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -65,7 +65,6 @@ import GHC.Cmm import GHC.Cmm.CLabel import GHC.Types.Basic -import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Utils.Panic @@ -95,11 +94,9 @@ data ReferenceKind class Monad m => CmmMakeDynamicReferenceM m where addImport :: CLabel -> m () - getThisModule :: m Module instance CmmMakeDynamicReferenceM NatM where addImport = addImportNat - getThisModule = getThisModuleNat cmmMakeDynamicReference :: CmmMakeDynamicReferenceM m @@ -113,13 +110,11 @@ cmmMakeDynamicReference config referenceKind lbl = return $ CmmLit $ CmmLabel lbl -- already processed it, pass through | otherwise - = do this_mod <- getThisModule - let platform = ncgPlatform config + = do let platform = ncgPlatform config case howToAccessLabel config (platformArch platform) (platformOS platform) - this_mod referenceKind lbl of AccessViaStub -> do @@ -208,7 +203,7 @@ data LabelAccessStyle | AccessViaSymbolPtr | AccessDirectly -howToAccessLabel :: NCGConfig -> Arch -> OS -> Module -> ReferenceKind -> CLabel -> LabelAccessStyle +howToAccessLabel :: NCGConfig -> Arch -> OS -> ReferenceKind -> CLabel -> LabelAccessStyle -- Windows -- In Windows speak, a "module" is a set of objects linked into the @@ -231,7 +226,7 @@ howToAccessLabel :: NCGConfig -> Arch -> OS -> Module -> ReferenceKind -> CLabel -- into the same .exe file. In this case we always access symbols directly, -- and never use __imp_SYMBOL. -- -howToAccessLabel config _ OSMinGW32 this_mod _ lbl +howToAccessLabel config _arch OSMinGW32 _kind lbl -- Assume all symbols will be in the same PE, so just access them directly. | not (ncgExternalDynamicRefs config) @@ -239,7 +234,7 @@ howToAccessLabel config _ OSMinGW32 this_mod _ lbl -- If the target symbol is in another PE we need to access it via the -- appropriate __imp_SYMBOL pointer. - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr -- Target symbol is in the same PE as the caller, so just access it directly. @@ -255,9 +250,9 @@ howToAccessLabel config _ OSMinGW32 this_mod _ lbl -- It is always possible to access something indirectly, -- even when it's not necessary. -- -howToAccessLabel config arch OSDarwin this_mod DataReference lbl +howToAccessLabel config arch OSDarwin DataReference lbl -- data access to a dynamic library goes via a symbol pointer - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr -- when generating PIC code, all cross-module data references must @@ -276,21 +271,21 @@ howToAccessLabel config arch OSDarwin this_mod DataReference lbl | otherwise = AccessDirectly -howToAccessLabel config arch OSDarwin this_mod JumpReference lbl +howToAccessLabel config arch OSDarwin JumpReference lbl -- dyld code stubs don't work for tailcalls because the -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: | arch == ArchX86 || arch == ArchX86_64 - , labelDynamic config this_mod lbl + , labelDynamic config lbl = AccessViaSymbolPtr -howToAccessLabel config arch OSDarwin this_mod _ lbl +howToAccessLabel config arch OSDarwin _kind lbl -- Code stubs are the usual method of choice for imported code; -- not needed on x86_64 because Apple's new linker, ld64, generates -- them automatically. | arch /= ArchX86_64 - , labelDynamic config this_mod lbl + , labelDynamic config lbl = AccessViaStub | otherwise @@ -301,7 +296,7 @@ howToAccessLabel config arch OSDarwin this_mod _ lbl -- AIX -- quite simple (for now) -howToAccessLabel _config _arch OSAIX _this_mod kind _lbl +howToAccessLabel _config _arch OSAIX kind _lbl = case kind of DataReference -> AccessViaSymbolPtr CallReference -> AccessDirectly @@ -318,7 +313,7 @@ howToAccessLabel _config _arch OSAIX _this_mod kind _lbl -- from position independent code. It is also required from the main program -- when dynamic libraries containing Haskell code are used. -howToAccessLabel _ (ArchPPC_64 _) os _ kind _ +howToAccessLabel _config (ArchPPC_64 _) os kind _lbl | osElfTarget os = case kind of -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC @@ -330,7 +325,7 @@ howToAccessLabel _ (ArchPPC_64 _) os _ kind _ -- regular calls are handled by the runtime linker _ -> AccessDirectly -howToAccessLabel config _ os _ _ _ +howToAccessLabel config _arch os _kind _lbl -- no PIC -> the dynamic linker does everything for us; -- if we don't dynamically link to Haskell code, -- it actually manages to do so without messing things up. @@ -339,11 +334,11 @@ howToAccessLabel config _ os _ _ _ not (ncgExternalDynamicRefs config) = AccessDirectly -howToAccessLabel config arch os this_mod DataReference lbl +howToAccessLabel config arch os DataReference lbl | osElfTarget os = case () of -- A dynamic label needs to be accessed via a symbol pointer. - _ | labelDynamic config this_mod lbl + _ | labelDynamic config lbl -> AccessViaSymbolPtr -- For PowerPC32 -fPIC, we have to access even static data @@ -369,25 +364,25 @@ howToAccessLabel config arch os this_mod DataReference lbl -- (AccessDirectly, because we get an implicit symbol stub) -- and calling functions from PIC code on non-i386 platforms (via a symbol stub) -howToAccessLabel config arch os this_mod CallReference lbl +howToAccessLabel config arch os CallReference lbl | osElfTarget os - , labelDynamic config this_mod lbl && not (ncgPIC config) + , labelDynamic config lbl && not (ncgPIC config) = AccessDirectly | osElfTarget os , arch /= ArchX86 - , labelDynamic config this_mod lbl + , labelDynamic config lbl , ncgPIC config = AccessViaStub -howToAccessLabel config _ os this_mod _ lbl +howToAccessLabel config _arch os _kind lbl | osElfTarget os - = if labelDynamic config this_mod lbl + = if labelDynamic config lbl then AccessViaSymbolPtr else AccessDirectly -- all other platforms -howToAccessLabel config _ _ _ _ _ +howToAccessLabel config _arch _os _kind _lbl | not (ncgPIC config) = AccessDirectly ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -90,6 +90,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = -- special case for code without info table: pprSectionAlign config (Section Text lbl) $$ pprProcAlignment config $$ + pprProcLabel config lbl $$ pprLabel platform lbl $$ -- blocks guaranteed not null, so label needed vcat (map (pprBasicBlock config top_info) blocks) $$ (if ncgDwarfEnabled config @@ -99,6 +100,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = Just (CmmStaticsRaw info_lbl _) -> pprSectionAlign config (Section Text info_lbl) $$ pprProcAlignment config $$ + pprProcLabel config lbl $$ (if platformHasSubsectionsViaSymbols platform then pdoc platform (mkDeadStripPreventer info_lbl) <> char ':' else empty) $$ @@ -114,6 +116,15 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = else empty) $$ pprSizeDecl platform info_lbl +-- | Output an internal proc label. See Note [Internal proc labels] in CLabel. +pprProcLabel :: NCGConfig -> CLabel -> SDoc +pprProcLabel config lbl + | ncgExposeInternalSymbols config + , Just lbl' <- ppInternalProcLabel (ncgThisModule config) lbl + = lbl' <> char ':' + | otherwise + = empty + -- | Output the ELF .size directive. pprSizeDecl :: Platform -> CLabel -> SDoc pprSizeDecl platform lbl ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -274,6 +274,7 @@ data GeneralFlag -- forwards all -L flags to the collect2 command without using a -- response file and as such breaking apart. | Opt_SingleLibFolder + | Opt_ExposeInternalSymbols | Opt_KeepCAFs | Opt_KeepGoing | Opt_ByteCode ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -376,7 +376,6 @@ import qualified GHC.LanguageExtensions as LangExt -- ----------------------------------------------------------------------------- -- DynFlags - -- | Used to differentiate the scope an include needs to apply to. -- We have to split the include paths to avoid accidentally forcing recursive -- includes since -I overrides the system search paths. See #14312. @@ -3417,6 +3416,7 @@ fFlagsDeps = [ flagSpec "error-spans" Opt_ErrorSpans, flagSpec "excess-precision" Opt_ExcessPrecision, flagSpec "expose-all-unfoldings" Opt_ExposeAllUnfoldings, + flagSpec "expose-internal-symbols" Opt_ExposeInternalSymbols, flagSpec "external-dynamic-refs" Opt_ExternalDynamicRefs, flagSpec "external-interpreter" Opt_ExternalInterpreter, flagSpec "flat-cache" Opt_FlatCache, @@ -4419,7 +4419,13 @@ setVerbosity :: Maybe Int -> DynP () setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 }) setDebugLevel :: Maybe Int -> DynP () -setDebugLevel mb_n = upd (\dfs -> dfs{ debugLevel = mb_n `orElse` 2 }) +setDebugLevel mb_n = + upd (\dfs -> exposeSyms $ dfs{ debugLevel = n }) + where + n = mb_n `orElse` 2 + exposeSyms + | n > 2 = setGeneralFlag' Opt_ExposeInternalSymbols + | otherwise = id data PkgDbRef = GlobalPkgDb ===================================== docs/users_guide/debug-info.rst ===================================== @@ -14,6 +14,7 @@ useable by most UNIX debugging tools. :category: debugging :since: 7.10, numeric levels since 8.0 + :implies: :ghc-flag:`-fexpose-internal-symbols` when ⟨n⟩ >= 2. Emit debug information in object code. Currently only DWARF debug information is supported on x86-64 and i386. Currently debug levels 0 ===================================== docs/users_guide/phases.rst ===================================== @@ -720,6 +720,20 @@ Options affecting code generation all target platforms. See the :ghc-flag:`--print-object-splitting-supported` flag to check whether your GHC supports object splitting. +.. ghc-flag:: -fexpose-internal-symbols + :shortdesc: Produce symbols for all functions, including internal functions. + :type: dynamic + :category: codegen + + Request that GHC emits verbose symbol tables which include local symbols + for module-internal functions. These can be useful for tools like + :ref:`perf ` but increase object file sizes. + This is implied by :ghc-flag:`-g2 <-g>` and above. + + :ghc-flag:`-fno-expose-internal-symbols <-fexpose-internal-symbols>` + suppresses all non-global symbol table entries, resulting in smaller object + file sizes at the expense of debuggability. + .. _options-linker: Options affecting linking ===================================== testsuite/tests/regalloc/regalloc_unit_tests.hs ===================================== @@ -106,7 +106,7 @@ compileCmmForRegAllocStats :: IO [( Maybe [Color.RegAllocStats (Alignment, RawCmmStatics) X86.Instr.Instr] , Maybe [Linear.RegAllocStats])] compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do - let ncgImpl = ncgImplF (initNCGConfig dflags) + let ncgImpl = ncgImplF (initNCGConfig dflags thisMod) hscEnv <- newHscEnv dflags -- parse the cmm file and output any warnings or errors @@ -126,7 +126,7 @@ compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do -- compile and discard the generated code, returning regalloc stats mapM (\ (count, thisCmm) -> - cmmNativeGen dflags thisMod thisModLoc ncgImpl + cmmNativeGen dflags thisModLoc ncgImpl usb dwarfFileIds dbgMap thisCmm count >>= (\(_, _, _, _, colorStats, linearStats, _) -> -- scrub unneeded output from cmmNativeGen View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/221aa82af64d3d40bcd8c341c13677acb50cb476...151f6f6f7bafa30a9e0f768d5ab187c6cbe35520 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/221aa82af64d3d40bcd8c341c13677acb50cb476...151f6f6f7bafa30a9e0f768d5ab187c6cbe35520 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 Tue Nov 10 02:25:28 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 21:25:28 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5fa9fa18d4624_10ee10651020106632c@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: a9ebd316 by Ben Gamari at 2020-11-09T21:25:21-05:00 Bump time submodule to 1.11 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 7 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9ebd31634b3357dffa14e2b5385df5815f904e2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9ebd31634b3357dffa14e2b5385df5815f904e2 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 Tue Nov 10 03:46:42 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 09 Nov 2020 22:46:42 -0500 Subject: [Git][ghc/ghc][wip/T17605] 134 commits: SMP.h: Add C11-style atomic operations Message-ID: <5faa0d22980f1_10eecd02e7c1071097@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17605 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - b08de93a by Ben Gamari at 2020-11-09T22:46:36-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - f7b927aa by Ben Gamari at 2020-11-09T22:46:36-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - 73f47e9f by Ben Gamari at 2020-11-09T22:46:36-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - 0ab4ecef by Ben Gamari at 2020-11-09T22:46:36-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3263780f03ca82310f8ff2ef4376cb743730f2dd...0ab4eceff307ccc5470244c3ad88d4996d79f843 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3263780f03ca82310f8ff2ef4376cb743730f2dd...0ab4eceff307ccc5470244c3ad88d4996d79f843 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 Tue Nov 10 04:00:56 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 09 Nov 2020 23:00:56 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-ncg] 512 commits: .gitignore *.hiedb files Message-ID: <5faa10786d027_10ee848ab2c107409c@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC Commits: 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 15c871cb by Moritz Angermann at 2020-11-09T03:13:11+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - d6ccd9ec by Moritz Angermann at 2020-11-09T11:38:26+08:00 Initial NCG - - - - - d248e4cd by Moritz Angermann at 2020-11-09T11:38:26+08:00 Address Takenobu's comments - - - - - 89127738 by Moritz Angermann at 2020-11-09T11:38:26+08:00 Fix floating points handling of NaNs - - - - - 02bcdbff by Moritz Angermann at 2020-11-09T11:38:26+08:00 Add basic Graph Coloring support - - - - - 1b9382c1 by Moritz Angermann at 2020-11-09T11:38:26+08:00 Drop debug - - - - - 321ffebb by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add primops_match.cmm testsuite - - - - - 451ee4a8 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fix -NaN for real this time. - - - - - a64fa6d5 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Adds nan test. - - - - - 6e2b113f by Moritz Angermann at 2020-11-09T11:38:27+08:00 no show - - - - - 220e2971 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Some notes on PIC - - - - - 2692e2ac by Moritz Angermann at 2020-11-09T11:38:27+08:00 Properly load W32 with bit 31 set. - - - - - 5cf3b4b8 by Moritz Angermann at 2020-11-09T11:38:27+08:00 better relocation logging - - - - - 93d5918b by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add AsmOpt Flags - - - - - 8ffa9d18 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Adds ANN instruction. I wish I had a `pad n` function for SDoc, that would interact with the layout, and just pad what ever was printed so far to `n` chars. - - - - - 0a2ff4a7 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Drop dead 32bit logic. - - - - - 6f3c9739 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add Show CmmExpr instances. Why would we want this, when we have Outputtable CmmExpr? Quite often when working on Code Generators, we want to structurally match on a Cmm Expression. Having to recover the Cmm Expression from its Outputtable text is not always trivial, and requires substantial effort. By having a Show instance, we can almost copy the definition to match on. - - - - - e129fb1b by Moritz Angermann at 2020-11-09T11:38:27+08:00 Drop duplicate show instance for CLabel now. - - - - - 6e36f6cf by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add link, lest I keep forgetting it. - - - - - d531a404 by Moritz Angermann at 2020-11-09T11:38:27+08:00 inline comments with // - - - - - 213cae42 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Some optimizations; not yet sure if safe or not. - - - - - 84395ed4 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add latest opt changes. - - - - - 15c52abf by Moritz Angermann at 2020-11-09T11:38:27+08:00 Address Takenobu Tani's comments. Thanks! - - - - - 5a75680f by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fix gcd :blush: - - - - - 08a7383f by Moritz Angermann at 2020-11-09T11:38:27+08:00 Overflow guard - - - - - eef63a00 by Moritz Angermann at 2020-11-09T11:38:27+08:00 More annotations. - - - - - 1c08cbb1 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Revert "Overflow guard" They are Integers not Ints. This reverts commit 3ef94e593a2848cf2bdc4251f5be34536642675f. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 021750bb by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add CmmAssign and CmmStore comments - - - - - 926b8dae by Moritz Angermann at 2020-11-09T11:38:27+08:00 Minor address mode changes - - - - - a771893b by Moritz Angermann at 2020-11-09T11:38:27+08:00 More Amode optimizations - - - - - 46eecdee by Moritz Angermann at 2020-11-09T11:38:27+08:00 I think this shoudl work for all Registers, not just CmmGlobal - - - - - 5323e028 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Opt <<, >> - - - - - 30980b7d by Moritz Angermann at 2020-11-09T11:38:27+08:00 Opt &&, || - - - - - 266d9443 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add branch ANNotations. - - - - - 5a5a1f6b by Moritz Angermann at 2020-11-09T11:38:27+08:00 Disable Opt &&, ||, due to mask immediate - - - - - d551bd8b by Moritz Angermann at 2020-11-09T11:38:27+08:00 Opt: Adds CBZ, CBNZ - - - - - ad673eb8 by Moritz Angermann at 2020-11-09T11:38:27+08:00 More generic CBZ, CBNZ - - - - - ff3a224e by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fixup - - - - - 6c4174e9 by Moritz Angermann at 2020-11-09T11:38:27+08:00 very rudimentary bitmask support. - - - - - defb2173 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add some more bitmasks - - - - - 54160bab by Moritz Angermann at 2020-11-09T11:38:27+08:00 Opt STR - - - - - 4270b359 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fixup - - - - - 1bff99c8 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fix MO_SF_Conv - - - - - 42847d4b by Moritz Angermann at 2020-11-09T11:38:27+08:00 Add Comment re MO_Memcpy - - - - - 3c2246d0 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Always PIC via GOT - - - - - cba0d9e3 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fix up generated assembly. Don't generate identity moves e.g. mov x18, x18 - - - - - bfa0d5c2 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Drop superfulous alignment generation. - - - - - 6616712f by Moritz Angermann at 2020-11-09T11:38:27+08:00 Hadrian :fire: - - - - - c43063ad by Moritz Angermann at 2020-11-09T11:38:27+08:00 Address Tekenobus comments. Thanks! - - - - - 6973fc12 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Adds J to distinguish jumps from B. Maybe this would be better handled with a phantom type? - - - - - 549fc6e5 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Make sp an Operand - - - - - 4e841046 by Moritz Angermann at 2020-11-09T11:38:27+08:00 allocMoreStack This is still broken, as we can't spill into arbitrary ranges. Hence while we can allocate extra space, we can't really spill past 4096 offsets due to the immediat having to be encoded. This leaves us with a max of 512 spill slots. We *can* work around this if we change the sp though. - - - - - 2269f930 by Moritz Angermann at 2020-11-09T11:38:27+08:00 [Spill/Reload] Spill Around :fire: - - - - - 518337b5 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Address Takenobus observations! Thanks! - - - - - 98f4c9a5 by Moritz Angermann at 2020-11-09T11:38:27+08:00 :sob: - - - - - fb0ab61b by Moritz Angermann at 2020-11-09T11:38:27+08:00 Revert the Spill/Reload fix; undo :got: loads. This breaks dynamic, however we can build a working stage2 compiler with the following mk/build.mk BuildFlavour = quick ifneq "$(BuildFlavour)" "" include mk/flavours/$(BuildFlavour).mk endif STRIP_CMD = : DYNAMIC_BY_DEFAULT = NO DYNAMIC_GHC_PROGRAMS = NO - - - - - feb9392e by Moritz Angermann at 2020-11-09T11:38:27+08:00 Disable trivial deadlock detection - - - - - d125ffa1 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Adds some annotations - - - - - 4a2e10e3 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Trying to get PIC right. - - - - - 4248c7d0 by Moritz Angermann at 2020-11-09T11:38:27+08:00 [aarch64] Fix spill/reload - - - - - 3d46c74c by Moritz Angermann at 2020-11-09T11:38:27+08:00 Try to get PIC right. - - - - - 2a0f9441 by Moritz Angermann at 2020-11-09T11:38:27+08:00 Spill/Reload only need a smaller window - - - - - fa776c2c by Moritz Angermann at 2020-11-09T11:38:27+08:00 Drop bad/useless optimisation This was due to not handling PIC symbols correctly and injecting CmmLoad as we do on other platforms, but this doesn't translate to aarch64's got lookups. - - - - - 60a591c8 by Moritz Angermann at 2020-11-09T11:38:27+08:00 B is b - - - - - 87928e6d by Moritz Angermann at 2020-11-09T11:38:27+08:00 Fix CCall |Now mark used registers properly for the Register Allocator. - - - - - 7bb91696 by Moritz Angermann at 2020-11-09T11:38:27+08:00 :sob: - - - - - 57876b45 by Moritz Angermann at 2020-11-09T11:38:27+08:00 :sob: :sob: - - - - - f844eea9 by Moritz Angermann at 2020-11-09T11:38:27+08:00 :sob: Segfault no 3. This showed up in T4114 - - - - - 7a003e12 by Moritz Angermann at 2020-11-09T11:38:55+08:00 Add mkComment to `Instruction` - - - - - b30ab6d7 by Moritz Angermann at 2020-11-09T11:38:55+08:00 Use mkComment for debugging - - - - - 40d1c8a1 by Moritz Angermann at 2020-11-09T11:38:55+08:00 Fix T4114 crashes T4114 causes this codepath to show up. - - - - - bdb773d4 by Moritz Angermann at 2020-11-09T11:38:55+08:00 Cleanup some compiler warnings - - - - - 90b16775 by Moritz Angermann at 2020-11-09T11:38:55+08:00 [Aarch64] No div-by-zero; disable test. - - - - - a39fa5cf by Moritz Angermann at 2020-11-09T11:38:55+08:00 Simplify aarch64 StgRun We don't need to do the callee save register dance. The compiler will do this for us already: 0000000000000000 <StgRun>: 0: a9b653f3 stp x19, x20, [sp, #-160]! 4: a9015bf5 stp x21, x22, [sp, #16] 8: a90263f7 stp x23, x24, [sp, #32] c: a9036bf9 stp x25, x26, [sp, #48] 10: a90473fb stp x27, x28, [sp, #64] 14: f9002bfe str x30, [sp, #80] 18: 6d0627e8 stp d8, d9, [sp, #96] 1c: 6d072fea stp d10, d11, [sp, #112] 20: 6d0837ec stp d12, d13, [sp, #128] 24: 6d093fee stp d14, d15, [sp, #144] 28: a9bf47f0 stp x16, x17, [sp, #-16]! 2c: d14013ff sub sp, sp, #0x4, lsl #12 30: aa0103f3 mov x19, x1 34: d61f0000 br x0 0000000000000038 <StgReturn>: 38: 914013ff add sp, sp, #0x4, lsl #12 3c: aa1603e0 mov x0, x22 40: a8c147f0 ldp x16, x17, [sp], #16 44: a9415bf5 ldp x21, x22, [sp, #16] 48: a94263f7 ldp x23, x24, [sp, #32] 4c: a9436bf9 ldp x25, x26, [sp, #48] 50: a94473fb ldp x27, x28, [sp, #64] 54: f9402bfe ldr x30, [sp, #80] 58: 6d4627e8 ldp d8, d9, [sp, #96] 5c: 6d472fea ldp d10, d11, [sp, #112] 60: 6d4837ec ldp d12, d13, [sp, #128] 64: 6d493fee ldp d14, d15, [sp, #144] 68: a8ca53f3 ldp x19, x20, [sp], #160 6c: d65f03c0 ret - - - - - 1cfcd252 by Moritz Angermann at 2020-11-09T11:38:55+08:00 Use ip0 for spills/reloads - - - - - 2cd77ea4 by Moritz Angermann at 2020-11-09T11:39:46+08:00 :broom: Cleanup - - - - - eda57783 by Moritz Angermann at 2020-11-09T11:39:46+08:00 Adds LLVM (AArch64) CI Job - - - - - 4de02f6c by Moritz Angermann at 2020-11-09T11:39:46+08:00 Add validate as well. - - - - - 5f435df5 by Moritz Angermann at 2020-11-09T11:39:46+08:00 Revert "Simplify aarch64 StgRun" This reverts commit f27472c0483db2382344f4a8f4c1b2a192d98725. - - - - - 4cee6853 by Moritz Angermann at 2020-11-09T11:39:46+08:00 Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md - - - - - fc7817a2 by Moritz Angermann at 2020-11-09T11:39:46+08:00 Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md - - - - - 1e12c166 by Moritz Angermann at 2020-11-09T11:39:46+08:00 [macOS] support for arm64 Adding basic changes to support arm64-apple-darwin - - - - - d6e30e03 by Moritz Angermann at 2020-11-09T11:39:46+08:00 Add CLabel logic - - - - - f0ad898f by Moritz Angermann at 2020-11-09T11:39:46+08:00 [configure] make arm64-apple-darwin an LLVM Target This is required as the llvm toolchain doesn't like aarch64-apple-darwin, and only accepts arm64-apple-darwin. - - - - - f9a9678d by Moritz Angermann at 2020-11-09T11:39:46+08:00 [configure] disable subsections_via_symbols on arm64/macOS LLVM's clang will not emit relocation entries for assembly local (L prefixed) symbols. In the presence of subsections_via_symbols, the linker is free to strip dead symbols from the object code, however due to the lack of relocations for assembly local symbols, branches will be invalidated through this dead stripping. As such we must not permit subsections_via_symbols on arm64/macho-o. - - - - - f5cab7f3 by Moritz Angermann at 2020-11-09T11:39:46+08:00 [arm64/mach-o] adrp/ldr symbol names This will break elf. We need to find a better solution for this symbol naming is platform dependent here. :got: / @gotpage :got_lo12: / @gotpageoff :lo12: / @pageoff - - - - - 3b4c9c48 by Moritz Angermann at 2020-11-09T11:39:46+08:00 [WIP] symbol garbage Naming is hard. Supporting assembler and linker even harder. L is the assembly local prefix l is the linker local prefix L is not relocated at all. l is relocated, but fails to for conditional branches. Send help! - - - - - e56196bd by Moritz Angermann at 2020-11-09T11:39:46+08:00 [MachO] cleanup compiler warnings - - - - - 6459ac58 by Moritz Angermann at 2020-11-09T11:42:40+08:00 [macOS/arm64] do not use read_only_relocs on arm64 The linker simply doesn't support it and will complain loudly. - - - - - 964a0c0c by Moritz Angermann at 2020-11-09T11:42:40+08:00 [Storage/Adjustor] Drop size check in allocExec This is violated by ghci, in InfoTable.hsc we call _allocateExec with a size that does not guarantee to be of ffi_closure size. Other allocateExec implementations do not have this check either; I highly doubt it's sensible to have this check in the presence of ghci's allocateExec calls. - - - - - 7671f117 by Moritz Angermann at 2020-11-09T11:42:40+08:00 [linker/elf] better errors (with error message) - - - - - 3b4ce6f4 by Moritz Angermann at 2020-11-09T11:43:26+08:00 [darwin] always pic, ios AND mac AND tv AND ... - - - - - 72888cf4 by Moritz Angermann at 2020-11-09T11:43:26+08:00 [aarch64/codegen] pack ccall arguments on darwin This is annoying, but the darwinpcs does not match the default aapcs :facepalm: - - - - - 962237a9 by Moritz Angermann at 2020-11-09T11:43:26+08:00 [linker:MachO] split PLT logic out. Why was this missing in the first place? It's now a bit more aligned to the elf plt logic. - - - - - 5d8f53fc by Moritz Angermann at 2020-11-09T11:43:26+08:00 [configure] fix LLVMTarget when native uname -p return "arm", hence we can't work with target_cpu, but need to match on the target triple. - - - - - 4f4eb26c by Moritz Angermann at 2020-11-09T11:43:26+08:00 [testsuite] fix subsections_via_symbols test - - - - - 88d2bfac by Moritz Angermann at 2020-11-09T11:43:26+08:00 [testsuite] FixT11649 - - - - - 99b84247 by Moritz Angermann at 2020-11-09T11:43:26+08:00 Fix conc059 test - - - - - b6545952 by Moritz Angermann at 2020-11-09T11:43:26+08:00 WIP: fix ghci adjustors on aarch64/arm (infotables) - - - - - 188fc6e1 by Moritz Angermann at 2020-11-09T11:43:26+08:00 [DWARF] Enable only on elf platforms - - - - - 18aeb254 by Moritz Angermann at 2020-11-09T11:43:26+08:00 [Testsuite/LLVM] Fix T5681, T7571, T8131b - - - - - aed6294a by Moritz Angermann at 2020-11-09T11:43:26+08:00 [testsuite/darwin] fix tests ghcilink003, ghcilink006 - - - - - da7d11ed by Moritz Angermann at 2020-11-09T11:43:26+08:00 Fix linker_error2 - - - - - 65cbfcc1 by Moritz Angermann at 2020-11-09T11:44:41+08:00 Sized Hints - - - - - 9e2e2b4d by Moritz Angermann at 2020-11-09T11:44:41+08:00 [Testsuite/arm64] Fix test derefnull - - - - - bf212421 by Moritz Angermann at 2020-11-09T11:44:41+08:00 [testsuite/arm64] fix section_alignment - - - - - b753727e by Moritz Angermann at 2020-11-09T11:44:42+08:00 [macOS/arm64] darwinpcs :facepalm: - - - - - 6da5633b by Moritz Angermann at 2020-11-09T11:46:52+08:00 [aarch64/darwin] ifdef for got lables. This should ideally be some runtime flag, but it would need access to the platform. - - - - - 8673771a by Moritz Angermann at 2020-11-09T11:46:52+08:00 [aarch64/rts] fix missing prototypes - - - - - cb2a5824 by Moritz Angermann at 2020-11-09T11:46:52+08:00 Int has Word size in Haskell. - - - - - d6768afc by Moritz Angermann at 2020-11-09T11:46:52+08:00 [debug only] warn on hint/arg mismatch - - - - - fa89f86e by Moritz Angermann at 2020-11-09T11:46:52+08:00 [AArch64 NCG] User argument format rather than hint. - - - - - 4953c7dd by Moritz Angermann at 2020-11-09T11:49:00+08:00 [Debug] Fix CmmFloat warnings. - - - - - 419a0d65 by Moritz Angermann at 2020-11-09T11:49:00+08:00 [aarch64/elf] fixup elf symbols - - - - - 94956097 by Moritz Angermann at 2020-11-09T11:49:00+08:00 :facepalm: - - - - - 78fc1916 by Moritz Angermann at 2020-11-09T11:49:00+08:00 :facepalm: - - - - - 309e9a52 by Moritz Angermann at 2020-11-09T11:49:00+08:00 [Adjustors] Proper allocator handling. - - - - - ee1b3b04 by Moritz Angermann at 2020-11-09T11:49:52+08:00 Revert "[AArch64] Aarch64 Always PIC" This reverts commit 921276592218211f441fcf011fc52441e3a2f0a6. - - - - - 48c259c6 by Moritz Angermann at 2020-11-09T11:49:52+08:00 Revert "[Storage/Adjustor] Drop size check in allocExec" This reverts commit 37a62ae956a25e5832fbe125a4d8ee556fd11042. - - - - - b9971f5a by Moritz Angermann at 2020-11-09T11:49:52+08:00 [Storage] Reinstate check; add comment. - - - - - 96a65e52 by Moritz Angermann at 2020-11-09T11:50:42+08:00 [AArch64] Aarch64 Always PIC - - - - - e463c589 by Moritz Angermann at 2020-11-09T11:51:06+08:00 [testsuite] static001 is not broken anymore. - - - - - 028a34f4 by Moritz Angermann at 2020-11-09T12:08:20+08:00 Revert "Sized Hints" This reverts commit 65cbfcc10e7ad32dd04ebce011860f5b557eacac. - - - - - a1104357 by Moritz Angermann at 2020-11-10T09:18:56+08:00 fix up rebase - - - - - 29 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e98e3d124a92cdf48108d918e501a132eaaee53a...a110435790495f25b750d0ef65aab6e0813ade11 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e98e3d124a92cdf48108d918e501a132eaaee53a...a110435790495f25b750d0ef65aab6e0813ade11 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 Tue Nov 10 09:06:26 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 04:06:26 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5faa58126cb26_10ee3ffb97b35a601102257@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b71e88e5 by Ben Gamari at 2020-11-10T04:06:08-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 30de4d22 by Sylvain Henry at 2020-11-10T04:06:11-05:00 Export SPEC from GHC.Exts (#13681) - - - - - e6e65078 by David Eichmann at 2020-11-10T04:06:12-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 65281e60 by Richard Eisenberg at 2020-11-10T04:06:12-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 3903c25f by David Eichmann at 2020-11-10T04:06:14-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - 9 changed files: - includes/rts/storage/Closures.h - includes/rts/storage/Heap.h - includes/rts/storage/TSO.h - libraries/base/GHC/Exts.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/Heap.c - rts/linker/PEi386.c - + testsuite/tests/typecheck/should_compile/T17186.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== includes/rts/storage/Closures.h ===================================== @@ -63,6 +63,11 @@ typedef struct { -------------------------------------------------------------------------- */ typedef struct { + // If TABLES_NEXT_TO_CODE is defined, then `info` is offset by + // `sizeof(StgInfoTable)` and so points to the `code` field of the + // StgInfoTable! You may want to use `get_itbl` to get the pointer to the + // start of the info table. See + // https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/rts/storage/heap-objects#tables_next_to_code. const StgInfoTable* info; #if defined(PROFILING) StgProfHeader prof; ===================================== includes/rts/storage/Heap.h ===================================== @@ -16,3 +16,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs , StgClosure *fun, StgClosure **payload, StgWord size); StgWord heap_view_closureSize(StgClosure *closure); + +/* + * Collect the pointers of a closure into the given array. `size` should be + * large enough to hold all collected pointers e.g. + * `heap_view_closureSize(closure)`. Returns the number of pointers collected. + * The caller must ensure that `closure` is not modified (or moved by the GC) + * for the duration of the call to `collect_pointers`. + */ +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[]); ===================================== includes/rts/storage/TSO.h ===================================== @@ -242,10 +242,22 @@ typedef struct StgTSO_ { typedef struct StgStack_ { StgHeader header; - StgWord32 stack_size; // stack size in *words* + + /* Size of the `stack` field in *words*. This is not affected by how much of + * the stack space is used, nor if more stack space is linked to by an + * UNDERFLOW_FRAME. + */ + StgWord32 stack_size; + StgWord8 dirty; // non-zero => dirty StgWord8 marking; // non-zero => someone is currently marking the stack - StgPtr sp; // current stack pointer + + /* Pointer to the "top" of the stack i.e. the most recently written address. + * The stack is filled downwards, so the "top" of the stack starts with `sp + * = stack + stack_size` and is decremented as the stack fills with data. + * See comment on "Invariants" below. + */ + StgPtr sp; StgWord stack[]; } StgStack; ===================================== libraries/base/GHC/Exts.hs ===================================== @@ -72,7 +72,7 @@ module GHC.Exts breakpoint, breakpointCond, -- * Ids with special behaviour - inline, noinline, lazy, oneShot, + inline, noinline, lazy, oneShot, SPEC (..), -- * Running 'RealWorld' state thread runRW#, ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -7,6 +7,9 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE UnliftedFFITypes #-} {-| Module : GHC.Exts.Heap @@ -25,6 +28,7 @@ module GHC.Exts.Heap ( , ClosureType(..) , PrimType(..) , HasHeapRep(getClosureData) + , getClosureDataFromHeapRep -- * Info Table types , StgInfoTable(..) @@ -58,7 +62,7 @@ import GHC.Exts.Heap.Utils import Control.Monad import Data.Bits -import GHC.Arr +import Foreign import GHC.Exts import GHC.Int import GHC.Word @@ -66,13 +70,19 @@ import GHC.Word #include "ghcconfig.h" class HasHeapRep (a :: TYPE rep) where - getClosureData :: a -> IO Closure + + -- | Decode a closure to it's heap representation ('GenClosure'). + getClosureData + :: a + -- ^ Closure to decode. + -> IO Closure + -- ^ Heap representation of the closure. instance HasHeapRep (a :: TYPE 'LiftedRep) where - getClosureData = getClosure + getClosureData = getClosureDataFromHeapObject instance HasHeapRep (a :: TYPE 'UnliftedRep) where - getClosureData x = getClosure (unsafeCoerce# x) + getClosureData x = getClosureDataFromHeapObject (unsafeCoerce# x) instance Int# ~ a => HasHeapRep (a :: TYPE 'IntRep) where getClosureData x = return $ @@ -102,49 +112,84 @@ instance Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) where getClosureData x = return $ DoubleClosure { ptipe = PDouble, doubleVal = D# x } --- | This returns the raw representation of the given argument. The second --- component of the triple is the raw words of the closure on the heap, and the --- third component is those words that are actually pointers. Once back in the --- Haskell world, the raw words that hold pointers may be outdated after a --- garbage collector run, but the corresponding values in 'Box's will still --- point to the correct value. -getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box]) -getClosureRaw x = do +-- | Get the heap representation of a closure _at this moment_, even if it is +-- unevaluated or an indirection or other exotic stuff. Beware when passing +-- something to this function, the same caveats as for +-- 'GHC.Exts.Heap.Closures.asBox' apply. +-- +-- For most use cases 'getClosureData' is an easier to use alternative. +-- +-- Currently TSO and STACK objects will return `UnsupportedClosure`. This is +-- because it is not memory safe to extract TSO and STACK objects (done via +-- `unpackClosure#`). Other threads may be mutating those objects and interleave +-- with reads in `unpackClosure#`. This is particularly problematic with STACKs +-- where pointer values may be overwritten by non-pointer values as the +-- corresponding haskell thread runs. +getClosureDataFromHeapObject + :: a + -- ^ Heap object to decode. + -> IO Closure + -- ^ Heap representation of the closure. +getClosureDataFromHeapObject x = do case unpackClosure# x of --- This is a hack to cover the bootstrap compiler using the old version of --- 'unpackClosure'. The new 'unpackClosure' return values are not merely --- a reordering, so using the old version would not work. - (# iptr, dat, pointers #) -> do - let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE - end = fromIntegral nelems - 1 - rawWds = [W# (indexWordArray# dat i) | I# i <- [0.. end] ] - pelems = I# (sizeofArray# pointers) - ptrList = amap' Box $ Array 0 (pelems - 1) pelems pointers - pure (Ptr iptr, rawWds, ptrList) - --- From GHC.Runtime.Heap.Inspect -amap' :: (t -> b) -> Array Int t -> [b] -amap' f (Array i0 i _ arr#) = map g [0 .. i - i0] - where g (I# i#) = case indexArray# arr# i# of - (# e #) -> f e - --- | This function returns a parsed heap representation of the argument _at --- this moment_, even if it is unevaluated or an indirection or other exotic --- stuff. Beware when passing something to this function, the same caveats as --- for 'asBox' apply. -getClosure :: a -> IO Closure -getClosure x = do - (iptr, wds, pts) <- getClosureRaw x - itbl <- peekItbl iptr - -- The remaining words after the header - let rawWds = drop (closureTypeHeaderSize (tipe itbl)) wds - -- For data args in a pointers then non-pointers closure - -- This is incorrect in non pointers-first setups - -- not sure if that happens - npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) wds +#if MIN_VERSION_ghc_prim(0,5,3) + (# infoTableAddr, heapRep, pointersArray #) -> do +#else + -- This is a hack to cover the bootstrap compiler using the old version + -- of 'unpackClosure'. The new 'unpackClosure' return values are not + -- merely a reordering, so using the old version would not work. + (# infoTableAddr, pointersArray, heapRep #) -> do +#endif + let infoTablePtr = Ptr infoTableAddr + ptrList = [case indexArray# pointersArray i of + (# ptr #) -> Box ptr + | I# i <- [0..(I# (sizeofArray# pointersArray)) - 1] + ] + + infoTable <- peekItbl infoTablePtr + case tipe infoTable of + TSO -> pure $ UnsupportedClosure infoTable + STACK -> pure $ UnsupportedClosure infoTable + _ -> getClosureDataFromHeapRep heapRep infoTablePtr ptrList + +-- | Convert an unpacked heap object, to a `GenClosure b`. The inputs to this +-- function can be generated from a heap object using `unpackClosure#`. +getClosureDataFromHeapRep + :: ByteArray# + -- ^ Heap representation of the closure as returned by `unpackClosure#`. + -- This includes all of the object including the header, info table + -- pointer, pointer data, and non-pointer data. The ByteArray# may be + -- pinned or unpinned. + -> Ptr StgInfoTable + -- ^ Pointer to the `StgInfoTable` of the closure, extracted from the heap + -- representation. The info table must not be movable by GC i.e. must be in + -- pinned or off-heap memory. + -> [b] + -- ^ Pointers in the payload of the closure, extracted from the heap + -- representation as returned by `collect_pointers()` in `Heap.c`. The type + -- `b` is some representation of a pointer e.g. `Any` or `Ptr Any`. + -> IO (GenClosure b) + -- ^ Heap representation of the closure. +getClosureDataFromHeapRep heapRep infoTablePtr pts = do + itbl <- peekItbl infoTablePtr + let -- heapRep as a list of words. + rawHeapWords :: [Word] + rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ] + where + nelems = (I# (sizeofByteArray# heapRep)) `div` wORD_SIZE + end = fromIntegral nelems - 1 + + -- Just the payload of rawHeapWords (no header). + payloadWords :: [Word] + payloadWords = drop (closureTypeHeaderSize (tipe itbl)) rawHeapWords + + -- The non-pointer words in the payload. Only valid for closures with a + -- "pointers first" layout. Not valid for bit field layout. + npts :: [Word] + npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) rawHeapWords case tipe itbl of t | t >= CONSTR && t <= CONSTR_NOCAF -> do - (p, m, n) <- dataConNames iptr + (p, m, n) <- dataConNames infoTablePtr if m == "GHC.ByteCode.Instr" && n == "BreakInfo" then pure $ UnsupportedClosure itbl else pure $ ConstrClosure itbl pts npts p m n @@ -164,9 +209,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to AP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 raw words to AP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ APClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -181,9 +226,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to PAP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail "Expected at least 2 raw words to PAP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ PAPClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -218,10 +263,10 @@ getClosure x = do unless (length pts >= 3) $ fail $ "Expected at least 3 ptr argument to BCO, found " ++ show (length pts) - unless (length rawWds >= 4) $ + unless (length payloadWords >= 4) $ fail $ "Expected at least 4 words to BCO, found " - ++ show (length rawWds) - let splitWord = rawWds !! 3 + ++ show (length payloadWords) + let splitWord = payloadWords !! 3 pure $ BCOClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -230,27 +275,30 @@ getClosure x = do (fromIntegral splitWord) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) #endif - (drop 4 rawWds) + (drop 4 payloadWords) ARR_WORDS -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 words to ARR_WORDS, found " - ++ show (length rawWds) - pure $ ArrWordsClosure itbl (head rawWds) (tail rawWds) + ++ show (length payloadWords) + pure $ ArrWordsClosure itbl (head payloadWords) (tail payloadWords) t | t >= MUT_ARR_PTRS_CLEAN && t <= MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 words to MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ MutArrClosure itbl (rawWds !! 0) (rawWds !! 1) pts + ++ "found " ++ show (length payloadWords) + pure $ MutArrClosure itbl (payloadWords !! 0) (payloadWords !! 1) pts t | t >= SMALL_MUT_ARR_PTRS_CLEAN && t <= SMALL_MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 word to SMALL_MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ SmallMutArrClosure itbl (rawWds !! 0) pts + ++ "found " ++ show (length payloadWords) + pure $ SmallMutArrClosure itbl (payloadWords !! 0) pts - t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> + t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> do + unless (length pts >= 1) $ + fail $ "Expected at least 1 words to MUT_VAR, found " + ++ show (length pts) pure $ MutVarClosure itbl (head pts) t | t == MVAR_CLEAN || t == MVAR_DIRTY -> do @@ -260,13 +308,12 @@ getClosure x = do pure $ MVarClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) BLOCKING_QUEUE -> - pure $ OtherClosure itbl pts wds + pure $ OtherClosure itbl pts rawHeapWords -- pure $ BlockingQueueClosure itbl -- (pts !! 0) (pts !! 1) (pts !! 2) (pts !! 3) - -- pure $ OtherClosure itbl pts wds + -- pure $ OtherClosure itbl pts rawHeapWords -- - WEAK -> pure $ WeakClosure { info = itbl ===================================== rts/Heap.c ===================================== @@ -76,23 +76,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs } } -StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { - ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); - - StgWord size = heap_view_closureSize(closure); - StgWord nptrs = 0; - StgWord i; - - // First collect all pointers here, with the comfortable memory bound - // of the whole closure. Afterwards we know how many pointers are in - // the closure and then we can allocate space on the heap and copy them - // there - StgClosure *ptrs[size]; - +// See Heap.h +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[size]) { StgClosure **end; - StgClosure **ptr; - const StgInfoTable *info = get_itbl(closure); + StgWord nptrs = 0; + StgWord i; switch (info->type) { case INVALID_OBJECT: @@ -101,6 +90,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { // No pointers case ARR_WORDS: + case STACK: break; // Default layout @@ -123,7 +113,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case FUN_0_2: case FUN_STATIC: end = closure->payload + info->layout.payload.ptrs; - for (ptr = closure->payload; ptr < end; ptr++) { + for (StgClosure **ptr = closure->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -136,7 +126,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case THUNK_0_2: case THUNK_STATIC: end = ((StgThunk *)closure)->payload + info->layout.payload.ptrs; - for (ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { + for (StgClosure **ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -228,6 +218,21 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { break; } + return nptrs; +} + +StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); + + StgWord size = heap_view_closureSize(closure); + + // First collect all pointers here, with the comfortable memory bound + // of the whole closure. Afterwards we know how many pointers are in + // the closure and then we can allocate space on the heap and copy them + // there + StgClosure *ptrs[size]; + StgWord nptrs = collect_pointers(closure, size, ptrs); + size = nptrs + mutArrPtrsCardTableSize(nptrs); StgMutArrPtrs *arr = (StgMutArrPtrs *)allocate(cap, sizeofW(StgMutArrPtrs) + size); @@ -236,7 +241,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { arr->ptrs = nptrs; arr->size = size; - for (i = 0; ipayload[i] = ptrs[i]; } ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } ===================================== testsuite/tests/typecheck/should_compile/T17186.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE TypeOperators, AllowAmbiguousTypes #-} + +module T17186 where + +-- This test is significantly abbreviated from what was posted; see +-- #16512 for more context. + +type family Dim v + +type family v `OfDim` (n :: Dim v) = r | r -> n + +(!*^) :: Dim m `OfDim` j -> Dim m `OfDim` i +(!*^) = undefined ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,4 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) - +test('T17186', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c354a4618876a89af7942dbf435f3da1f73a70d0...3903c25fc0d998191940743dafc4ee80b40a7a2c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c354a4618876a89af7942dbf435f3da1f73a70d0...3903c25fc0d998191940743dafc4ee80b40a7a2c 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 Tue Nov 10 12:22:14 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 10 Nov 2020 07:22:14 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] Update user's guide entry on demand analysis and worker/wrapper Message-ID: <5faa85f69041_10ee3ffb98a7f520113468d@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: c70b5613 by Sebastian Graf at 2020-11-10T13:20:04+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 4 changed files: - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst Changes: ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -44,7 +44,7 @@ Compiler Code using ``Void#`` now has to enable :extension:`UnboxedTuples`. ``ghc`` library -~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~ - The ``con_args`` field of ``ConDeclGADT`` has been renamed to ``con_g_args``. This is because the type of ``con_g_args`` is now different from the type of ===================================== docs/users_guide/debugging.rst ===================================== @@ -334,16 +334,22 @@ subexpression elimination pass. its rationale. .. ghc-flag:: -ddump-stranal - :shortdesc: Dump strictness analyser output + :shortdesc: Dump demand analysis output :type: dynamic - Dump strictness analyser output + Dump demand analysis output. + + See :ghc-flag:`-fstrictness` for the syntax and semantics of demand + annotations. .. ghc-flag:: -ddump-str-signatures - :shortdesc: Dump strictness signatures + :shortdesc: Dump top-level demand signatures :type: dynamic - Dump strictness signatures + Dump top-level demand signatures as produced by demand analysis. + + See :ghc-flag:`-fstrictness` for the syntax and semantics of demand + annotations. .. ghc-flag:: -ddump-cpranal :shortdesc: Dump CPR analysis output @@ -381,7 +387,6 @@ subexpression elimination pass. Dump output of Core preparation pass - STG representation ~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/exts/instances.rst ===================================== @@ -147,7 +147,7 @@ Where: ``(forall a. a)`` and ``(Eq a => a)`` are legal. - ``ctype`` is a ``btype`` that has no restrictions on an outermost ``forall``/``=>``, so ``forall a. a`` and ``Eq a => a`` are legal ``ctype``\s. -- ``arg_type`` is a type that is not allowed to have ``forall``s or ``=>``\s +- ``arg_type`` is a type that is not allowed to have ``forall``\s or ``=>``\s - ``prefix_cls_tycon`` is a class type constructor written prefix (e.g., ``Show`` or ``(&&&)``), while ``infix_cls_tycon`` is a class type constructor written infix (e.g., ``\`Show\``` or ``&&&``). ===================================== docs/users_guide/using-optimisation.rst ===================================== @@ -1125,7 +1125,7 @@ by saying ``-fno-wombat``. available parameter registers on x86_64. .. ghc-flag:: -fstrictness - :shortdesc: Turn on strictness analysis. + :shortdesc: Turn on demand analysis. Implied by :ghc-flag:`-O`. Implies :ghc-flag:`-fworker-wrapper` :type: dynamic :reverse: -fno-strictness @@ -1133,23 +1133,147 @@ by saying ``-fno-wombat``. :default: on - Switch on the strictness analyser. The implementation is described in the - paper `Theory and Practice of Demand Analysis in Haskell - `__. - - The strictness analyser figures out when arguments and variables in - a function can be treated 'strictly' (that is they are always - evaluated in the function at some point). This allow GHC to apply - certain optimisations such as unboxing that otherwise don't apply as - they change the semantics of the program when applied to lazy - arguments. + Turn on demand analysis. + + A *Demand* describes an evaluation context of an expression. *Demand + analysis* tries to find out what demands a function puts on its arguments + when called: If an argument is scrutinised on every code path, the function + is strict in that argument and GHC is free to use the more efficient + call-by-value calling convention, as well as pass parameters unboxed. + + Apart from *strictness analysis*, demand analysis also performs *usage + analysis*: Where *strict* translates to "evaluated at least once", usage + analysis asks whether arguments and bindings are "evaluated at most once" + or not at all ("evaluated at most zero times"), e.g. *absent*. For the + former, GHC may use call-by-name instead of call-by-need, effectively + turning thunks into non-memoised functions. For the latter, no code needs + to be generated at all: An absent argument can simply be replaced by a + dummy value at the call site or omitted altogether. + + The worker/wrapper transformation (:ghc-flag:`-fworker-wrapper`) is + reponsible for exploiting unboxing opportunities and replacing absent + arguments by dummies. For arugments that can't be unboxed, opportunities + for call-by-value and call-by-name are exploited in CorePrep when + translating to STG. + + It's not only interesting to look at how often a binding is *evaluated*, + but also how often a function *is called*. If a function is called at most + once, we may freely eta-expand it, even if doing so destroys shared work + if the function was called multiple times. This information translates + into ``OneShotInfo`` annotations that the Simplifier acts on. + + **Notation** + + So demand analysis is about conservatively inferring lower and upper + bounds about how many times something is evaluated/called. We call the + "how many times" part a *cardinality*. In the compiler and debug output + we differentiate the following cardinality intervals as approximations + to cardinality: + + +----------+------------------------------+--------+---------------------------------------+ + | Interval | Set of denoted cardinalities | Syntax | Explanation tying syntax to semantics | + +==========+==============================+========+=======================================+ + | [1,0] | {} | ``B`` | bottom element | + +----------+------------------------------+--------+---------------------------------------+ + | [0,0] | {0} | ``A`` | absent | + +----------+------------------------------+--------+---------------------------------------+ + | [0,1] | {0,1} | ``1`` | used at most once | + +----------+------------------------------+--------+---------------------------------------+ + | [0,ω] | {0,1,ω} | ``U`` | top element, no information, | + | | | | used at least 0, at most many times | + +----------+------------------------------+--------+---------------------------------------+ + | [1,1] | {1} | ``S`` | strict, used exactly once | + +----------+------------------------------+--------+---------------------------------------+ + | [1,ω] | {1,ω} | ``M`` | strict, used possibly many times | + +----------+------------------------------+--------+---------------------------------------+ + + Note that it's never interesting to differentiate between a cardinality + of 2 and 3, or even 4232123. We just approximate the >1 case with ω, + standing for "many times". + + Apart from the cardinality describing *how often* an argument is evaluated, + a demand also carries a *sub-demand*, describing *how deep* something + is evaluated beyond a simple ``seq``-like evaluation. + + For example, ``fst`` is strict in its argument, and also in the first + component of the argument. It will not evaluate the argument's second + component. That is expressed by the demand ``SP(SU,A)``. The ``P`` is for + "product sub-demand", which has a *demand* for each product field. The + notation ``SU`` just says "evaluated strictly (``S``), with everything + nested inside evaluated according to ``U``" -- e.g., no information, + because that would depend on the evaluation context of the call site of + ``fst``. The role of ``U`` in ``SU`` is that of a *polymorphic* sub-demand, + being semantically equivalent to the sub-demand ``P(UP(..))``, which we + simply abbreviate by the (consequently overloaded) cardinality notation + ``U``. + + For another example, the expression ``x + 1`` evaluates ``x`` according to + demand ``SP(U)``. We have seen single letters stand for cardinalities and + polymorphic sub-demands, but what does the single letter ``U`` mean for a + *demand*? Such a single letter demand simply expands to a cardinality and + a polymorphic sub-demand of the same letter: E.g. ``U`` is equivalent to + ``UU`` by expansion of the single letter demand, which is equivalent to + ``UP(UP(..))``, so ``U``\s all the way down. + + **Demand signatures** + + We summarise a function's demand properties in its *demand signature*. + This is the general syntax: + + .. code-block:: + + {x->dx,y->dy,z->dz...}...d + ^ ^ ^ ^ ^ ^ + | | | | | | + | \---+---+------/ | + | | | + demand on free demand on divergence + variables arguments information + (omitted if empty) (omitted if + no information) + + We summarise ``fst``'s demand properties in its *demand signature* + ````, which just says "If ``fst`` is applied to one argument, + that argument is evaluated according to ``SP(SU,A)``". For another + example, the demand signature of ``seq`` would be ```` and that of + ``+`` would be ````. + + If not omitted, the divergence information can be ``b`` (surely diverges) + or ``x`` (surely diverges or throws a precise exception). For example, + ``error`` has demand signature ``b`` and ``throwIO`` (which is the + only way to throw precise exceptions) has demand signature ``<_>x`` + (leaving out the complicated demand on the ``Exception`` dictionary). + + **Call sub-demands** + + Consider ``maybe``: + + .. code-block:: + + maybe :: b -> (a -> b) -> Maybe a -> b + maybe n _ Nothing = n + maybe _ s (Just a) = s a + + We give it demand signature ````. The ``C1(U)`` is a + *call sub-demand* that says "called at most once, where the result is + used according to ``U``". It's in a position where we expect a demand, + and similarly to before, this notation is short for ``1C1(U)``, which also + says that the argument was evaluated once. When the evaluation cardinality + conincides with the outer call cardinality, it is omitted. The expression + ``f `seq` f 1 2`` puts ``f`` under demand ``MCS(U)`` and serves as an example + where evaluation cardinality doesn't conincide with call cardinality. + + Cardinality is always relative to the enclosing call cardinality, so + ``g 1 2 + g 3 4`` puts ``g`` under demand ``CM(CS(U))``, which says "called + multiple times (``M``), but every time it is called with one argument, + it is applied exactly once to another argument (``S``)". .. ghc-flag:: -fstrictness-before=⟨n⟩ - :shortdesc: Run an additional strictness analysis before simplifier phase ⟨n⟩ + :shortdesc: Run an additional demand analysis before simplifier phase ⟨n⟩ :type: dynamic :category: - Run an additional strictness analysis before simplifier phase ⟨n⟩. + Run an additional demand analysis before simplifier phase ⟨n⟩. .. ghc-flag:: -funbox-small-strict-fields :shortdesc: Flatten strict constructor fields with a pointer-sized @@ -1308,14 +1432,20 @@ by saying ``-fno-wombat``. potential inlining. .. ghc-flag:: -fworker-wrapper - :shortdesc: Enable the worker-wrapper transformation. + :shortdesc: Enable the worker/wrapper transformation. :type: dynamic :category: - Enable the worker-wrapper transformation after a strictness - analysis pass. Implied by :ghc-flag:`-O`, and by :ghc-flag:`-fstrictness`. + Enable the worker/wrapper transformation after a demand analysis pass. + + Exploits strictness and absence information by unboxing strict arguments + and replacing absent fields by dummy values in a wrapper function that + will inline in all relevant scenarios and thus expose a specialised, + unboxed calling convention of the worker function. + + Implied by :ghc-flag:`-O`, and by :ghc-flag:`-fstrictness`. Disabled by :ghc-flag:`-fno-strictness`. Enabling :ghc-flag:`-fworker-wrapper` - while strictness analysis is disabled (by :ghc-flag:`-fno-strictness`) + while demand analysis is disabled (by :ghc-flag:`-fno-strictness`) has no effect. .. ghc-flag:: -fbinary-blob-threshold=⟨n⟩ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c70b5613a4ac59e4046feed23e7d99f388cdd958 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c70b5613a4ac59e4046feed23e7d99f388cdd958 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 Tue Nov 10 13:28:55 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 10 Nov 2020 08:28:55 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5faa9597a3fc_10ee3ffb8d8cb92811380b1@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: a940892b by Moritz Angermann at 2020-11-10T13:28:16+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a940892b6630589f998ab29cd0545d8a68e81434 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a940892b6630589f998ab29cd0545d8a68e81434 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 Tue Nov 10 13:32:16 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 10 Nov 2020 08:32:16 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 112 commits: SMP.h: Add C11-style atomic operations Message-ID: <5faa9660d89c8_10eeec9fec41139644@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - 78c22006 by Sebastian Graf at 2020-11-10T14:32:07+01:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - bebd73a7 by Sebastian Graf at 2020-11-10T14:32:07+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1((1(U),S(U)))`. This would allow Nested CPR to unbox the division, for example. Now other advances in expressiveness like #18885 are possible. Fixes #18903. - - - - - edea2fb9 by Sebastian Graf at 2020-11-10T14:32:07+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/EnumSet.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c70b5613a4ac59e4046feed23e7d99f388cdd958...edea2fb99faaa4706bcd781b508cc4e80b1715ba -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c70b5613a4ac59e4046feed23e7d99f388cdd958...edea2fb99faaa4706bcd781b508cc4e80b1715ba 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 Tue Nov 10 13:35:40 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 10 Nov 2020 08:35:40 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5faa972caa9de_10eeac87e4011402e4@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: f2f412ed by Moritz Angermann at 2020-11-10T13:35:31+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2f412edebd62d768736f2a6e3261f7ed803855a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2f412edebd62d768736f2a6e3261f7ed803855a 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 Tue Nov 10 14:54:54 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 10 Nov 2020 09:54:54 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 2 commits: Fix error output Message-ID: <5faaa9be17151_10ee3ffbafe36c881147246@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 81480c41 by Richard Eisenberg at 2020-11-09T14:23:08-05:00 Fix error output - - - - - 6a4ca962 by Richard Eisenberg at 2020-11-10T09:54:32-05:00 Reimplement flatten_exact_fam_app Hopefully will be faster? - - - - - 5 changed files: - compiler/GHC/Data/Maybe.hs - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/Solver/Monad.hs - testsuite/tests/patsyn/should_fail/T11010.stderr - testsuite/tests/roles/should_compile/Roles3.stderr Changes: ===================================== compiler/GHC/Data/Maybe.hs ===================================== @@ -16,7 +16,7 @@ module GHC.Data.Maybe ( failME, isSuccess, orElse, - firstJust, firstJusts, + firstJust, firstJusts, firstJustsM, whenIsJust, expectJust, rightToMaybe, @@ -31,6 +31,7 @@ import Control.Monad import Control.Monad.Trans.Maybe import Control.Exception (catch, SomeException(..)) import Data.Maybe +import Data.Foldable ( foldlM ) import GHC.Utils.Misc (HasCallStack) infixr 4 `orElse` @@ -51,6 +52,15 @@ firstJust a b = firstJusts [a, b] firstJusts :: [Maybe a] -> Maybe a firstJusts = msum +-- | Takes computations returnings @Maybes@; tries each one in order. +-- The first one to return a @Just@ wins. Returns @Nothing@ if all computations +-- return @Nothing at . +firstJustsM :: (Monad m, Foldable f) => f (m (Maybe a)) -> m (Maybe a) +firstJustsM = foldlM go Nothing where + go :: Monad m => Maybe a -> m (Maybe a) -> m (Maybe a) + go Nothing action = action + go result@(Just _) _action = return result + expectJust :: HasCallStack => String -> Maybe a -> a {-# INLINE expectJust #-} expectJust _ (Just x) = x ===================================== compiler/GHC/Tc/Solver/Flatten.hs ===================================== @@ -31,6 +31,7 @@ import GHC.Utils.Panic import GHC.Tc.Solver.Monad as TcS import GHC.Utils.Misc +import GHC.Data.Maybe import Control.Monad import GHC.Utils.Monad ( zipWith3M ) import Data.List.NonEmpty ( NonEmpty(..) ) @@ -748,7 +749,6 @@ so those families can get reduced. flatten_fam_app :: TyCon -> [TcType] -> FlatM (Xi, Coercion) -- flatten_fam_app can be over-saturated - -- flatten_exact_fam_app is exactly saturated -- flatten_exact_fam_app_fully lifts out the application to top level -- Postcondition: Coercion :: Xi ~ F tys flatten_fam_app tc tys -- Can be over-saturated @@ -769,6 +769,92 @@ flatten_fam_app tc tys -- Can be over-saturated -- See note [flatten_exact_fam_app_fully performance] flatten_exact_fam_app_fully :: TyCon -> [TcType] -> FlatM (Xi, Coercion) flatten_exact_fam_app_fully tc tys + = do { checkStackDepth (mkTyConApp tc tys) + + -- Step 1. Try to reduce without reducing arguments first. + ; result1 <- try_to_reduce tc tys + ; case result1 of + { Just (co, xi) -> finish (xi, co) + ; Nothing -> + + -- That didn't work. So reduce the arguments. + do { (xis, cos, kind_co) <- flatten_args_tc tc (repeat Nominal) tys + -- kind_co :: tcTypeKind(F xis) ~N tcTypeKind(F tys) + + ; eq_rel <- getEqRel + ; let role = eqRelRole eq_rel + args_co = mkTyConAppCo role tc cos + -- args_co :: F xis ~r F tys + + homogenise :: TcType -> TcCoercion -> (TcType, TcCoercion) + -- in (xi', co') = homogenise xi co + -- assume co :: xi ~r F xis, co is homogeneous + -- then xi' :: tcTypeKind(F tys) + -- and co' :: xi' ~r F tys, which is homogeneous + homogenise xi co = (casted_xi, final_co) + where + casted_xi = xi `mkCastTy` kind_co + -- casted_xi :: tcTypeKind(F tys) + homo_co = mkTcGReflLeftCo role xi kind_co + -- homo_co :: casted_xi ~r xi + + final_co = homo_co `mkTcTransCo` co `mkTcTransCo` args_co + + ; result2 <- liftTcS $ lookupFamAppInert tc xis + ; flavour <- getFlavour + ; case result2 of + { Just (co, xi, fr@(_, inert_eq_rel)) + -- co :: F xis ~ir xi + + | fr `eqCanRewriteFR` (flavour, eq_rel) -> + do { traceFlat "flatten/flat-cache hit" (ppr tc <+> ppr xis $$ ppr xi) + ; finish (homogenise xi downgraded_co) } + where + inert_role = eqRelRole inert_eq_rel + role = eqRelRole eq_rel + downgraded_co = tcDowngradeRole role inert_role (mkTcSymCo co) + -- downgraded_co :: xi ~r F xis + + ; _ -> + + -- inert didn't work. Try to reduce again + do { result3 <- try_to_reduce tc xis + ; case result3 of + Just (co, xi) -> finish (homogenise xi co) + Nothing -> return (homogenise reduced (mkTcReflCo role reduced)) + where + reduced = mkTyConApp tc xis }}}}} + where + -- call this if the above attempts made progress. + -- This recursively flattens the result and then adds to the cache + finish :: (Xi, Coercion) -> FlatM (Xi, Coercion) + finish (xi, co) = do { (fully, fully_co) <- bumpDepth $ flatten_one xi + ; let final_co = fully_co `mkTcTransCo` co + ; eq_rel <- getEqRel + ; flavour <- getFlavour + ; when (eq_rel == NomEq && flavour /= Derived) $ -- the cache only wants Nominal eqs + liftTcS $ extendFamAppCache tc tys (final_co, fully) + ; return (fully, final_co) } + +-- Returned coercion is output ~r input, where r is the role in the FlatM monad +try_to_reduce :: TyCon -> [TcType] -> FlatM (Maybe (TcCoercion, TcType)) +try_to_reduce tc tys + = do { flavour <- getFlavour + ; result <- liftTcS $ firstJustsM [ lookupFamAppCache flavour tc tys + , matchFam tc tys ] + ; downgrade result } + where + downgrade :: Maybe (TcCoercionN, TcType) -> FlatM (Maybe (TcCoercion, TcType)) + downgrade Nothing = return Nothing + downgrade (Just (co, xi)) + = do { traceFlat "Eager T.F. reduction success" $ + vcat [ ppr tc, ppr tys, ppr xi + , ppr co <+> dcolon <+> ppr (coercionKind co) + ] + ; role <- getRole + ; return (Just (tcDowngradeRole role Nominal co, xi)) } + +{- "RAE" -- See Note [Reduce type family applications eagerly] -- the following tcTypeKind should never be evaluated, as it's just used in -- casting, and casts by refl are dropped @@ -872,9 +958,8 @@ flatten_exact_fam_app_fully tc tys ; eq_rel <- getEqRel ; let co = maybeTcSubCo eq_rel norm_co `mkTransCo` mkSymCo final_co - ; flavour <- getFlavour - -- NB: only extend cache with nominal, given equalities - ; when (eq_rel == NomEq && flavour == Given) $ + -- NB: only extend cache with nominal equalities + ; when (eq_rel == NomEq) $ liftTcS $ extendFamAppCache tc tys (co, xi) ; let role = eqRelRole eq_rel xi' = xi `mkCastTy` kind_co @@ -899,9 +984,12 @@ flatten_exact_fam_app_fully tc tys `mkTransCo` mkSymCo final_co) ; return $ Just (xi, co) } Nothing -> pure Nothing } +-} {- Note [Reduce type family applications eagerly] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +"RAE": Update Note. + If we come across a type-family application like (Append (Cons x Nil) t), then, rather than flattening to a skolem etc, we may as well just reduce it on the spot to (Cons x t). This saves a lot of intermediate steps. @@ -943,6 +1031,8 @@ have any knowledge as to *why* these facts are true. Note [Runaway Derived rewriting] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +"RAE": Remove. We do occurs-checking now. + Suppose we have [WD] F a ~ T (F a) We *don't* want to fall into a hole using that to rewrite a Derived ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -91,7 +91,7 @@ module GHC.Tc.Solver.Monad ( foldIrreds, -- The flattening cache - lookupFamApp, extendFamAppCache, + lookupFamAppInert, lookupFamAppCache, extendFamAppCache, pprKicked, -- Inert function equalities @@ -189,6 +189,7 @@ import Data.List ( partition, mapAccumL ) import qualified Data.Semigroup as S import Data.List.NonEmpty ( NonEmpty(..), cons, toList, nonEmpty ) import qualified Data.List.NonEmpty as NE +import Control.Arrow ( first ) #if defined(DEBUG) import GHC.Data.Graph.Directed @@ -404,13 +405,15 @@ data InertSet , inert_famapp_cache :: FunEqMap (TcCoercion, TcType) -- If F tys :-> (co, rhs, flav), - -- then co :: F tys ~ rhs - -- flav is [G] + -- then co :: rhs ~ F tys + -- + -- Some entries in the cache might have arisen from Wanteds, and + -- so this should be used only for rewriting Wanteds. -- -- Just a hash-cons cache for use when reducing family applications -- only -- - -- Only nominal, Given equalities end up in here (along with + -- Only nominal equalities end up in here (along with -- top-level instances) , inert_solved_dicts :: DictMap CtEvidence @@ -2368,13 +2371,12 @@ removeInertCt is ct = CIrredCan {} -> panic "removeInertCt: CIrredEvCan" CNonCanonical {} -> panic "removeInertCt: CNonCanonical" --- | Looks up a family application in both the inerts and the famapp-cache -lookupFamApp :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavourRole)) -lookupFamApp fam_tc tys - = do { IS { inert_famapp_cache = famapp_cache - , inert_cans = IC { inert_funeqs = inert_funeqs } } <- getTcSInerts - ; return (firstJusts [lookup_inerts inert_funeqs, - lookup_famapps famapp_cache]) } +-- | Looks up a family application in the inerts; returned coercion +-- is oriented input ~ output +lookupFamAppInert :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavourRole)) +lookupFamAppInert fam_tc tys + = do { IS { inert_cans = IC { inert_funeqs = inert_funeqs } } <- getTcSInerts + ; return (lookup_inerts inert_funeqs) } where lookup_inerts inert_funeqs | Just (EqualCtList (CEqCan { cc_ev = ctev, cc_rhs = rhs } :| _)) @@ -2382,11 +2384,12 @@ lookupFamApp fam_tc tys = Just (ctEvCoercion ctev, rhs, ctEvFlavourRole ctev) | otherwise = Nothing - lookup_famapps famapp_cache - | Just (co, rhs) <- findFunEq famapp_cache fam_tc tys - = Just (co, rhs, (Given, NomEq)) - | otherwise = Nothing - +lookupFamAppCache :: CtFlavour -> TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType)) +lookupFamAppCache Given _ _ = return Nothing + -- the famapp_cache contains some wanteds. Not appropriate to rewrite a Given. +lookupFamAppCache _ fam_tc tys + = do { IS { inert_famapp_cache = famapp_cache } <- getTcSInerts + ; return (findFunEq famapp_cache fam_tc tys) } lookupInInerts :: CtLoc -> TcPredType -> TcS (Maybe CtEvidence) -- Is this exact predicate type cached in the solved or canonicals of the InertSet? @@ -3209,6 +3212,7 @@ zonkTyCoVarKind tv = wrapTcS (TcM.zonkTyCoVarKind tv) ---------------------------- extendFamAppCache :: TyCon -> [Type] -> (TcCoercion, TcType) -> TcS () +-- NB: co :: rhs ~ F tys, to match expectations of flattener extendFamAppCache tc xi_args stuff@(_, ty) = do { dflags <- getDynFlags ; when (gopt Opt_FamAppCache dflags) $ @@ -3489,8 +3493,8 @@ checkReductionDepth loc ty solverDepthErrorTcS loc ty } matchFam :: TyCon -> [Type] -> TcS (Maybe (CoercionN, TcType)) --- Given (F tys) return (ty, co), where co :: F tys ~N ty -matchFam tycon args = wrapTcS $ matchFamTcM tycon args +-- Given (F tys) return (ty, co), where co :: ty ~N F tys +matchFam tycon args = fmap (fmap (first mkTcSymCo)) $ wrapTcS $ matchFamTcM tycon args matchFamTcM :: TyCon -> [Type] -> TcM (Maybe (CoercionN, TcType)) -- Given (F tys) return (ty, co), where co :: F tys ~N ty ===================================== testsuite/tests/patsyn/should_fail/T11010.stderr ===================================== @@ -1,5 +1,5 @@ -T11010.hs:9:36: error: +T11010.hs:9:34: error: • Could not deduce: a1 ~ Int from the context: a ~ Int bound by the signature for pattern synonym ‘IntFun’ ===================================== testsuite/tests/roles/should_compile/Roles3.stderr ===================================== @@ -21,7 +21,7 @@ COERCION AXIOMS axiom Roles3.N:C3 :: C3 a b = a -> F3 b -> F3 b axiom Roles3.N:C4 :: C4 a b = a -> F4 b -> F4 b Dependent modules: [] -Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.16.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== Roles3.$tcC4 @@ -48,20 +48,18 @@ Roles3.$tc'C:C1 = GHC.Types.TyCon 4508088879886988796## 13962145553903222779## Roles3.$trModule (GHC.Types.TrNameS "'C:C1"#) 1 $krep -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0 -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 1 -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep -$krep [InlPrag=NOUSERINLINE[~]] - = GHC.Types.KindRepFun GHC.Types.krep$* $krep -$krep [InlPrag=NOUSERINLINE[~]] - = GHC.Types.KindRepFun GHC.Types.krep$* $krep -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0 +$krep [InlPrag=[~]] = GHC.Types.KindRepVar 1 +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint [] -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tc~ ((:) GHC.Types.krep$* ((:) $krep ((:) $krep []))) $krep [InlPrag=[~]] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a97a29b2f471d15fbfbc6572debdbde4c056e637...6a4ca962c448cba22b2a3f6c870a769f254f9ce1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a97a29b2f471d15fbfbc6572debdbde4c056e637...6a4ca962c448cba22b2a3f6c870a769f254f9ce1 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 Tue Nov 10 15:26:27 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 10:26:27 -0500 Subject: [Git][ghc/ghc][master] rts/linker: Fix relocation overflow in PE linker Message-ID: <5faab123b1498_10ee3ffbaec830e01159214@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 1 changed file: - rts/linker/PEi386.c Changes: ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d445cf05d47e8c5513c55cb5e7157b33e83c8123 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d445cf05d47e8c5513c55cb5e7157b33e83c8123 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 Tue Nov 10 15:27:06 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 10:27:06 -0500 Subject: [Git][ghc/ghc][master] Export SPEC from GHC.Exts (#13681) Message-ID: <5faab14a3677e_10ee3ffbac19f39c11621dc@gitlab.haskell.org.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: Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - [...] Content analysis details: (5.0 points, 5.0 required) pts rule name description ---- ---------------------- -------------------------------------------------- 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.8 RDNS_NONE Delivered to internal network by a host with no rDNS 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: Marge Bot Subject: [Git][ghc/ghc][master] Export SPEC from GHC.Exts (#13681) Date: Tue, 10 Nov 2020 10:27:06 -0500 Size: 12845 URL: From gitlab at gitlab.haskell.org Tue Nov 10 15:27:42 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 10:27:42 -0500 Subject: [Git][ghc/ghc][master] ghc-heap: expose decoding from heap representation Message-ID: <5faab16ea76b9_10ee3ffb94d83e2811649d4@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 3 changed files: - includes/rts/storage/Heap.h - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/Heap.c Changes: ===================================== includes/rts/storage/Heap.h ===================================== @@ -16,3 +16,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs , StgClosure *fun, StgClosure **payload, StgWord size); StgWord heap_view_closureSize(StgClosure *closure); + +/* + * Collect the pointers of a closure into the given array. `size` should be + * large enough to hold all collected pointers e.g. + * `heap_view_closureSize(closure)`. Returns the number of pointers collected. + * The caller must ensure that `closure` is not modified (or moved by the GC) + * for the duration of the call to `collect_pointers`. + */ +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[]); ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -7,6 +7,9 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE UnliftedFFITypes #-} {-| Module : GHC.Exts.Heap @@ -25,6 +28,7 @@ module GHC.Exts.Heap ( , ClosureType(..) , PrimType(..) , HasHeapRep(getClosureData) + , getClosureDataFromHeapRep -- * Info Table types , StgInfoTable(..) @@ -58,7 +62,7 @@ import GHC.Exts.Heap.Utils import Control.Monad import Data.Bits -import GHC.Arr +import Foreign import GHC.Exts import GHC.Int import GHC.Word @@ -66,13 +70,19 @@ import GHC.Word #include "ghcconfig.h" class HasHeapRep (a :: TYPE rep) where - getClosureData :: a -> IO Closure + + -- | Decode a closure to it's heap representation ('GenClosure'). + getClosureData + :: a + -- ^ Closure to decode. + -> IO Closure + -- ^ Heap representation of the closure. instance HasHeapRep (a :: TYPE 'LiftedRep) where - getClosureData = getClosure + getClosureData = getClosureDataFromHeapObject instance HasHeapRep (a :: TYPE 'UnliftedRep) where - getClosureData x = getClosure (unsafeCoerce# x) + getClosureData x = getClosureDataFromHeapObject (unsafeCoerce# x) instance Int# ~ a => HasHeapRep (a :: TYPE 'IntRep) where getClosureData x = return $ @@ -102,49 +112,84 @@ instance Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) where getClosureData x = return $ DoubleClosure { ptipe = PDouble, doubleVal = D# x } --- | This returns the raw representation of the given argument. The second --- component of the triple is the raw words of the closure on the heap, and the --- third component is those words that are actually pointers. Once back in the --- Haskell world, the raw words that hold pointers may be outdated after a --- garbage collector run, but the corresponding values in 'Box's will still --- point to the correct value. -getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box]) -getClosureRaw x = do +-- | Get the heap representation of a closure _at this moment_, even if it is +-- unevaluated or an indirection or other exotic stuff. Beware when passing +-- something to this function, the same caveats as for +-- 'GHC.Exts.Heap.Closures.asBox' apply. +-- +-- For most use cases 'getClosureData' is an easier to use alternative. +-- +-- Currently TSO and STACK objects will return `UnsupportedClosure`. This is +-- because it is not memory safe to extract TSO and STACK objects (done via +-- `unpackClosure#`). Other threads may be mutating those objects and interleave +-- with reads in `unpackClosure#`. This is particularly problematic with STACKs +-- where pointer values may be overwritten by non-pointer values as the +-- corresponding haskell thread runs. +getClosureDataFromHeapObject + :: a + -- ^ Heap object to decode. + -> IO Closure + -- ^ Heap representation of the closure. +getClosureDataFromHeapObject x = do case unpackClosure# x of --- This is a hack to cover the bootstrap compiler using the old version of --- 'unpackClosure'. The new 'unpackClosure' return values are not merely --- a reordering, so using the old version would not work. - (# iptr, dat, pointers #) -> do - let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE - end = fromIntegral nelems - 1 - rawWds = [W# (indexWordArray# dat i) | I# i <- [0.. end] ] - pelems = I# (sizeofArray# pointers) - ptrList = amap' Box $ Array 0 (pelems - 1) pelems pointers - pure (Ptr iptr, rawWds, ptrList) - --- From GHC.Runtime.Heap.Inspect -amap' :: (t -> b) -> Array Int t -> [b] -amap' f (Array i0 i _ arr#) = map g [0 .. i - i0] - where g (I# i#) = case indexArray# arr# i# of - (# e #) -> f e - --- | This function returns a parsed heap representation of the argument _at --- this moment_, even if it is unevaluated or an indirection or other exotic --- stuff. Beware when passing something to this function, the same caveats as --- for 'asBox' apply. -getClosure :: a -> IO Closure -getClosure x = do - (iptr, wds, pts) <- getClosureRaw x - itbl <- peekItbl iptr - -- The remaining words after the header - let rawWds = drop (closureTypeHeaderSize (tipe itbl)) wds - -- For data args in a pointers then non-pointers closure - -- This is incorrect in non pointers-first setups - -- not sure if that happens - npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) wds +#if MIN_VERSION_ghc_prim(0,5,3) + (# infoTableAddr, heapRep, pointersArray #) -> do +#else + -- This is a hack to cover the bootstrap compiler using the old version + -- of 'unpackClosure'. The new 'unpackClosure' return values are not + -- merely a reordering, so using the old version would not work. + (# infoTableAddr, pointersArray, heapRep #) -> do +#endif + let infoTablePtr = Ptr infoTableAddr + ptrList = [case indexArray# pointersArray i of + (# ptr #) -> Box ptr + | I# i <- [0..(I# (sizeofArray# pointersArray)) - 1] + ] + + infoTable <- peekItbl infoTablePtr + case tipe infoTable of + TSO -> pure $ UnsupportedClosure infoTable + STACK -> pure $ UnsupportedClosure infoTable + _ -> getClosureDataFromHeapRep heapRep infoTablePtr ptrList + +-- | Convert an unpacked heap object, to a `GenClosure b`. The inputs to this +-- function can be generated from a heap object using `unpackClosure#`. +getClosureDataFromHeapRep + :: ByteArray# + -- ^ Heap representation of the closure as returned by `unpackClosure#`. + -- This includes all of the object including the header, info table + -- pointer, pointer data, and non-pointer data. The ByteArray# may be + -- pinned or unpinned. + -> Ptr StgInfoTable + -- ^ Pointer to the `StgInfoTable` of the closure, extracted from the heap + -- representation. The info table must not be movable by GC i.e. must be in + -- pinned or off-heap memory. + -> [b] + -- ^ Pointers in the payload of the closure, extracted from the heap + -- representation as returned by `collect_pointers()` in `Heap.c`. The type + -- `b` is some representation of a pointer e.g. `Any` or `Ptr Any`. + -> IO (GenClosure b) + -- ^ Heap representation of the closure. +getClosureDataFromHeapRep heapRep infoTablePtr pts = do + itbl <- peekItbl infoTablePtr + let -- heapRep as a list of words. + rawHeapWords :: [Word] + rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ] + where + nelems = (I# (sizeofByteArray# heapRep)) `div` wORD_SIZE + end = fromIntegral nelems - 1 + + -- Just the payload of rawHeapWords (no header). + payloadWords :: [Word] + payloadWords = drop (closureTypeHeaderSize (tipe itbl)) rawHeapWords + + -- The non-pointer words in the payload. Only valid for closures with a + -- "pointers first" layout. Not valid for bit field layout. + npts :: [Word] + npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) rawHeapWords case tipe itbl of t | t >= CONSTR && t <= CONSTR_NOCAF -> do - (p, m, n) <- dataConNames iptr + (p, m, n) <- dataConNames infoTablePtr if m == "GHC.ByteCode.Instr" && n == "BreakInfo" then pure $ UnsupportedClosure itbl else pure $ ConstrClosure itbl pts npts p m n @@ -164,9 +209,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to AP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 raw words to AP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ APClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -181,9 +226,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to PAP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail "Expected at least 2 raw words to PAP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ PAPClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -218,10 +263,10 @@ getClosure x = do unless (length pts >= 3) $ fail $ "Expected at least 3 ptr argument to BCO, found " ++ show (length pts) - unless (length rawWds >= 4) $ + unless (length payloadWords >= 4) $ fail $ "Expected at least 4 words to BCO, found " - ++ show (length rawWds) - let splitWord = rawWds !! 3 + ++ show (length payloadWords) + let splitWord = payloadWords !! 3 pure $ BCOClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -230,27 +275,30 @@ getClosure x = do (fromIntegral splitWord) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) #endif - (drop 4 rawWds) + (drop 4 payloadWords) ARR_WORDS -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 words to ARR_WORDS, found " - ++ show (length rawWds) - pure $ ArrWordsClosure itbl (head rawWds) (tail rawWds) + ++ show (length payloadWords) + pure $ ArrWordsClosure itbl (head payloadWords) (tail payloadWords) t | t >= MUT_ARR_PTRS_CLEAN && t <= MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 words to MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ MutArrClosure itbl (rawWds !! 0) (rawWds !! 1) pts + ++ "found " ++ show (length payloadWords) + pure $ MutArrClosure itbl (payloadWords !! 0) (payloadWords !! 1) pts t | t >= SMALL_MUT_ARR_PTRS_CLEAN && t <= SMALL_MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 word to SMALL_MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ SmallMutArrClosure itbl (rawWds !! 0) pts + ++ "found " ++ show (length payloadWords) + pure $ SmallMutArrClosure itbl (payloadWords !! 0) pts - t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> + t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> do + unless (length pts >= 1) $ + fail $ "Expected at least 1 words to MUT_VAR, found " + ++ show (length pts) pure $ MutVarClosure itbl (head pts) t | t == MVAR_CLEAN || t == MVAR_DIRTY -> do @@ -260,13 +308,12 @@ getClosure x = do pure $ MVarClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) BLOCKING_QUEUE -> - pure $ OtherClosure itbl pts wds + pure $ OtherClosure itbl pts rawHeapWords -- pure $ BlockingQueueClosure itbl -- (pts !! 0) (pts !! 1) (pts !! 2) (pts !! 3) - -- pure $ OtherClosure itbl pts wds + -- pure $ OtherClosure itbl pts rawHeapWords -- - WEAK -> pure $ WeakClosure { info = itbl ===================================== rts/Heap.c ===================================== @@ -76,23 +76,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs } } -StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { - ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); - - StgWord size = heap_view_closureSize(closure); - StgWord nptrs = 0; - StgWord i; - - // First collect all pointers here, with the comfortable memory bound - // of the whole closure. Afterwards we know how many pointers are in - // the closure and then we can allocate space on the heap and copy them - // there - StgClosure *ptrs[size]; - +// See Heap.h +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[size]) { StgClosure **end; - StgClosure **ptr; - const StgInfoTable *info = get_itbl(closure); + StgWord nptrs = 0; + StgWord i; switch (info->type) { case INVALID_OBJECT: @@ -101,6 +90,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { // No pointers case ARR_WORDS: + case STACK: break; // Default layout @@ -123,7 +113,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case FUN_0_2: case FUN_STATIC: end = closure->payload + info->layout.payload.ptrs; - for (ptr = closure->payload; ptr < end; ptr++) { + for (StgClosure **ptr = closure->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -136,7 +126,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case THUNK_0_2: case THUNK_STATIC: end = ((StgThunk *)closure)->payload + info->layout.payload.ptrs; - for (ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { + for (StgClosure **ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -228,6 +218,21 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { break; } + return nptrs; +} + +StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); + + StgWord size = heap_view_closureSize(closure); + + // First collect all pointers here, with the comfortable memory bound + // of the whole closure. Afterwards we know how many pointers are in + // the closure and then we can allocate space on the heap and copy them + // there + StgClosure *ptrs[size]; + StgWord nptrs = collect_pointers(closure, size, ptrs); + size = nptrs + mutArrPtrsCardTableSize(nptrs); StgMutArrPtrs *arr = (StgMutArrPtrs *)allocate(cap, sizeofW(StgMutArrPtrs) + size); @@ -236,7 +241,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { arr->ptrs = nptrs; arr->size = size; - for (i = 0; ipayload[i] = ptrs[i]; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7814cd5bb0d145c4d83d7566885bdc3992b63d0c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7814cd5bb0d145c4d83d7566885bdc3992b63d0c 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 Tue Nov 10 15:28:17 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 10:28:17 -0500 Subject: [Git][ghc/ghc][master] Add test case for #17186. Message-ID: <5faab191bcea7_10ee3ffbadd865b01167498@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2 changed files: - + testsuite/tests/typecheck/should_compile/T17186.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== testsuite/tests/typecheck/should_compile/T17186.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE TypeOperators, AllowAmbiguousTypes #-} + +module T17186 where + +-- This test is significantly abbreviated from what was posted; see +-- #16512 for more context. + +type family Dim v + +type family v `OfDim` (n :: Dim v) = r | r -> n + +(!*^) :: Dim m `OfDim` j -> Dim m `OfDim` i +(!*^) = undefined ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,4 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) - +test('T17186', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa344d33dba71f31f55269c5fc733daa3830073a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa344d33dba71f31f55269c5fc733daa3830073a 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 Tue Nov 10 15:28:54 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 10:28:54 -0500 Subject: [Git][ghc/ghc][master] Add code comments for StgInfoTable and StgStack structs Message-ID: <5faab1b66bce0_10eeae8786c11702e9@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - 2 changed files: - includes/rts/storage/Closures.h - includes/rts/storage/TSO.h Changes: ===================================== includes/rts/storage/Closures.h ===================================== @@ -63,6 +63,11 @@ typedef struct { -------------------------------------------------------------------------- */ typedef struct { + // If TABLES_NEXT_TO_CODE is defined, then `info` is offset by + // `sizeof(StgInfoTable)` and so points to the `code` field of the + // StgInfoTable! You may want to use `get_itbl` to get the pointer to the + // start of the info table. See + // https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/rts/storage/heap-objects#tables_next_to_code. const StgInfoTable* info; #if defined(PROFILING) StgProfHeader prof; ===================================== includes/rts/storage/TSO.h ===================================== @@ -242,10 +242,22 @@ typedef struct StgTSO_ { typedef struct StgStack_ { StgHeader header; - StgWord32 stack_size; // stack size in *words* + + /* Size of the `stack` field in *words*. This is not affected by how much of + * the stack space is used, nor if more stack space is linked to by an + * UNDERFLOW_FRAME. + */ + StgWord32 stack_size; + StgWord8 dirty; // non-zero => dirty StgWord8 marking; // non-zero => someone is currently marking the stack - StgPtr sp; // current stack pointer + + /* Pointer to the "top" of the stack i.e. the most recently written address. + * The stack is filled downwards, so the "top" of the stack starts with `sp + * = stack + stack_size` and is decremented as the stack fills with data. + * See comment on "Invariants" below. + */ + StgPtr sp; StgWord stack[]; } StgStack; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e63a0fb1bdaecc7916a3cc35dcfd2b2ef37c328 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2e63a0fb1bdaecc7916a3cc35dcfd2b2ef37c328 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 Tue Nov 10 15:49:33 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 10:49:33 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5faab68d40cd2_10ee3ffb986d760c11793e3@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: e9a31e22 by Ben Gamari at 2020-11-10T10:49:27-05:00 Bump time submodule to 1.11 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 8 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9a31e2217e70dd3f543c9d763a997c1e83e8d76 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e9a31e2217e70dd3f543c9d763a997c1e83e8d76 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 Tue Nov 10 15:56:42 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 10:56:42 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/backports Message-ID: <5faab83a9c5e7_10ee3ffb8d19b464118258b@gitlab.haskell.org.mail> Ben Gamari deleted branch wip/backports at Glasgow Haskell Compiler / GHC -- 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 Tue Nov 10 15:56:43 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 10:56:43 -0500 Subject: [Git][ghc/ghc][ghc-9.0] 19 commits: Bignum: make GMP's bignat_add not recursive Message-ID: <5faab83b71545_10eecce7668118276c@gitlab.haskell.org.mail> Ben Gamari pushed to branch ghc-9.0 at Glasgow Haskell Compiler / GHC Commits: bba8f79c by Sylvain Henry at 2020-11-09T11:10:17-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. (cherry picked from commit bff74de713dac3e62c3bb6f1946e0649549f2215) - - - - - ed1699b2 by Tamar Christina at 2020-11-09T11:11:52-05:00 winio: Fix unused variables warnings (cherry picked from commit cb1f755c6fb77f140aee11fdc7b4da04dd5dcd02) - - - - - 0736b4e3 by Simon Peyton Jones at 2020-11-09T11:13:57-05:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion (cherry picked from commit 0b3d23afcad8bc14f2ba69b8dbe05c314e6e7b29) - - - - - 6c1cf280 by Tamar Christina at 2020-11-09T11:17:24-05:00 winio: simplify logic remove optimization step. (cherry picked from commit 412018c1214a19649e0ccfff73e80a0622635dd5) - - - - - e49c8923 by David Beacham at 2020-11-09T14:15:13-05:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog (cherry picked from commit 9ad51bc9d2ad9168abad271f715ce73d3562218a) - - - - - fb544de7 by Sylvain Henry at 2020-11-09T14:15:15-05:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a (cherry picked from commit 17d2f0a886f9f56ea408d2dd8b7f054021da19a4) - - - - - fa671e75 by Vladislav Zavialov at 2020-11-09T14:15:15-05:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. (cherry picked from commit bf2411a3c198cb2df93a9e0aa0c3b8297f47058d) - - - - - e5f73b99 by Ben Gamari at 2020-11-09T14:15:15-05:00 Bump win32-tarballs version to 0.3 This should fix #18774. (cherry picked from commit e5c7c9c8578de1248826c21ebd08e475d094a552) - - - - - 063d174f by Ben Gamari at 2020-11-09T14:15:15-05:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. (cherry picked from commit a848d52748c09a27ed5bef0fb039c51656bebdf1) - - - - - da266403 by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fixed bytestring reading interface. (cherry picked from commit 0fd3d360cab977e00fb6d90d0519962227b029bb) - - - - - c4fa35fa by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fixed more data error. (cherry picked from commit dfaef1cae7a4a0cb8783933274dae7f39d7165a0) - - - - - 556c2356 by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fix array splat (cherry picked from commit 6f0243ae5b359124936a8ff3dd0a287df3d7aca2) - - - - - c3a8c0bf by Tamar Christina at 2020-11-09T14:15:16-05:00 winio: fixed timeouts non-threaded. (cherry picked from commit c832f7e2a9314cfd61257cb161b1795b612d12b5) - - - - - e615aa85 by Andreas Klebinger at 2020-11-09T14:15:16-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) - - - - - 25a24e5d by Alan Zimmerman at 2020-11-09T14:15:16-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 (cherry picked from commit 616bec0dee67ae4841c4e60e9406cc9c63358223) - - - - - 2b3af303 by Ben Gamari at 2020-11-09T14:15:16-05:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. (cherry picked from commit 6434c2e35122886ad28a861cb857fa47bcc7e82d) - - - - - 06e7aed0 by Ben Gamari at 2020-11-09T14:15:16-05:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows (cherry picked from commit d76224c29a78ab962d86b9a1a92cde73e41b6479) - - - - - 918157d5 by Ben Gamari at 2020-11-09T19:17:08-05:00 testsuite: Update output for T18888_datakinds - - - - - 7fcca77f by Ben Gamari at 2020-11-09T19:17:13-05:00 testsuite: Update output for T12427a - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Flatten.hs - configure.ac - libraries/base/Data/Ord.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/Event/Windows.hsc - libraries/base/GHC/IO/Handle/Text.hs - libraries/base/GHC/IO/Windows/Handle.hsc - libraries/base/changelog.md - libraries/base/tests/IO/all.T - + libraries/base/tests/IO/bytestringread001.hs - + libraries/base/tests/IO/bytestringread001.stdout - libraries/ghc-bignum/src/GHC/Num/Backend/GMP.hs - mk/get-win32-tarballs.py - rts/RtsSymbols.c - rts/win32/AsyncWinIO.c - rts/win32/AsyncWinIO.h - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d7f5ec8232d9053b192cb94b19c5d5e85bc46f4...7fcca77f1b3d315b95de2acc76bdac3512a522ff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d7f5ec8232d9053b192cb94b19c5d5e85bc46f4...7fcca77f1b3d315b95de2acc76bdac3512a522ff 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 Tue Nov 10 15:59:37 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 10:59:37 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5faab8e981d01_10eee4bcc84118918c@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - ed33667f by Ben Gamari at 2020-11-10T10:59:29-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - a2d25a49 by Ben Gamari at 2020-11-10T10:59:29-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - a3dace81 by Ben Gamari at 2020-11-10T10:59:29-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - f3c2fcfe by Ben Gamari at 2020-11-10T10:59:29-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - a6d62c3e by Ömer Sinan Ağacan at 2020-11-10T10:59:30-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 76dbaae6 by Ray Shih at 2020-11-10T10:59:30-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 14d8717c by GHC GitLab CI at 2020-11-10T10:59:30-05:00 rts: Introduce highMemDynamic - - - - - f799294a by GHC GitLab CI at 2020-11-10T10:59:30-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - includes/rts/Linker.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/rts/storage/Heap.h - includes/rts/storage/TSO.h - libraries/base/GHC/Exts.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Heap.c - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3903c25fc0d998191940743dafc4ee80b40a7a2c...f799294a63bccbf287e091acd437be225bd57aa8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3903c25fc0d998191940743dafc4ee80b40a7a2c...f799294a63bccbf287e091acd437be225bd57aa8 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 Tue Nov 10 16:10:34 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 11:10:34 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-8.10-backports Message-ID: <5faabb7af5f8_10ee10ed53541216494@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-8.10-backports 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 Tue Nov 10 16:10:48 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 11:10:48 -0500 Subject: [Git][ghc/ghc][wip/dwarf-bindists] 1111 commits: DmdAnal: Improve handling of precise exceptions Message-ID: <5faabb88b074f_10ee10ed535412195fa@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/dwarf-bindists at Glasgow Haskell Compiler / GHC Commits: 9bd20e83 by Sebastian Graf at 2020-05-15T10:42:09-04:00 DmdAnal: Improve handling of precise exceptions This patch does two things: Fix possible unsoundness in what was called the "IO hack" and implement part 2.1 of the "fixing precise exceptions" plan in https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions, which, in combination with !2956, supersedes !3014 and !2525. **IO hack** The "IO hack" (which is a fallback to preserve precise exceptions semantics and thus soundness, rather than some smart thing that increases precision) is called `exprMayThrowPreciseException` now. I came up with two testcases exemplifying possible unsoundness (if twisted enough) in the old approach: - `T13380d`: Demonstrating unsoundness of the "IO hack" when resorting to manual state token threading and direct use of primops. More details below. - `T13380e`: Demonstrating unsoundness of the "IO hack" when we have Nested CPR. Not currently relevant, as we don't have Nested CPR yet. - `T13380f`: Demonstrating unsoundness of the "IO hack" for safe FFI calls. Basically, the IO hack assumed that precise exceptions can only be thrown from a case scrutinee of type `(# State# RealWorld, _ #)`. I couldn't come up with a program using the `IO` abstraction that violates this assumption. But it's easy to do so via manual state token threading and direct use of primops, see `T13380d`. Also similar code might be generated by Nested CPR in the (hopefully not too) distant future, see `T13380e`. Hence, we now have a more careful test in `forcesRealWorld` that passes `T13380{d,e}` (and will hopefully be robust to Nested CPR). **Precise exceptions** In #13380 and #17676 we saw that we didn't preserve precise exception semantics in demand analysis. We fixed that with minimal changes in !2956, but that was terribly unprincipled. That unprincipledness resulted in a loss of precision, which is tracked by these new test cases: - `T13380b`: Regression in dead code elimination, because !2956 was too syntactic about `raiseIO#` - `T13380c`: No need to apply the "IO hack" when the IO action may not throw a precise exception (and the existing IO hack doesn't detect that) Fixing both issues in !3014 turned out to be too complicated and had the potential to regress in the future. Hence we decided to only fix `T13380b` and augment the `Divergence` lattice with a new middle-layer element, `ExnOrDiv`, which means either `Diverges` (, throws an imprecise exception) or throws a *precise* exception. See the wiki page on Step 2.1 for more implementational details: https://gitlab.haskell.org/ghc/ghc/wikis/fixing-precise-exceptions#dead-code-elimination-for-raiseio-with-isdeadenddiv-introducing-exnordiv-step-21 - - - - - 568d7279 by Ben Gamari at 2020-05-15T10:42:46-04:00 GHC.Cmm.Opt: Handle MO_XX_Conv This MachOp was introduced by 2c959a1894311e59cd2fd469c1967491c1e488f3 but a wildcard match in cmmMachOpFoldM hid the fact that it wasn't handled. Ideally we would eliminate the match but this appears to be a larger task. Fixes #18141. - - - - - 5bcf8606 by Ryan Scott at 2020-05-17T08:46:38-04:00 Remove duplicate Note [When to print foralls] in GHC.Core.TyCo.Ppr There are two different Notes named `[When to print foralls]`. The most up-to-date one is in `GHC.Iface.Type`, but there is a second one in `GHC.Core.TyCo.Ppr`. The latter is less up-to-date, as it was written before GHC switched over to using ifaces to pretty-print types. I decided to just remove the latter and replace it with a reference to the former. [ci skip] - - - - - 55f0e783 by Fumiaki Kinoshita at 2020-05-21T12:10:44-04:00 base: Add Generic instances to various datatypes under GHC.* * GHC.Fingerprint.Types: Fingerprint * GHC.RTS.Flags: GiveGCStats, GCFlags, ConcFlags, DebugFlags, CCFlags, DoHeapProfile, ProfFlags, DoTrace, TraceFlags, TickyFlags, ParFlags and RTSFlags * GHC.Stats: RTSStats and GCStats * GHC.ByteOrder: ByteOrder * GHC.Unicode: GeneralCategory * GHC.Stack.Types: SrcLoc Metric Increase: haddock.base - - - - - a9311cd5 by Gert-Jan Bottu at 2020-05-21T12:11:31-04:00 Explicit Specificity Implementation for Ticket #16393. Explicit specificity allows users to manually create inferred type variables, by marking them with braces. This way, the user determines which variables can be instantiated through visible type application. The additional syntax is included in the parser, allowing users to write braces in type variable binders (type signatures, data constructors etc). This information is passed along through the renamer and verified in the type checker. The AST for type variable binders, data constructors, pattern synonyms, partial signatures and Template Haskell has been updated to include the specificity of type variables. Minor notes: - Bumps haddock submodule - Disables pattern match checking in GHC.Iface.Type with GHC 8.8 - - - - - 24e61aad by Ben Price at 2020-05-21T12:12:17-04:00 Lint should say when it is checking a rule It is rather confusing that when lint finds an error in a rule attached to a binder, it reports the error as in the RHS, not the rule: ... In the RHS of foo We add a clarifying line: ... In the RHS of foo In a rule attached to foo The implication that the rule lives inside the RHS is a bit odd, but this niggle is already present for unfoldings, whose pattern we are following. - - - - - 78c6523c by Ben Gamari at 2020-05-21T12:13:01-04:00 nonmoving: Optimise the write barrier - - - - - 13f6c9d0 by Andreas Klebinger at 2020-05-21T12:13:45-04:00 Refactor linear reg alloc to remember past assignments. When assigning registers we now first try registers we assigned to in the past, instead of picking the "first" one. This is in extremely helpful when dealing with loops for which variables are dead for part of the loop. This is important for patterns like this: foo = arg1 loop: use(foo) ... foo = getVal() goto loop; There we: * assign foo to the register of arg1. * use foo, it's dead after this use as it's overwritten after. * do other things. * look for a register to put foo in. If we pick an arbitrary one it might differ from the register the start of the loop expect's foo to be in. To fix this we simply look for past register assignments for the given variable. If we find one and the register is free we use that register. This reduces the need for fixup blocks which match the register assignment between blocks. In the example above between the end and the head of the loop. This patch also moves branch weight estimation ahead of register allocation and adds a flag to control it (cmm-static-pred). * It means the linear allocator is more likely to assign the hotter code paths first. * If it assign these first we are: + Less likely to spill on the hot path. + Less likely to introduce fixup blocks on the hot path. These two measure combined are surprisingly effective. Based on nofib we get in the mean: * -0.9% instructions executed * -0.1% reads/writes * -0.2% code size. * -0.1% compiler allocations. * -0.9% compile time. * -0.8% runtime. Most of the benefits are simply a result of removing redundant moves and spills. Reduced compiler allocations likely are the result of less code being generated. (The added lookup is mostly non-allocating). - - - - - edc2cc58 by Andreas Klebinger at 2020-05-21T12:14:25-04:00 NCG: Codelayout: Distinguish conditional and other branches. In #18053 we ended up with a suboptimal code layout because the code layout algorithm didn't distinguish between conditional and unconditional control flow. We can completely eliminate unconditional control flow instructions by placing blocks next to each other, not so much for conditionals. In terms of implementation we simply give conditional branches less weight before computing the layout. Fixes #18053 - - - - - b7a6b2f4 by Gleb Popov at 2020-05-21T12:15:26-04:00 gitlab-ci: Set locale to C.UTF-8. - - - - - a8c27cf6 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Allow spaces in GHCi :script file names This patch updates the user interface of GHCi so that file names passed to the ':script' command may contain spaces escaped with a backslash. For example: :script foo\ bar.script The implementation uses a modified version of 'words' that does not break on escaped spaces. Fixes #18027. - - - - - 82663959 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Add extra tests for GHCi :script syntax checks The syntax for GHCi's ":script" command allows for only a single file name to be passed as an argument. This patch adds a test for the cases in which a file name is missing or multiple file names are passed. Related to #T18027. - - - - - a0b79e1b by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Allow GHCi :script file names in double quotes This patch updates the user interface of GHCi so that file names passed to the ':script' command can be wrapped in double quotes. For example: :script "foo bar.script" The implementation uses a modified version of 'words' that treats character sequences enclosed in double quotes as single words. Fixes #18027. - - - - - cf566330 by Stefan Holdermans at 2020-05-21T12:16:08-04:00 Update documentation for GHCi :script This patch adds the fixes that allow for file names containing spaces to be passed to GHCi's ':script' command to the release notes for 8.12 and expands the user-guide documentation for ':script' by mentioning how such file names can be passed. Related to #18027. - - - - - 0004ccb8 by Tuan Le at 2020-05-21T12:16:46-04:00 llvmGen: Consider Relocatable read-only data as not constantReferences: #18137 - - - - - 964d3ea2 by John Ericson at 2020-05-21T12:17:30-04:00 Use `Checker` for `tc_pat` - - - - - b797aa42 by John Ericson at 2020-05-21T12:17:30-04:00 Use `Checker` for `tc_lpat` and `tc_lpats` - - - - - 5108e84a by John Ericson at 2020-05-21T12:17:30-04:00 More judiciously panic in `ts_pat` - - - - - 510e0451 by John Ericson at 2020-05-21T12:17:30-04:00 Put `PatEnv` first in `GHC.Tc.Gen.Pat.Checker` - - - - - cb4231db by John Ericson at 2020-05-21T12:17:30-04:00 Tiny cleaup eta-reduce away a function argument In GHC, not in the code being compiled! - - - - - 6890c38d by John Ericson at 2020-05-21T12:17:30-04:00 Use braces with do in `SplicePat` case for consistency - - - - - 3451584f by buggymcbugfix at 2020-05-21T12:18:06-04:00 Fix spelling mistakes and typos - - - - - b552e531 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Add INLINABLE pragmas to Enum list producers The INLINABLE pragmas ensure that we export stable (unoptimised) unfoldings in the interface file so we can do list fusion at usage sites. Related tickets: #15185, #8763, #18178. - - - - - e7480063 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Piggyback on Enum Word methods for Word64 If we are on a 64 bit platform, we can use the efficient Enum Word methods for the Enum Word64 instance. - - - - - 892b0c41 by buggymcbugfix at 2020-05-21T12:18:06-04:00 Document INLINE(ABLE) pragmas that enable fusion - - - - - 2b363ebb by Richard Eisenberg at 2020-05-21T12:18:45-04:00 MR template should ask for key part - - - - - a95bbd0b by Sebastian Graf at 2020-05-21T12:19:37-04:00 Make `Int`'s `mod` and `rem` strict in their first arguments They used to be strict until 4d2ac2d (9 years ago). It's obviously better to be strict for performance reasons. It also blocks #18067. NoFib results: ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- integer -1.1% +0.4% wheel-sieve2 +21.2% +20.7% -------------------------------------------------------------------------------- Min -1.1% -0.0% Max +21.2% +20.7% Geometric Mean +0.2% +0.2% ``` The regression in `wheel-sieve2` is due to reboxing that likely will go away with the resolution of #18067. See !3282 for details. Fixes #18187. - - - - - d3d055b8 by Galen Huntington at 2020-05-21T12:20:18-04:00 Clarify pitfalls of NegativeLiterals; see #18022. - - - - - 1b508a9e by Alexey Kuleshevich at 2020-05-21T12:21:02-04:00 Fix wording in primops documentation to reflect the correct reasoning: * Besides resizing functions, shrinking ones also mutate the size of a mutable array and because of those two `sizeofMutabeByteArray` and `sizeofSmallMutableArray` are now deprecated * Change reference in documentation to the newer functions `getSizeof*` instead of `sizeof*` for shrinking functions * Fix incorrect mention of "byte" instead of "small" - - - - - 4ca0c8a1 by Andreas Klebinger at 2020-05-21T12:21:53-04:00 Don't variable-length encode magic iface constant. We changed to use variable length encodings for many types by default, including Word32. This makes sense for numbers but not when Word32 is meant to represent four bytes. I added a FixedLengthEncoding newtype to Binary who's instances interpret their argument as a collection of bytes instead of a number. We then use this when writing/reading magic numbers to the iface file. I also took the libery to remove the dummy iface field. This fixes #18180. - - - - - a1275081 by Krzysztof Gogolewski at 2020-05-21T12:22:35-04:00 Add a regression test for #11506 The testcase works now. See explanation in https://gitlab.haskell.org/ghc/ghc/issues/11506#note_273202 - - - - - 8a816e5f by Krzysztof Gogolewski at 2020-05-21T12:23:55-04:00 Sort deterministically metric output Previously, we sorted according to the test name and way, but the metrics (max_bytes_used/peak_megabytes_allocated etc.) were appearing in nondeterministic order. - - - - - 566cc73f by Sylvain Henry at 2020-05-21T12:24:45-04:00 Move isDynLinkName into GHC.Types.Name It doesn't belong into GHC.Unit.State - - - - - d830bbc9 by Adam Sandberg Ericsson at 2020-05-23T13:36:20-04:00 docs: fix formatting and add some links [skip ci] - - - - - 49301ad6 by Andrew Martin at 2020-05-23T13:37:01-04:00 Implement cstringLength# and FinalPtr This function and its accompanying rule resolve issue #5218. A future PR to the bytestring library will make the internal Data.ByteString.Internal.unsafePackAddress compute string length with cstringLength#. This will improve the status quo because it is eligible for constant folding. Additionally, introduce a new data constructor to ForeignPtrContents named FinalPtr. This additional data constructor, when used in the IsString instance for ByteString, leads to more Core-to-Core optimization opportunities, fewer runtime allocations, and smaller binaries. Also, this commit re-exports all the functions from GHC.CString (including cstringLength#) in GHC.Exts. It also adds a new test driver. This test driver is used to perform substring matches on Core that is dumped after all the simplifier passes. In this commit, it is used to check that constant folding of cstringLength# works. - - - - - dcd6bdcc by Ben Gamari at 2020-05-23T13:37:48-04:00 simplCore: Ignore ticks in rule templates This fixes #17619, where a tick snuck in to the template of a rule, resulting in a panic during rule matching. The tick in question was introduced via post-inlining, as discussed in `Note [Simplifying rules]`. The solution we decided upon was to simply ignore ticks in the rule template, as discussed in `Note [Tick annotations in RULE matching]`. Fixes #18162. Fixes #17619. - - - - - 82cb8913 by John Ericson at 2020-05-23T13:38:32-04:00 Fix #18145 and also avoid needless work with implicit vars - `forAllOrNothing` now is monadic, so we can trace whether we bind an explicit `forall` or not. - #18145 arose because the free vars calculation was needlessly complex. It is now greatly simplified. - Replaced some other implicit var code with `filterFreeVarsToBind`. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - a60dc835 by Ben Gamari at 2020-05-23T13:39:12-04:00 Bump process submodule Fixes #17926. - - - - - 856adf54 by Ben Gamari at 2020-05-23T13:40:21-04:00 users-guide: Clarify meaning of -haddock flag Fixes #18206. - - - - - 7ae57afd by Ben Gamari at 2020-05-23T13:41:03-04:00 git: Add ignored commits file This can be used to tell git to ignore bulk renaming commits like the recently-finished module hierarchy refactoring. Configured with, git config blame.ignoreRevsFile .git-ignore-revs - - - - - 63d30e60 by jneira at 2020-05-24T01:54:42-04:00 Add hie-bios script for windows systems It is a direct translation of the sh script - - - - - 59182b88 by jneira at 2020-05-24T01:54:42-04:00 Honour previous values for CABAL and CABFLAGS The immediate goal is let the hie-bios.bat script set CABFLAGS with `-v0` and remove all cabal output except the compiler arguments - - - - - 932dc54e by jneira at 2020-05-24T01:54:42-04:00 Add specific configuration for windows in hie.yaml - - - - - e0eda070 by jneira at 2020-05-24T01:54:42-04:00 Remove not needed hie-bios output - - - - - a0ea59d6 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Move Config module into GHC.Settings - - - - - 37430251 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Rename GHC.Core.Arity into GHC.Core.Opt.Arity - - - - - a426abb9 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Rename GHC.Hs.Types into GHC.Hs.Type See discussion in https://gitlab.haskell.org/ghc/ghc/issues/13009#note_268610 - - - - - 1c91a7a0 by Sylvain Henry at 2020-05-24T01:55:24-04:00 Bump haddock submodule - - - - - 66bd24d1 by Ryan Scott at 2020-05-24T01:56:03-04:00 Add orderingTyCon to wiredInTyCons (#18185) `Ordering` needs to be wired in for use in the built-in `CmpNat` and `CmpSymbol` type families, but somehow it was never added to the list of `wiredInTyCons`, leading to the various oddities observed in #18185. Easily fixed by moving `orderingTyCon` from `basicKnownKeyNames` to `wiredInTyCons`. Fixes #18185. - - - - - 01c43634 by Matthew Pickering at 2020-05-24T01:56:42-04:00 Remove unused hs-boot file - - - - - 7a07aa71 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix cross-compiler build (#16051) - - - - - 15ccca16 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix distDir per stage - - - - - b420fb24 by Sylvain Henry at 2020-05-24T15:22:17-04:00 Hadrian: fix hp2ps error during cross-compilation Fixed by @alp (see https://gitlab.haskell.org/ghc/ghc/issues/16051#note_274265) - - - - - cd339ef0 by Joshua Price at 2020-05-24T15:22:56-04:00 Make Unicode brackets opening/closing tokens (#18225) The tokens `[|`, `|]`, `(|`, and `|)` are opening/closing tokens as described in GHC Proposal #229. This commit makes the unicode variants (`⟦`, `⟧`, `⦇`, and `⦈`) act the same as their ASCII counterparts. - - - - - 013d7120 by Ben Gamari at 2020-05-25T09:48:17-04:00 Revert "Specify kind variables for inferred kinds in base." As noted in !3132, this has rather severe knock-on consequences in user-code. We'll need to revisit this before merging something along these lines. This reverts commit 9749fe1223d182b1f8e7e4f7378df661c509f396. - - - - - 4c4312ed by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Drop redundant ad-hoc boot module check To determine whether the module is a boot module Coverage.addTicksToBinds was checking for a `boot` suffix in the module source filename. This is quite ad-hoc and shouldn't be necessary; the callsite in `deSugar` already checks that the module isn't a boot module. - - - - - 1abf3c84 by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Make tickBoxCount strict This could otherwise easily cause a leak of (+) thunks. - - - - - b2813750 by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Make ccIndices strict This just seems like a good idea. - - - - - 02e278eb by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Don't produce ModBreaks if not HscInterpreted emptyModBreaks contains a bottom and consequently it's important that we don't use it unless necessary. - - - - - b8c014ce by Ben Gamari at 2020-05-25T09:48:53-04:00 Coverage: Factor out addMixEntry - - - - - 53814a64 by Zubin Duggal at 2020-05-26T03:03:24-04:00 Add info about typeclass evidence to .hie files See `testsuite/tests/hiefile/should_run/HieQueries.hs` and `testsuite/tests/hiefile/should_run/HieQueries.stdout` for an example of this We add two new fields, `EvidenceVarBind` and `EvidenceVarUse` to the `ContextInfo` associated with an Identifier. These are associated with the appropriate identifiers for the evidence variables collected when we come across `HsWrappers`, `TcEvBinds` and `IPBinds` while traversing the AST. Instance dictionary and superclass selector dictionaries from `tcg_insts` and classes defined in `tcg_tcs` are also recorded in the AST as originating from their definition span This allows us to save a complete picture of the evidence constructed by the constraint solver, and will let us report this to the user, enabling features like going to the instance definition from the invocation of a class method(or any other method taking a constraint) and finding all usages of a particular instance. Additionally, - Mark NodeInfo with an origin so we can differentiate between bindings origininating in the source vs those in ghc - Along with typeclass evidence info, also include information on Implicit Parameters - Add a few utility functions to HieUtils in order to query the new info Updates haddock submodule - - - - - 6604906c by Sebastian Graf at 2020-05-26T03:04:04-04:00 Make WorkWrap.Lib.isWorkerSmallEnough aware of the old arity We should allow a wrapper with up to 82 parameters when the original function had 82 parameters to begin with. I verified that this made no difference on NoFib, but then again it doesn't use huge records... Fixes #18122. - - - - - cf772f19 by Sylvain Henry at 2020-05-26T03:04:45-04:00 Enhance Note [About units] for Backpack - - - - - ede24126 by Takenobu Tani at 2020-05-27T00:13:55-04:00 core-spec: Modify file paths according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * GHC/Core.hs <= coreSyn/CoreSyn.hs * GHC/Core/Coercion.hs <= types/Coercion.hs * GHC/Core/Coercion/Axiom.hs <= types/CoAxiom.hs * GHC/Core/Coercion/Opt.hs <= types/OptCoercion.hs * GHC/Core/DataCon.hs <= basicTypes/DataCon.hs * GHC/Core/FamInstEnv.hs <= types/FamInstEnv.hs * GHC/Core/Lint.hs <= coreSyn/CoreLint.hs * GHC/Core/Subst.hs <= coreSyn/CoreSubst.hs * GHC/Core/TyCo/Rep.hs <= types/TyCoRep.hs * GHC/Core/TyCon.hs <= types/TyCon.hs * GHC/Core/Type.hs <= types/Type.hs * GHC/Core/Unify.hs <= types/Unify.hs * GHC/Types/Literal.hs <= basicTypes/Literal.hs * GHC/Types/Var.hs <= basicTypes/Var.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [skip ci] - - - - - 04750304 by Ben Gamari at 2020-05-27T00:14:33-04:00 eventlog: Fix racy flushing Previously no attempt was made to avoid multiple threads writing their capability-local eventlog buffers to the eventlog writer simultaneously. This could result in multiple eventlog streams being interleaved. Fix this by documenting that the EventLogWriter's write() and flush() functions may be called reentrantly and fix the default writer to protect its FILE* by a mutex. Fixes #18210. - - - - - d6203f24 by Joshua Price at 2020-05-27T00:15:17-04:00 Make `identifier` parse unparenthesized `->` (#18060) - - - - - 28deee28 by Ben Gamari at 2020-05-28T16:23:21-04:00 GHC.Core.Unfold: Refactor traceInline This reduces duplication as well as fixes a bug wherein -dinlining-check would override -ddump-inlinings. Moreover, the new variant - - - - - 1f393e1e by Ben Gamari at 2020-05-28T16:23:21-04:00 Avoid unnecessary allocations due to tracing utilities While ticky-profiling the typechecker I noticed that hundreds of millions of SDocs are being allocated just in case -ddump-*-trace is enabled. This is awful. We avoid this by ensuring that the dump flag check is inlined into the call site, ensuring that the tracing document needn't be allocated unless it's actually needed. See Note [INLINE conditional tracing utilities] for details. Fixes #18168. Metric Decrease: T9961 haddock.Cabal haddock.base haddock.compiler - - - - - 5f621a78 by Vladislav Zavialov at 2020-05-28T16:23:58-04:00 Add Semigroup/Monoid for Q (#18123) - - - - - dc5f004c by Xavier Denis at 2020-05-28T16:24:37-04:00 Fix #18071 Run the core linter on candidate instances to ensure they are well-kinded. Better handle quantified constraints by using a CtWanted to avoid having unsolved constraints thrown away at the end by the solver. - - - - - 10e6982c by Sebastian Graf at 2020-05-28T16:25:14-04:00 FloatOut: Only eta-expand dead-end RHS if arity will increase (#18231) Otherwise we risk turning trivial RHS into non-trivial RHS, introducing unnecessary bindings in the next Simplifier run, resulting in more churn. Fixes #18231. - - - - - 08dab5f7 by Sebastian Graf at 2020-05-28T16:25:14-04:00 DmdAnal: Recognise precise exceptions from case alternatives (#18086) Consider ```hs m :: IO () m = do putStrLn "foo" error "bar" ``` `m` (from #18086) always throws a (precise or imprecise) exception or diverges. Yet demand analysis infers `<L,A>` as demand signature instead of `<L,A>x` for it. That's because the demand analyser sees `putStrLn` occuring in a case scrutinee and decides that it has to `deferAfterPreciseException`, because `putStrLn` throws a precise exception on some control flow paths. This will mask the `botDiv` `Divergence`of the single case alt containing `error` to `topDiv`. Since `putStrLn` has `topDiv` itself, the final `Divergence` is `topDiv`. This is easily fixed: `deferAfterPreciseException` works by `lub`ing with the demand type of a virtual case branch denoting the precise exceptional control flow. We used `nopDmdType` before, but we can be more precise and use `exnDmdType`, which is `nopDmdType` with `exnDiv`. Now the `Divergence` from the case alt will degrade `botDiv` to `exnDiv` instead of `topDiv`, which combines with the result from the scrutinee to `exnDiv`, and all is well. Fixes #18086. - - - - - aef95f11 by Ben Gamari at 2020-05-28T16:25:53-04:00 Ticky-ticky: Record DataCon name in ticker name This makes it significantly easier to spot the nature of allocations regressions and comes at a reasonably low cost. - - - - - 8f021b8c by Ben Gamari at 2020-05-28T16:26:34-04:00 hadrian: Don't track GHC's verbosity argument Teach hadrian to ignore GHC's -v argument in its recompilation check, thus fixing #18131. - - - - - 13d9380b by Ben Gamari at 2020-05-28T16:27:20-04:00 Rip out CmmStackInfo(updfr_space) As noted in #18232, this field is currently completely unused and moreover doesn't have a clear meaning. - - - - - f10d11fa by Andreas Klebinger at 2020-05-29T01:38:42-04:00 Fix "build/elem" RULE. An redundant constraint prevented the rule from matching. Fixing this allows a call to elem on a known list to be translated into a series of equality checks, and eventually a simple case expression. Surprisingly this seems to regress elem for strings. To avoid this we now also allow foldrCString to inline and add an UTF8 variant. This results in elem being compiled to a tight non-allocating loop over the primitive string literal which performs a linear search. In the process this commit adds UTF8 variants for some of the functions in GHC.CString. This is required to make this work for both ASCII and UTF8 strings. There are also small tweaks to the CString related rules. We now allow ourselfes the luxury to compare the folding function via eqExpr, which helps to ensure the rule fires before we inline foldrCString*. Together with a few changes to allow matching on both the UTF8 and ASCII variants of the CString functions. - - - - - bbeb2389 by Ben Gamari at 2020-05-29T01:39:19-04:00 CoreToStg: Add Outputable ArgInfo instance - - - - - 0e3361ca by Simon Peyton Jones at 2020-05-29T01:39:19-04:00 Make Lint check return type of a join point Consider join x = rhs in body It's important that the type of 'rhs' is the same as the type of 'body', but Lint wasn't checking that invariant. Now it does! This was exposed by investigation into !3113. - - - - - c49f7df0 by Simon Peyton Jones at 2020-05-29T01:39:19-04:00 Do not float join points in exprIsConApp_maybe We hvae been making exprIsConApp_maybe cleverer in recent times: commit b78cc64e923716ac0512c299f42d4d0012306c05 Date: Thu Nov 15 17:14:31 2018 +0100 Make constructor wrappers inline only during the final phase commit 7833cf407d1f608bebb1d38bb99d3035d8d735e6 Date: Thu Jan 24 17:58:50 2019 +0100 Look through newtype wrappers (Trac #16254) commit c25b135ff5b9c69a90df0ccf51b04952c2dc6ee1 Date: Thu Feb 21 12:03:22 2019 +0000 Fix exprIsConApp_maybe But alas there was still a bug, now immortalised in Note [Don't float join points] in SimpleOpt. It's quite hard to trigger because it requires a dead join point, but it came up when compiling Cabal Cabal.Distribution.Fields.Lexer.hs, when working on !3113. Happily, the fix is extremly easy. Finding the bug was not so easy. - - - - - 46720997 by Ben Gamari at 2020-05-29T01:39:19-04:00 Allow simplification through runRW# Because runRW# inlines so late, we were previously able to do very little simplification across it. For instance, given even a simple program like case runRW# (\s -> let n = I# 42# in n) of I# n# -> f n# we previously had no way to avoid the allocation of the I#. This patch allows the simplifier to push strict contexts into the continuation of a runRW# application, as explained in in Note [Simplification of runRW#] in GHC.CoreToStg.Prep. Fixes #15127. Metric Increase: T9961 Metric Decrease: ManyConstructors Co-Authored-By: Simon Peyton-Jone <simonpj at microsoft.com> - - - - - 277c2f26 by Ben Gamari at 2020-05-29T01:39:55-04:00 Eta expand un-saturated primops Now since we no longer try to predict CAFfyness we have no need for the solution to #16846. Eta expanding unsaturated primop applications is conceptually simpler, especially in the presence of levity polymorphism. This essentially reverts cac8dc9f51e31e4c0a6cd9bc302f7e1bc7c03beb, as suggested in #18079. Closes #18079. - - - - - f44d7ae0 by Simon Jakobi at 2020-05-29T01:40:34-04:00 base: Scrap deprecation plan for Data.Monoid.{First,Last} See the discussion on the libraries mailing list for context: https://mail.haskell.org/pipermail/libraries/2020-April/030357.html - - - - - 8b494895 by Jeremy Schlatter at 2020-05-29T01:41:12-04:00 Fix typo in documentation - - - - - 998450f4 by Gleb Popov at 2020-05-29T01:41:53-04:00 Always define USE_PTHREAD_FOR_ITIMER for FreeBSD. - - - - - f9a513e0 by Alp Mestanogullari at 2020-05-29T01:42:36-04:00 hadrian: introduce 'install' target Its logic is very simple. It `need`s the `binary-dist-dir` target and runs suitable `configure` and `make install` commands for the user. A new `--prefix` command line argument is introduced to specify where GHC should be installed. - - - - - 67738db1 by Travis Whitaker at 2020-05-29T13:34:48-04:00 Build a threaded stage 1 if the bootstrapping GHC supports it. - - - - - aac19e6c by Peter Trommler at 2020-05-29T13:35:24-04:00 PPC NCG: No per-symbol .section ".toc" directives All position independent symbols are collected during code generation and emitted in one go. Prepending each symbol with a .section ".toc" directive is redundant. This patch drops the per-symbol directives leading to smaller assembler files. Fixes #18250 - - - - - 4413828b by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Teach getNumProcessors to return available processors Previously we would report the number of physical processors, which can be quite wrong in a containerized setting. Now we rather return how many processors are in our affinity mask when possible. I also refactored the code to prefer platform-specific since this will report logical CPUs instead of physical (using `machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD). Fixes #14781. - - - - - 1449435c by Ben Gamari at 2020-05-30T06:07:31-04:00 users-guide: Note change in getNumProcessors in users guide - - - - - 3d960169 by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Drop compatibility shims for Windows Vista We can now assume that the thread and processor group interfaces are available. - - - - - 7f8f948c by Peter Trommler at 2020-05-30T06:08:07-04:00 PPC NCG: Fix .size directive on powerpc64 ELF v1 Thanks to Sergei Trofimovich for pointing out the issue. Fixes #18237 - - - - - 7c555b05 by Andreas Klebinger at 2020-05-30T06:08:43-04:00 Optimize GHC.Utils.Monad. Many functions in this module are recursive and as such are marked loop breakers. Which means they are unlikely to get an unfolding. This is *bad*. We always want to specialize them to specific Monads. Which requires a visible unfolding at the use site. I rewrote the recursive ones from: foo f x = ... foo x' ... to foo f x = go x where go x = ... As well as giving some pragmas to make all of them available for specialization. The end result is a reduction of allocations of about -1.4% for nofib/spectral/simple/Main.hs when compiled with `-O`. ------------------------- Metric Decrease: T12425 T14683 T5631 T9233 T9675 T9961 WWRec ------------------------- - - - - - 8b1cb5df by Ben Gamari at 2020-05-30T06:09:20-04:00 Windows: Bump Windows toolchain to 0.2 - - - - - 6947231a by Zubin Duggal at 2020-05-30T06:10:02-04:00 Simplify contexts in GHC.Iface.Ext.Ast - - - - - 2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00 Cleanup OVERWRITING_CLOSURE logic The code is just more confusing than it needs to be. We don't need to mix the threaded check with the ldv profiling check since ldv's init already checks for this. Hence they can be two separate checks. Taking the sanity checking into account is also cleaner via DebugFlags.sanity. No need for checking the DEBUG define. The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the old code had also make things a lot more opaque IMO so I removed those. - - - - - 6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00 Fix OVERWRITING_CLOSURE assuming closures are not inherently used The new ASSERT in LDV_recordDead() was being tripped up by MVars when removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via OVERWRITE_INFO(). - - - - - 38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00 Always zero shrunk mutable array slop when profiling When shrinking arrays in the profiling way we currently don't always zero the leftover slop. This means we can't traverse such closures in the heap profiler. The old Note [zeroing slop] and #8402 have some rationale for why this is so but I belive the reasoning doesn't apply to mutable closures. There users already have to ensure multiple threads don't step on each other's toes so zeroing should be safe. - - - - - b0c1f2a6 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for #18151 - - - - - 9a99a178 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for desugaring of PostfixOperators - - - - - 2b89ca5b by Ben Gamari at 2020-06-01T06:33:37-04:00 HsToCore: Eta expand left sections Strangely, the comment next to this code already alluded to the fact that even simply eta-expanding will sacrifice laziness. It's quite unclear how we regressed so far. See #18151. - - - - - d412d7a3 by Kirill Elagin at 2020-06-01T06:34:21-04:00 Winferred-safe-imports: Do not exit with error Currently, when -Winferred-safe-imports is enabled, even when it is not turned into an error, the compiler will still exit with exit code 1 if this warning was emitted. Make sure it is really treated as a warning. - - - - - f945eea5 by Ben Gamari at 2020-06-01T06:34:58-04:00 nonmoving: Optimise log2_ceil - - - - - aab606e4 by Bodigrim at 2020-06-01T06:35:36-04:00 Clarify description of fromListN - - - - - 7e5220e2 by Bodigrim at 2020-06-01T06:35:36-04:00 Apply suggestion to libraries/base/GHC/Exts.hs - - - - - f3fb1ce9 by fendor at 2020-06-01T06:36:18-04:00 Add `isInScope` check to `lintCoercion` Mirrors the behaviour of `lintType`. - - - - - 5ac4d946 by fendor at 2020-06-01T06:36:18-04:00 Lint rhs of IfaceRule - - - - - 1cef6126 by Jeremy Schlatter at 2020-06-01T06:37:00-04:00 Fix wording in documentation The duplicate "orphan instance" phrase here doesn't make sense, and was probably an accident. - - - - - 5aaf08f2 by Takenobu Tani at 2020-06-01T06:37:43-04:00 configure: Modify aclocal.m4 according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * Rename: * compiler/GHC/Parser.hs <= compiler/parser/Parser.hs * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs * Add: * compiler/GHC/Cmm/Lexer.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular - - - - - 15857ad8 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Don't fail if we can't unlink __symlink_test Afterall, it's possible we were unable to create it due to lack of symlink permission. - - - - - 4a7229ef by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Refactor ghostscript detection Tamar reported that he saw crashes due to unhandled exceptions. - - - - - 2ab37eaf by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/perf_notes: Fix ill-typed assignments - - - - - e45d5b66 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/testutil: Fix bytes/str mismatch - - - - - 7002d0cb by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Work around spurious mypy failure - - - - - 11390e3a by Takenobu Tani at 2020-06-01T06:39:05-04:00 Clean up file paths for new module hierarchy This updates comments only. This patch replaces file references according to new module hierarchy. See also: * https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular * https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 8f2e5732 by Takenobu Tani at 2020-06-01T06:39:05-04:00 Modify file paths to module paths for new module hierarchy This updates comments only. This patch replaces module references according to new module hierarchy [1][2]. For files under the `compiler/` directory, I replace them as module paths instead of file paths. For instance, `GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3]. For current and future haddock's markup, this patch encloses the module name with "" [4]. [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 [3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613 [4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules - - - - - 68b71c4a by Tom Ellis at 2020-06-01T06:39:55-04:00 Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo - - - - - 95da76c2 by Sylvain Henry at 2020-06-01T06:40:41-04:00 Hadrian: fix binary-dist target for cross-compilation - - - - - 730fcd54 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for the @-operator Since GHC diverges from the Haskell Report by allowing the user to define (@) as an infix operator, we better give a good error message when the user does so unintentionally. In general, this is rather hard to do, as some failures will be discovered only in the renamer or the type checker: x :: (Integer, Integer) x @ (a, b) = (1, 2) This patch does *not* address this general case. However, it gives much better error messages when the binding is not syntactically valid: pairs xs @ (_:xs') = zip xs xs' Before this patch, the error message was rather puzzling: <interactive>:1:1: error: Parse error in pattern: pairs After this patch, the error message includes a hint: <interactive>:1:1: error: Parse error in pattern: pairs In a function binding for the ‘@’ operator. Perhaps you meant an as-pattern, which must not be surrounded by whitespace - - - - - 0fde5377 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TypeApplications With this patch, we always parse f @t as a type application, thereby producing better error messages. This steals two syntactic forms: * Prefix form of the @-operator in expressions. Since the @-operator is a divergence from the Haskell Report anyway, this is not a major loss. * Prefix form of @-patterns. Since we are stealing loose infix form anyway, might as well sacrifice the prefix form for the sake of much better error messages. - - - - - c68e7e1e by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TemplateHaskellQuotes While [e| |], [t| |], [d| |], and so on, steal syntax from list comprehensions, [| |] and [|| ||] do not steal any syntax. Thus we can improve error messages by always accepting them in the lexer. Turns out the renamer already performs necessary validation. - - - - - 120aedbd by Ben Gamari at 2020-06-01T16:07:02-04:00 gitlab-ci: Disable use of ld.lld on ARMv7 It turns out that lld non-deterministically fails on ARMv7. I suspect this may be due to the a kernel regression as this only started happening when we upgraded to 5.4. Nevertheless, easily avoided by simply sticking with gold. Works around #18280. - - - - - d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00 gitlab-ci: Ensure that workaround for #18280 applies to bindisttest We need to ensure that the `configure` flags working around #18280 are propagated to the bindisttest `configure` as well. - - - - - cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00 gitlab-ci: Allow ARMv7 job to fail Due to #18298. - - - - - 32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00 Clean up boot vs non-boot disambiguating types We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule. - - - - - c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00 docs: Add more details on InterruptibleFFI. Details from https://gitlab.haskell.org/ghc/ghc/issues/8684 and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430 - - - - - 1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00 Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr. MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd. This regression did not make it into a release of GHC. Here, the original behavior is restored, and FinalPtr is given the same treatment as PlainPtr. - - - - - 2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00 Fix documentation on type families not being extracted It looks like the location of the Names used for CoAxioms on type families are now located at their type constructors. Previously, Docs.hs thought the Names were located in the RHS, so the RealSrcSpan in the instanceMap and getInstLoc didn't match up. Fixes #18241 - - - - - 6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00 GHC.Hs.Instances: Compile with -O0 This module contains exclusively Data instances, which are going to be slow no matter what we do. Furthermore, they are incredibly slow to compile with optimisation (see #9557). Consequently we compile this with -O0. See #18254. - - - - - c330331a by nineonine at 2020-06-04T04:37:59-04:00 Add test for #17669 - - - - - cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00 rts: Add Windows-specific implementation of rtsSleep Previously we would use the POSIX path, which uses `nanosleep`. However, it turns out that `nanosleep` is provided by `libpthread` on Windows. In general we don't want to incur such a dependency. Avoid this by simply using `Sleep` on Windows. Fixes #18272. - - - - - ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00 compiler: Disable use of process jobs with process < 1.6.9 Due to #17926. - - - - - 6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00 [linker] Adds void printLoadedObjects(void); This allows us to dump in-memory object code locations for debugging. Fixup printLoadedObjects prototype - - - - - af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00 base: fix sign confusion in log1mexp implementation (fix #17125) author: claude (https://gitlab.haskell.org/trac-claude) The correct threshold for log1mexp is -(log 2) with the current specification of log1mexp. This change improves accuracy for large negative inputs. To avoid code duplication, a small helper function is added; it isn't the default implementation in Floating because it needs Ord. This patch does nothing to address that the Haskell specification is different from that in common use in other languages. - - - - - 2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00 Simple subsumption This patch simplifies GHC to use simple subsumption. Ticket #17775 Implements GHC proposal #287 https://github.com/ghc-proposals/ghc-proposals/blob/master/ proposals/0287-simplify-subsumption.rst All the motivation is described there; I will not repeat it here. The implementation payload: * tcSubType and friends become noticably simpler, because it no longer uses eta-expansion when checking subsumption. * No deeplyInstantiate or deeplySkolemise That in turn means that some tests fail, by design; they can all be fixed by eta expansion. There is a list of such changes below. Implementing the patch led me into a variety of sticky corners, so the patch includes several othe changes, some quite significant: * I made String wired-in, so that "foo" :: String rather than "foo" :: [Char] This improves error messages, and fixes #15679 * The pattern match checker relies on knowing about in-scope equality constraints, andd adds them to the desugarer's environment using addTyCsDs. But the co_fn in a FunBind was missed, and for some reason simple-subsumption ends up with dictionaries there. So I added a call to addTyCsDs. This is really part of #18049. * I moved the ic_telescope field out of Implication and into ForAllSkol instead. This is a nice win; just expresses the code much better. * There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader. We called checkDataKindSig inside tc_kind_sig, /before/ solveEqualities and zonking. Obviously wrong, easily fixed. * solveLocalEqualitiesX: there was a whole mess in here, around failing fast enough. I discovered a bad latent bug where we could successfully kind-check a type signature, and use it, but have unsolved constraints that could fill in coercion holes in that signature -- aargh. It's all explained in Note [Failure in local type signatures] in GHC.Tc.Solver. Much better now. * I fixed a serious bug in anonymous type holes. IN f :: Int -> (forall a. a -> _) -> Int that "_" should be a unification variable at the /outer/ level; it cannot be instantiated to 'a'. This was plain wrong. New fields mode_lvl and mode_holes in TcTyMode, and auxiliary data type GHC.Tc.Gen.HsType.HoleMode. This fixes #16292, but makes no progress towards the more ambitious #16082 * I got sucked into an enormous refactoring of the reporting of equality errors in GHC.Tc.Errors, especially in mkEqErr1 mkTyVarEqErr misMatchMsg misMatchMsgOrCND In particular, the very tricky mkExpectedActualMsg function is gone. It took me a full day. But the result is far easier to understand. (Still not easy!) This led to various minor improvements in error output, and an enormous number of test-case error wibbles. One particular point: for occurs-check errors I now just say Can't match 'a' against '[a]' rather than using the intimidating language of "occurs check". * Pretty-printing AbsBinds Tests review * Eta expansions T11305: one eta expansion T12082: one eta expansion (undefined) T13585a: one eta expansion T3102: one eta expansion T3692: two eta expansions (tricky) T2239: two eta expansions T16473: one eta determ004: two eta expansions (undefined) annfail06: two eta (undefined) T17923: four eta expansions (a strange program indeed!) tcrun035: one eta expansion * Ambiguity check at higher rank. Now that we have simple subsumption, a type like f :: (forall a. Eq a => Int) -> Int is no longer ambiguous, because we could write g :: (forall a. Eq a => Int) -> Int g = f and it'd typecheck just fine. But f's type is a bit suspicious, and we might want to consider making the ambiguity check do a check on each sub-term. Meanwhile, these tests are accepted, whereas they were previously rejected as ambiguous: T7220a T15438 T10503 T9222 * Some more interesting error message wibbles T13381: Fine: one error (Int ~ Exp Int) rather than two (Int ~ Exp Int, Exp Int ~ Int) T9834: Small change in error (improvement) T10619: Improved T2414: Small change, due to order of unification, fine T2534: A very simple case in which a change of unification order means we get tow unsolved constraints instead of one tc211: bizarre impredicative tests; just accept this for now Updates Cabal and haddock submodules. Metric Increase: T12150 T12234 T5837 haddock.base Metric Decrease: haddock.compiler haddock.Cabal haddock.base Merge note: This appears to break the `UnliftedNewtypesDifficultUnification` test. It has been marked as broken in the interest of merging. (cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5) - - - - - 2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00 Simplify bindLHsTyVarBndrs and bindHsQTyVars Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate `Maybe` arguments, which I find terribly confusing. Thankfully, it's possible to remove one `Maybe` argument from each of these functions, which this patch accomplishes: * `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if GHC should warn about any of the quantified type variables going unused. However, every call site uses `Nothing` in practice. This makes sense, since it doesn't really make sense to warn about unused type variables bound by an `LHsQTyVars`. For instance, you wouldn't warn about the `a` in `data Proxy a = Proxy` going unused. As a result, I simply remove this `Maybe SDoc` argument altogether. * `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same reasons that `bindHsQTyVars` took one. To make things more confusing, however, `bindLHsTyVarBndrs` also takes a separate `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in warnings and error messages. In practice, the `Maybe SDoc` and the `HsDocContext` often contain the same text. See the call sites for `bindLHsTyVarBndrs` in `rnFamInstEqn` and `rnConDecl`, for instance. There are only a handful of call sites where the text differs between the `Maybe SDoc` and `HsDocContext` arguments: * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`" and the `HsDocContext` says "`In the transformation rule`". * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says "`In the type`" but the `HsDocContext` is inhereted from the surrounding context (e.g., if `rnHsTyKi` were called on a top-level type signature, the `HsDocContext` would be "`In the type signature`" instead) In both cases, warnings/error messages arguably _improve_ by unifying making the `Maybe SDoc`'s text match that of the `HsDocContext`. As a result, I decided to remove the `Maybe SDoc` argument to `bindLHsTyVarBndrs` entirely and simply reuse the text from the `HsDocContext`. (I decided to change the phrase "transformation rule" to "rewrite rule" while I was in the area.) The `Maybe SDoc` argument has one other purpose: signaling when to emit "`Unused quantified type variable`" warnings. To recover this functionality, I replaced the `Maybe SDoc` argument with a boolean-like `WarnUnusedForalls` argument. The only `bindLHsTyVarBndrs` call site that chooses _not_ to emit these warnings in `bindHsQTyVars`. - - - - - e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00 hadrian: Add missing deriveConstants dependency on ghcplatform.h deriveConstants wants to compile C sources which #include PosixSource.h, which itself #includes ghcplatform.h. Make sure that Hadrian knows about this dependency. Fixes #18290. - - - - - b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00 ghc-prim needs to depend on libc and libm libm is just an empty shell on musl, and all the math functions are contained in libc. - - - - - 6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00 Disable DLL loading if without system linker Some platforms (musl, aarch64) do not have a working dynamic linker implemented in the libc, even though we might see dlopen. It will ultimately just return that this is not supported. Hence we'll add a flag to the compiler to flat our disable loading dlls. This is needed as we will otherwise try to load the shared library even if this will subsequently fail. At that point we have given up looking for static options though. - - - - - 4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00 Range is actually +/-2^32, not +/-2^31 See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf - - - - - f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00 OccurAnal: Avoid exponential behavior due to where clauses Previously the `Var` case of `occAnalApp` could in some cases (namely in the case of `runRW#` applications) call `occAnalRhs` two. In the case of nested `runRW#`s this results in exponential complexity. In some cases the compilation time that resulted would be very long indeed (see #18296). Fixes #18296. Metric Decrease: T9961 T12150 T12234 - - - - - 9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00 Add link to GHC's wiki in the GHC API header This adds a URL to point to GHC's wiki in the GHC API header. Newcomers could easily find more information from the GHC API's web like [1]. [1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html [skip ci] - - - - - 72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00 Make GADT constructors adhere to the forall-or-nothing rule properly Issue #18191 revealed that the types of GADT constructors don't quite adhere to the `forall`-or-nothing rule. This patch serves to clean up this sad state of affairs somewhat. The main change is not in the code itself, but in the documentation, as this patch introduces two sections to the GHC User's Guide: * A "Formal syntax for GADTs" section that presents a BNF-style grammar for what is and isn't allowed in GADT constructor types. This mostly exists to codify GHC's existing behavior, but it also imposes a new restriction that addresses #18191: the outermost `forall` and/or context in a GADT constructor is not allowed to be surrounded by parentheses. Doing so would make these `forall`s/contexts nested, and GADTs do not support nested `forall`s/contexts at present. * A "`forall`-or-nothing rule" section that describes exactly what the `forall`-or-nothing rule is all about. Surprisingly, there was no mention of this anywhere in the User's Guide up until now! To adhere the new specification in the "Formal syntax for GADTs" section of the User's Guide, the following code changes were made: * A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced. This is very much like `splitLHsSigmaTy`, except that it avoids splitting apart any parentheses, which can be syntactically significant for GADT types. See `Note [No nested foralls or contexts in GADT constructors]` in `GHC.Hs.Type`. * `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return it when given a prefix GADT constructor. Unlike `ConDeclGADT`, `ConDeclGADTPrefixPs` does not split the GADT type into its argument and result types, as this cannot be done until after the type is renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why this is the case). * `GHC.Renamer.Module.rnConDecl` now has an additional case for `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into its `forall`s, context, argument types, and result type, and (2) checks for nested `forall`s/contexts. Step (2) used to be performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather than the renamer, but now the relevant code from the typechecker can simply be deleted. One nice side effect of this change is that we are able to give a more accurate error message for GADT constructors that use visible dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`), which improves the stderr in the `T16326_Fail6` test case. Fixes #18191. Bumps the Haddock submodule. - - - - - a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00 Always use rnImplicitBndrs to bring implicit tyvars into scope This implements a first step towards #16762 by changing the renamer to always use `rnImplicitBndrs` to bring implicitly bound type variables into scope. The main change is in `rnFamInstEqn` and `bindHsQTyVars`, which previously used _ad hoc_ methods of binding their implicit tyvars. There are a number of knock-on consequences: * One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding mechanism was to give more precise source locations in `-Wunused-type-patterns` warnings. (See https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an example of this.) However, these warnings are actually a little _too_ precise, since implicitly bound type variables don't have exact binding sites like explicitly bound type variables do. A similar problem existed for "`Different names for the same type variable`" errors involving implicit tyvars bound by `bindHsQTyVars`. Therefore, we simply accept the less precise (but more accurate) source locations from `rnImplicitBndrs` in `rnFamInstEqn` and `bindHsQTyVars`. See `Note [Source locations for implicitly bound type variables]` in `GHC.Rename.HsType` for the full story. * In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs to be able to look up names from the parent class (in the event that we are renaming an associated type family instance). As a result, `rnImplicitBndrs` now takes an argument of type `Maybe assoc`, which is `Just` in the event that a type family instance is associated with a class. * Previously, GHC kept track of three type synonyms for free type variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups` (which are allowed to contain duplicates), and `FreeKiTyVarsNoDups` (which contain no duplicates). However, making is a distinction between `-Dups` and `-NoDups` is now pointless, as all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually end up being passed to `rnImplicitBndrs`, which removes duplicates. As a result, I decided to just get rid of `FreeKiTyVarsDups` and `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`. * The `bindLRdrNames` and `deleteBys` functions are now dead code, so I took the liberty of removing them. - - - - - 24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00 Clarify leaf module names for new module hierarchy This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00 rts: Remove unused GET_ENTRY closure macro This macro is not used and got broken in the meantime, as ENTRY_CODE was deleted. - - - - - 87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00 Fix -fkeep-cafs flag name in users guide - - - - - ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00 Expose impliedGFlags, impledOffGFlags, impliedXFlags - - - - - 7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00 Cross-module LambdaFormInfo passing - Store LambdaFormInfos of exported Ids in interface files - Use them in importing modules This is for optimization purposes: if we know LambdaFormInfo of imported Ids we can generate more efficient calling code, see `getCallMethod`. Exporting (putting them in interface files or in ModDetails) and importing (reading them from interface files) are both optional. We don't assume known LambdaFormInfos anywhere and do not change how we call Ids with unknown LambdaFormInfos. Runtime, allocation, and residency numbers when building Cabal-the-library (commit 0d4ee7ba3): (Log and .hp files are in the MR: !2842) | | GHC HEAD | This patch | Diff | |-----|----------|------------|----------------| | -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% | | -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% | | -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% | | | GHC HEAD | This patch | Diff | |-----|-----------------|-----------------|----------------------------| | -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% | | -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% | | -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% | NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively turn all GCs into major GCs, and do GC more often. | | GHC HEAD | This patch | Diff | |-----|----------------------------|------------------------------|----------------------------| | -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% | | -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% | | -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% | NoFib results: -------------------------------------------------------------------------------- Program Size Allocs Instrs Reads Writes -------------------------------------------------------------------------------- CS 0.0% 0.0% +0.0% +0.0% +0.0% CSD 0.0% 0.0% 0.0% +0.0% +0.0% FS 0.0% 0.0% +0.0% +0.0% +0.0% S 0.0% 0.0% +0.0% +0.0% +0.0% VS 0.0% 0.0% +0.0% +0.0% +0.0% VSD 0.0% 0.0% +0.0% +0.0% +0.1% VSM 0.0% 0.0% +0.0% +0.0% +0.0% anna 0.0% 0.0% -0.3% -0.8% -0.0% ansi 0.0% 0.0% -0.0% -0.0% 0.0% atom 0.0% 0.0% -0.0% -0.0% 0.0% awards 0.0% 0.0% -0.1% -0.3% 0.0% banner 0.0% 0.0% -0.0% -0.0% -0.0% bernouilli 0.0% 0.0% -0.0% -0.0% -0.0% binary-trees 0.0% 0.0% -0.0% -0.0% +0.0% boyer 0.0% 0.0% -0.0% -0.0% 0.0% boyer2 0.0% 0.0% -0.0% -0.0% 0.0% bspt 0.0% 0.0% -0.0% -0.2% 0.0% cacheprof 0.0% 0.0% -0.1% -0.4% +0.0% calendar 0.0% 0.0% -0.0% -0.0% 0.0% cichelli 0.0% 0.0% -0.9% -2.4% 0.0% circsim 0.0% 0.0% -0.0% -0.0% 0.0% clausify 0.0% 0.0% -0.1% -0.3% 0.0% comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0% compress 0.0% 0.0% -0.0% -0.0% -0.0% compress2 0.0% 0.0% -0.0% -0.0% 0.0% constraints 0.0% 0.0% -0.1% -0.2% -0.0% cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0% cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0% cse 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0% dom-lt 0.0% 0.0% -0.1% -0.2% 0.0% eliza 0.0% 0.0% -0.5% -1.5% 0.0% event 0.0% 0.0% -0.0% -0.0% -0.0% exact-reals 0.0% 0.0% -0.1% -0.3% +0.0% exp3_8 0.0% 0.0% -0.0% -0.0% -0.0% expert 0.0% 0.0% -0.3% -1.0% -0.0% fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0% fasta 0.0% 0.0% -0.0% -0.0% +0.0% fem 0.0% 0.0% -0.0% -0.0% 0.0% fft 0.0% 0.0% -0.0% -0.0% 0.0% fft2 0.0% 0.0% -0.0% -0.0% 0.0% fibheaps 0.0% 0.0% -0.0% -0.0% +0.0% fish 0.0% 0.0% 0.0% -0.0% +0.0% fluid 0.0% 0.0% -0.4% -1.2% +0.0% fulsom 0.0% 0.0% -0.0% -0.0% 0.0% gamteb 0.0% 0.0% -0.1% -0.3% 0.0% gcd 0.0% 0.0% -0.0% -0.0% 0.0% gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0% genfft 0.0% 0.0% -0.0% -0.0% 0.0% gg 0.0% 0.0% -0.0% -0.0% +0.0% grep 0.0% 0.0% -0.0% -0.0% -0.0% hidden 0.0% 0.0% -0.1% -0.4% -0.0% hpg 0.0% 0.0% -0.2% -0.5% +0.0% ida 0.0% 0.0% -0.0% -0.0% +0.0% infer 0.0% 0.0% -0.3% -0.8% -0.0% integer 0.0% 0.0% -0.0% -0.0% +0.0% integrate 0.0% 0.0% -0.0% -0.0% 0.0% k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0% kahan 0.0% 0.0% -0.0% -0.0% +0.0% knights 0.0% 0.0% -2.2% -5.4% 0.0% lambda 0.0% 0.0% -0.6% -1.8% 0.0% last-piece 0.0% 0.0% -0.0% -0.0% 0.0% lcss 0.0% 0.0% -0.0% -0.1% 0.0% life 0.0% 0.0% -0.0% -0.1% 0.0% lift 0.0% 0.0% -0.2% -0.6% +0.0% linear 0.0% 0.0% -0.0% -0.0% -0.0% listcompr 0.0% 0.0% -0.0% -0.0% 0.0% listcopy 0.0% 0.0% -0.0% -0.0% 0.0% maillist 0.0% 0.0% -0.1% -0.3% +0.0% mandel 0.0% 0.0% -0.0% -0.0% 0.0% mandel2 0.0% 0.0% -0.0% -0.0% -0.0% mate +0.0% 0.0% -0.0% -0.0% -0.0% minimax 0.0% 0.0% -0.2% -1.0% 0.0% mkhprog 0.0% 0.0% -0.1% -0.2% -0.0% multiplier 0.0% 0.0% -0.0% -0.0% -0.0% n-body 0.0% 0.0% -0.0% -0.0% +0.0% nucleic2 0.0% 0.0% -0.1% -0.2% 0.0% para 0.0% 0.0% -0.0% -0.0% -0.0% paraffins 0.0% 0.0% -0.0% -0.0% 0.0% parser 0.0% 0.0% -0.2% -0.7% 0.0% parstof 0.0% 0.0% -0.0% -0.0% +0.0% pic 0.0% 0.0% -0.0% -0.0% 0.0% pidigits 0.0% 0.0% +0.0% +0.0% +0.0% power 0.0% 0.0% -0.2% -0.6% +0.0% pretty 0.0% 0.0% -0.0% -0.0% -0.0% primes 0.0% 0.0% -0.0% -0.0% 0.0% primetest 0.0% 0.0% -0.0% -0.0% -0.0% prolog 0.0% 0.0% -0.3% -1.1% 0.0% puzzle 0.0% 0.0% -0.0% -0.0% 0.0% queens 0.0% 0.0% -0.0% -0.0% +0.0% reptile 0.0% 0.0% -0.0% -0.0% 0.0% reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0% rewrite 0.0% 0.0% -0.7% -2.5% -0.0% rfib 0.0% 0.0% -0.0% -0.0% 0.0% rsa 0.0% 0.0% -0.0% -0.0% 0.0% scc 0.0% 0.0% -0.1% -0.2% -0.0% sched 0.0% 0.0% -0.0% -0.0% -0.0% scs 0.0% 0.0% -1.0% -2.6% +0.0% simple 0.0% 0.0% +0.0% -0.0% +0.0% solid 0.0% 0.0% -0.0% -0.0% 0.0% sorting 0.0% 0.0% -0.6% -1.6% 0.0% spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0% sphere 0.0% 0.0% -0.0% -0.0% -0.0% symalg 0.0% 0.0% -0.0% -0.0% +0.0% tak 0.0% 0.0% -0.0% -0.0% 0.0% transform 0.0% 0.0% -0.0% -0.0% 0.0% treejoin 0.0% 0.0% -0.0% -0.0% 0.0% typecheck 0.0% 0.0% -0.0% -0.0% +0.0% veritas +0.0% 0.0% -0.2% -0.4% +0.0% wang 0.0% 0.0% -0.0% -0.0% 0.0% wave4main 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0% x2n1 0.0% 0.0% -0.0% -0.0% -0.0% -------------------------------------------------------------------------------- Min 0.0% 0.0% -2.2% -5.4% -0.0% Max +0.0% 0.0% +0.0% +0.0% +0.1% Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0% Metric increases micro benchmarks tracked in #17686: Metric Increase: T12150 T12234 T12425 T13035 T5837 T6048 T9233 Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00 Give Language a Bounded instance - - - - - 9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Optimisation in Unique.Supply This patch switches on -fno-state-hack in GHC.Types.Unique.Supply. It turned out that my fixes for #18078 (coercion floating) changed the optimisation pathway for mkSplitUniqSupply in such a way that we had an extra allocation inside the inner loop. Adding -fno-state-hack fixed that -- and indeed the loop in mkSplitUniqSupply is a classic example of the way in which -fno-state-hack can be bad; see #18238. Moreover, the new code is better than the old. They allocate the same, but the old code ends up with a partial application. The net effect is that the test perf/should_run/UniqLoop runs 20% faster! From 2.5s down to 2.0s. The allocation numbers are the same -- but elapsed time falls. Good! The bad thing about this is that it's terribly delicate. But at least it's a good example of such delicacy in action. There is a long Note [Optimising the unique supply] which now explains all this. - - - - - 6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Implement cast worker/wrapper properly The cast worker/wrapper transformation transforms x = e |> co into y = e x = y |> co This is done by the simplifier, but we were being careless about transferring IdInfo from x to y, and about what to do if x is a NOINLNE function. This resulted in a series of bugs: #17673, #18093, #18078. This patch fixes all that: * Main change is in GHC.Core.Opt.Simplify, and the new prepareBinding function, which does this cast worker/wrapper transform. See Note [Cast worker/wrappers]. * There is quite a bit of refactoring around prepareRhs, makeTrivial etc. It's nicer now. * Some wrappers from strictness and cast w/w, notably those for a function with a NOINLINE, should inline very late. There wasn't really a mechanism for that, which was an existing bug really; so I invented a new finalPhase = Phase (-1). It's used for all simplifier runs after the user-visible phase 2,1,0 have run. (No new runs of the simplifier are introduced thereby.) See new Note [Compiler phases] in GHC.Types.Basic; the main changes are in GHC.Core.Opt.Driver * Doing this made me trip over two places where the AnonArgFlag on a FunTy was being lost so we could end up with (Num a -> ty) rather than (Num a => ty) - In coercionLKind/coercionRKind - In contHoleType in the Simplifier I fixed the former by defining mkFunctionType and using it in coercionLKind/RKind. I could have done the same for the latter, but the information is almost to hand. So I fixed the latter by - adding sc_hole_ty to ApplyToVal (like ApplyToTy), - adding as_hole_ty to ValArg (like TyArg) - adding sc_fun_ty to StrictArg Turned out I could then remove ai_type from ArgInfo. This is just moving the deck chairs around, but it worked out nicely. See the new Note [AnonArgFlag] in GHC.Types.Var * When looking at the 'arity decrease' thing (#18093) I discovered that stable unfoldings had a much lower arity than the actual optimised function. That's what led to the arity-decrease message. Simple solution: eta-expand. It's described in Note [Eta-expand stable unfoldings] in GHC.Core.Opt.Simplify * I also discovered that unsafeCoerce wasn't being inlined if the context was boring. So (\x. f (unsafeCoerce x)) would create a thunk -- yikes! I fixed that by making inlineBoringOK a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold. I also found that unsafeCoerceName was unused, so I removed it. I made a test case for #18078, and a very similar one for #17673. The net effect of all this on nofib is very modest, but positive: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.4% -0.1% -3.1% -3.1% 0.0% fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0% maillist -0.4% -0.1% -7.8% -1.0% -14.3% primetest -0.4% -15.6% -7.1% -6.6% 0.0% -------------------------------------------------------------------------------- Min -0.9% -15.6% -13.3% -14.2% -14.3% Max -0.3% 0.0% +12.1% +12.4% 0.0% Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1% All following metric decreases are compile-time allocation decreases between -1% and -3%: Metric Decrease: T5631 T13701 T14697 T15164 - - - - - 32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00 Fix lookupGlobalOccRn_maybe sometimes reporting an error In some cases it was possible for lookupGlobalOccRn_maybe to return an error, when it should be returning a Nothing. If it called lookupExactOcc_either when there were no matching GlobalRdrElts in the otherwise case, it would return an error message. This could be caused when lookupThName_maybe in Template Haskell was looking in different namespaces (thRdrNameGuesses), guessing different namespaces that the name wasn't guaranteed to be found in. However, by addressing this some more accurate errors were being lost in the conversion to Maybes. So some of the lookup* functions have been shuffled about so that errors should always be ignored in lookup*_maybes, and propagated otherwise. This fixes #18263 - - - - - 9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00 Initialize the allocation counter in GHCi to 0 (Fixes #16012) According to the documentation for the function `getAllocationCounter` in [System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html) initialize the allocationCounter also in GHCi to 0. - - - - - 8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00 test: fix conc038 We had spurious failures of conc038 test on CI with stdout: ``` newThread started -mainThread -Haskell: 2 newThread back again +mainThread 1 sec later shutting down +Haskell: 2 ``` - - - - - 4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00 Release Notes: Add news from the pattern-match checker [skip ci] - - - - - 3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00 Only test T16190 with the NCG T16190 is meant to test a NCG feature. It has already caused spurious failures in other MRs (e.g. !2165) when LLVM is used. - - - - - 2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00 DynFlags refactoring VIII (#17957) * Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.* * Add LlvmOpts datatype to store Llvm backend options * Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and Llvm.MetaExpr) which require LlvmOpts. * Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`) - - - - - 7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove unused code - - - - - 72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor homeUnit * rename thisPackage into homeUnit * document and refactor several Backpack things - - - - - 8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Rename unsafeGetUnitInfo into unsafeLookupUnit - - - - - f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Add allowVirtualUnits field in PackageState Instead of always querying DynFlags to know whether we are allowed to use virtual units (i.e. instantiated on-the-fly, cf Note [About units] in GHC.Unit), we store it once for all in `PackageState.allowVirtualUnits`. This avoids using DynFlags too much (cf #17957) and is preliminary work for #14335. - - - - - e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Enhance UnitId use * use UnitId instead of String to identify wired-in units * use UnitId instead of Unit in the backend (Unit are only use by Backpack to produce type-checked interfaces, not real code) * rename lookup functions for consistency * documentation - - - - - 9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove LinkerUnitId type alias - - - - - d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor WiredMap * Remove WiredInUnitId and WiredUnitId type aliases - - - - - 3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document and refactor `mkUnit` and `mkUnitInfoMap` - - - - - d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove PreloadUnitId type alias - - - - - f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename listUnitInfoMap into listUnitInfo There is no Map involved - - - - - ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc. - - - - - 202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Make ClosureUnitInfoMap uses UnitInfoMap - - - - - 55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove ClosureUnitInfoMap - - - - - 653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit (2) * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc. - - - - - ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move dump_mod_map into initUnits - - - - - 598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move wiring of homeUnitInstantiations outside of mkUnitState - - - - - 437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00 Avoid timing module map dump in initUnits - - - - - 9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove preload parameter of mkUnitState * Remove preload parameter (unused) * Don't explicitly return preloaded units: redundant because already returned as "preloadUnits" field of UnitState - - - - - 266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: refactor unwireUnit - - - - - 9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document getPreloadUnitsAnd - - - - - bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: remove useless add_package parameter - - - - - 36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: make listVisibleModuleNames take a UnitState - - - - - 5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document add_package - - - - - 4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document closeUnitDeps - - - - - 42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: findWiredInUnits - - - - - a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: reportCycles, reportUnusable - - - - - 8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: merge_databases - - - - - fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: add UnitConfig datatype Avoid directly querying flags from DynFlags to build the UnitState. Instead go via UnitConfig so that we could reuse this to make another UnitState for plugins. - - - - - 4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move distrustAll into mkUnitState - - - - - 28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Create helper upd_wired_in_home_instantiations - - - - - ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Put database cache in UnitConfig - - - - - bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00 Don't return preload units when we set DyNFlags Preload units can be retrieved in UnitState when needed (i.e. in GHCi) - - - - - 1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 NCGConfig: remove useless ncgUnitId field - - - - - c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Doc: fix some comments - - - - - 456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Bump haddock submodule and allow metric decrease Metric Decrease: T12150 T12234 T5837 Metric Increase: T16190 - - - - - 42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00 Trim the demand for recursive product types Ticket #18304 showed that we need to be very careful when exploring the demand (esp usage demand) on recursive product types. This patch solves the problem by trimming the demand on such types -- in effect, a form of "widening". See the Note [Trimming a demand to a type] in DmdAnal, which explains how I did this by piggy-backing on an existing mechansim for trimming demands becuase of GADTs. The significant payload of this patch is very small indeed: * Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to avoid looking through recursive types. But on the way * I found that ae_rec_tc was entirely inoperative and did nothing. So I removed it altogether from DmdAnal. * I moved some code around in DmdAnal and Demand. (There are no actual changes in dmdFix.) * I changed the API of DmsAnal.dmdAnalRhsLetDown to return a StrictSig rather than a decorated Id * I removed the dead function peelTsFuns from Demand Performance effects: Nofib: 0.0% changes. Not surprising, because they don't use recursive products Perf tests T12227: 1% increase in compiler allocation, becuase $cto gets w/w'd. It did not w/w before because it takes a deeply nested argument, so the worker gets too many args, so we abandon w/w altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough) With this patch we trim the demands. That is not strictly necessary (since these Generic type constructors are like tuples -- they can't cause a loop) but the net result is that we now w/w $cto which is fine. UniqLoop: 16% decrease in /runtime/ allocation. The UniqSupply is a recursive product, so currently we abandon all strictness on 'churn'. With this patch 'churn' gets useful strictness, and we w/w it. Hooray Metric Decrease: UniqLoop Metric Increase: T12227 - - - - - 87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00 Add introductory prose for Data.Traversable - - - - - 9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00 Fix #12073: Add MonadFix Q instance - - - - - 220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00 testsuite: Increase size of T12150 As noted in #18319, this test was previously very fragile. Increase its size to make it more likely that its fails with its newly-increased acceptance threshold. Metric Increase: T12150 - - - - - 8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00 gitlab-ci: Always push perf notes Previously we ci.sh would run with `set -e` implying that we wouldn't push perf notes if the testsuite were to fail, even if it *only* failed due to perf notes. This rendered the whole performance testing story quite fragile as a single regressing commit would cause every successive commit to fail since a new baseline would not be uploaded. Fix this by ensuring that we always push performance notes. - - - - - 7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00 gitlab-ci: Eliminate redundant push of CI metrics - - - - - a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00 Use HsForAllTelescope to avoid inferred, visible foralls Currently, `HsForAllTy` permits the combination of `ForallVis` and `Inferred`, but you can't actually typecheck code that uses it (e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a new `HsForAllTelescope` data type that makes a type-level distinction between visible and invisible `forall`s such that visible `forall`s do not track `Specificity`. That part of the patch is actually quite small; the rest is simply changing consumers of `HsType` to accommodate this new type. Fixes #18235. Bumps the `haddock` submodule. - - - - - c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00 winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges. The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00 codeGen: Don't discard live case binders in unsafeEqualityProof logic Previously CoreToStg would unconditionally discard cases of the form: case unsafeEqualityProof of wild { _ -> rhs } and rather replace the whole thing with `rhs`. However, in some cases (see #18227) the case binder is still live, resulting in unbound occurrences in `rhs`. Fix this by only discarding the case if the case binder is dead. Fixes #18227. - - - - - e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00 testsuite: Add tests for #18227 T18227A is the original issue which gave rise to the ticket and depends upon bytestring. T18227B is a minimized reproducer. - - - - - 8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Fix rts include and library paths Fixes two bugs: * (?) and (<>) associated in a surprising way * We neglected to include libdw paths in the rts configure flags - - - - - bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Drop redundant GHC arguments Cabal should already be passing this arguments to GHC. - - - - - 01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00 FFI: Fix pass small ints in foreign call wrappers The Haskell calling convention requires integer parameters smaller than wordsize to be promoted to wordsize (where the upper bits are don't care). To access such small integer parameter read a word from the parameter array and then cast that word to the small integer target type. Fixes #15933 - - - - - 502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00 Fix "ndecreasingIndentation" in manual (#18116) - - - - - 9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00 Use foldl' in unionManyUniqDSets - - - - - 761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00 Load .lo as well. Some archives contain so called linker objects, with the affectionate .lo suffic. For example the musl libc.a will come in that form. We still want to load those objects, hence we should not discard them and look for .lo as well. Ultimately we might want to fix this proerly by looking at the file magic. - - - - - cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00 User's Guide: KnownNat evidence is Natural This bit of documentation got outdated after commit 1fcede43d2b30f33b7505e25eb6b1f321be0407f - - - - - d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00 Fix typos and formatting in user guide - - - - - 56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00 Resolve TODO - - - - - 3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00 Rename TcHoleErrors to GHC.Tc.Errors.Hole - - - - - d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00 hadrian: Build with threaded runtime if available See #16873. - - - - - 0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00 T16190: only measure bytes_allocated Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics fluctuate by 13%. - - - - - 4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00 docs: fix formatting in users guide - - - - - eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00 Move CLabel assertions into smart constructors (#17957) It avoids using DynFlags in the Outputable instance of Clabel to check assertions at pretty-printing time. - - - - - 7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00 base: Bump to 4.15.0.0 - - - - - 20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00 configure: Use grep -q instead of --quiet The latter is apparently not supported by busybox. - - - - - 40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00 Linear types (#15981) This is the first step towards implementation of the linear types proposal (https://github.com/ghc-proposals/ghc-proposals/pull/111). It features * A language extension -XLinearTypes * Syntax for linear functions in the surface language * Linearity checking in Core Lint, enabled with -dlinear-core-lint * Core-to-core passes are mostly compatible with linearity * Fields in a data type can be linear or unrestricted; linear fields have multiplicity-polymorphic constructors. If -XLinearTypes is disabled, the GADT syntax defaults to linear fields The following items are not yet supported: * a # m -> b syntax (only prefix FUN is supported for now) * Full multiplicity inference (multiplicities are really only checked) * Decent linearity error messages * Linear let, where, and case expressions in the surface language (each of these currently introduce the unrestricted variant) * Multiplicity-parametric fields * Syntax for annotating lambda-bound or let-bound with a multiplicity * Syntax for non-linear/multiple-field-multiplicity records * Linear projections for records with a single linear field * Linear pattern synonyms * Multiplicity coercions (test LinearPolyType) A high-level description can be found at https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation Following the link above you will find a description of the changes made to Core. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Matthew Pickering * Arnaud Spiwack With contributions from: * Mark Barbone * Alexander Vershilov Updates haddock submodule. - - - - - 6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00 Various performance improvements This implements several general performance improvements to GHC, to offset the effect of the linear types change. General optimisations: - Add a `coreFullView` function which iterates `coreView` on the head. This avoids making function recursive solely because the iterate `coreView` themselves. As a consequence, this functions can be inlined, and trigger case-of-known constructor (_e.g._ `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`, `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`, `tyConAppTyCon_maybe`). The common pattern about all these functions is that they are almost always used as views, and immediately consumed by a case expression. This commit also mark them asx `INLINE`. - In `subst_ty` add a special case for nullary `TyConApp`, which avoid allocations altogether. - Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This required quite a bit of module shuffling. case. `myTyConApp` enforces crucial sharing, which was lost during substitution. See also !2952 . - Make `subst_ty` stricter. - In `eqType` (specifically, in `nonDetCmpType`), add a special case, tested first, for the very common case of nullary `TyConApp`. `nonDetCmpType` has been made `INLINE` otherwise it is actually a regression. This is similar to the optimisations in !2952. Linear-type specific optimisations: - Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in the definition of the pattern synonyms `One` and `Many`. - Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`: `Multiplicity` now import `Type` normally, rather than from the `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the `One` and `Many` pattern synonyms. - Make `updateIdTypeAndMult` strict in its type and multiplicity - The `scaleIdBy` gets a specialised definition rather than being an alias to `scaleVarBy` - `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type, Type)` instead of `Type -> Maybe (Scaled Type, Type)` - Remove the `MultMul` pattern synonym in favour of a view `isMultMul` because pattern synonyms appear not to inline well. - in `eqType`, in a `FunTy`, compare multiplicities last: they are almost always both `Many`, so it helps failing faster. - Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the instances of `TyConApp ManyDataConTy []` are physically the same. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Arnaud Spiwack Metric Decrease: haddock.base T12227 T12545 T12990 T1969 T3064 T5030 T9872b Metric Increase: haddock.base haddock.Cabal haddock.compiler T12150 T12234 T12425 T12707 T13035 T13056 T15164 T16190 T18304 T1969 T3064 T3294 T5631 T5642 T5837 T6048 T9020 T9233 T9675 T9872a T9961 WWRec - - - - - 57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Remove integer-simple integer-simple uses lists of words (`[Word]`) to represent big numbers instead of ByteArray#: * it is less efficient than the newer ghc-bignum native backend * it isn't compatible with the big number representation that is now shared by all the ghc-bignum backends (based on the one that was used only in integer-gmp before). As a consequence, we simply drop integer-simple - - - - - 9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00 ghc-bignum library ghc-bignum is a newer package that aims to replace the legacy integer-simple and integer-gmp packages. * it supports several backends. In particular GMP is still supported and most of the code from integer-gmp has been merged in the "gmp" backend. * the pure Haskell "native" backend is new and is much faster than the previous pure Haskell implementation provided by integer-simple * new backends are easier to write because they only have to provide a few well defined functions. All the other code is common to all backends. In particular they all share the efficient small/big number distinction previously used only in integer-gmp. * backends can all be tested against the "native" backend with a simple Cabal flag. Backends are only allowed to differ in performance, their results should be the same. * Add `integer-gmp` compat package: provide some pattern synonyms and function aliases for those in `ghc-bignum`. It is intended to avoid breaking packages that depend on `integer-gmp` internals. Update submodules: text, bytestring Metric Decrease: Conversions ManyAlternatives ManyConstructors Naperian T10359 T10547 T10678 T12150 T12227 T12234 T12425 T13035 T13719 T14936 T1969 T4801 T4830 T5237 T5549 T5837 T8766 T9020 parsing001 space_leak_001 T16190 haddock.base On ARM and i386, T17499 regresses (+6% > 5%). On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%). Metric Increase: T17499 T13701 - - - - - 96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update compiler Thanks to ghc-bignum, the compiler can be simplified: * Types and constructors of Integer and Natural can be wired-in. It means that we don't have to query them from interfaces. It also means that numeric literals don't have to carry their type with them. * The same code is used whatever ghc-bignum backend is enabled. In particular, conversion of bignum literals into final Core expressions is now much more straightforward. Bignum closure inspection too. * GHC itself doesn't depend on any integer-* package anymore * The `integerLibrary` setting is gone. - - - - - 0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `base` package * GHC.Natural isn't implemented in `base` anymore. It is provided by ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural primitives in `base` without fearing issues with built-in rewrite rules (cf #15286) * `base` doesn't conditionally depend on an integer-* package anymore, it depends on ghc-bignum * Some duplicated code in integer-* can now be factored in GHC.Float * ghc-bignum tries to use a uniform naming convention so most of the other changes are renaming - - - - - aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `make` based build system * replace integer-* package selection with ghc-bignum backend selection - - - - - f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update testsuite * support detection of slow ghc-bignum backend (to replace the detection of integer-simple use). There are still some test cases that the native backend doesn't handle efficiently enough. * remove tests for GMP only functions that have been removed from ghc-bignum * fix test results showing dependent packages (e.g. integer-gmp) or showing suggested instances * fix test using Integer/Natural API or showing internal names - - - - - dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update Hadrian * support ghc-bignum backend selection in flavours and command-line * support ghc-bignum "--check" flag (compare results of selected backend against results of the native one) in flavours and command-line (e.g. pass --bignum=check-gmp" to check the "gmp" backend) * remove the hack to workaround #15286 * build GMP only when the gmp backend is used * remove hacks to workaround `text` package flags about integer-*. We fix `text` to use ghc-bignum unconditionally in another patch - - - - - fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Bump bytestring and text submodules - - - - - 1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00 docs: mention -hiedir in docs for -outputdir [skip ci] - - - - - 729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00 Hadrian: fix build on Mac OS Catalina (#17798) - - - - - 95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00 Relax allocation threshold for T12150. This test performs little work, so the most minor allocation changes often cause the test to fail. Increasing the threshold to 2% should help with this. - - - - - 8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00 hadrian: Bump pinned cabal.project to an existent index-state - - - - - 08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00 Fix uninitialized field read in Linker.c Valgrind report of the bug when running the test `linker_unload`: ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522) ==29666== by 0x36C0600: loadArchive (LoadArchive.c:626) ==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload) ==29666== ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507) ==29666== by 0x369CA8D: loadObj_ (Linker.c:1536) ==29666== by 0x369CB17: loadObj (Linker.c:1557) ==29666== by 0x3866BC: main (linker_unload.c:33) The problem is `mkOc` allocates a new `ObjectCode` and calls `setOcInitialStatus` without initializing the `status` field. `setOcInitialStatus` reads the field as first thing: static void setOcInitialStatus(ObjectCode* oc) { if (oc->status == OBJECT_DONT_RESOLVE) return; if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; } } `setOcInitialStatus` is unsed in two places for two different purposes: in `mkOc` where we don't have the `status` field initialized yet (`mkOc` is supposed to initialize it), and `loadOc` where we do have `status` field initialized and we want to update it. Instead of splitting the function into two functions which are both called just once I inline the functions in the use sites and remove it. Fixes #18342 - - - - - da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00 fix windows bootstrap due to linker changes - - - - - 2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00 DynFlags: store default depth in SDocContext (#17957) It avoids having to use DynFlags to reach for pprUserLength. - - - - - d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00 Move tablesNextToCode field into Platform tablesNextToCode is a platform setting and doesn't belong into DynFlags (#17957). Doing this is also a prerequisite to fix #14335 where we deal with two platforms (target and host) that may have different platform settings. - - - - - 809caedf by John Ericson at 2020-06-23T22:47:37-04:00 Switch from HscSource to IsBootInterface for module lookup in GhcMake We look up modules by their name, and not their contents. There is no way to separately reference a signature vs regular module; you get what you get. Only boot files can be referenced indepenently with `import {-# SOURCE #-}`. - - - - - 7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Cmm: introduce SAVE_REGS/RESTORE_REGS We don't want to save both Fn and Dn register sets on x86-64 as they are aliased to the same arch register (XMMn). Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]` which makes a set of Cmm registers alive so that they cover all arch registers used to pass parameter, we could have Fn, Dn and XMMn alive at the same time. It made the LLVM code generator choke (see #17920). Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of registers. - - - - - 2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00 CmmToC: don't add extern decl to parsed Cmm data Previously, if a .cmm file *not in the RTS* contained something like: ```cmm section "rodata" { msg : bits8[] "Test\n"; } ``` It would get compiled by CmmToC into: ```c ERW_(msg); const char msg[] = "Test\012"; ``` and fail with: ``` /tmp/ghc32129_0/ghc_4.hc:5:12: error: error: conflicting types for \u2018msg\u2019 const char msg[] = "Test\012"; ^~~ In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error: /tmp/ghc32129_0/ghc_4.hc:4:6: error: note: previous declaration of \u2018msg\u2019 was here ERW_(msg); ^ /builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error: note: in definition of macro \u2018ERW_\u2019 #define ERW_(X) extern StgWordArray (X) ^ ``` See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes Now we don't generate these extern declarations (ERW_, etc.) for top-level data. It shouldn't change anything for the RTS (the only place we use .cmm files) as it is already special cased in `GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit extern declarations when needed. Note that it allows `cgrun069` test to pass with CmmToC (cf #15467). - - - - - 5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00 LLVM: refactor and comment register padding code (#17920) - - - - - cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Add tests for #17920 Metric Decrease: T12150 T12234 - - - - - a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00 Fix issue #18262 by zonking constraints after solving Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results. - - - - - 181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00 Fix a buglet in Simplify.simplCast This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal - - - - - 625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00 Two small tweaks to Coercion.simplifyArgsWorker These tweaks affect the inner loop of simplifyArgsWorker, which in turn is called from the flattener in Flatten.hs. This is a key perf bottleneck to T9872{a,b,c,d}. These two small changes have a modest but useful benefit. No change in functionality whatsoever. Relates to #18354 - - - - - b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00 Don't use timesInt2# with GHC < 8.11 (fix #18358) - - - - - 7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00 Fix invalid printf format - - - - - a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00 Add missing entry to freeNamesItem (#18369) - - - - - 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - 38f829c6 by Ben Gamari at 2020-11-10T11:10:41-05:00 gitlab-ci: Introduce DWARF release jobs for Deb10 and Fedora 27 - - - - - 18 changed files: - + .git-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/merge_request_templates/merge-request.md - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - − compiler/GHC/Builtin/Names.hs-boot - compiler/GHC/Builtin/Names/TH.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/481e31740672a37c5b3a8924bba7e15c4080bc2e...38f829c66612dc57717cab79e1a19fe6f4c2e0fc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/481e31740672a37c5b3a8924bba7e15c4080bc2e...38f829c66612dc57717cab79e1a19fe6f4c2e0fc 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 Tue Nov 10 16:11:42 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 11:11:42 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] testsuite: Add test for #18346 Message-ID: <5faabbbe16dd1_10ee3ffbadb4f9cc12202c0@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: a9d871d5 by Ben Gamari at 2020-11-10T11:11:31-05:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. (cherry picked from commit ee5dcdf95a7c408e9c339aacebf89a007a735f8f) - - - - - 3 changed files: - + testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs - + testsuite/tests/simplCore/should_compile/T18346/T18346.hs - + testsuite/tests/simplCore/should_compile/T18346/all.T Changes: ===================================== testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE RankNTypes #-} + +module MiniLens ((^.), Getting, Lens', lens, view) where + +import Data.Functor.Const (Const(..)) + +type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t + +type Lens' s a = Lens s s a a + +lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b +lens sa sbt afb s = sbt s <$> afb (sa s) +{-# INLINE lens #-} + +type Getting r s a = (a -> Const r a) -> s -> Const r s + +view :: Getting a s a -> s -> a +view l = getConst . l Const +{-# INLINE view #-} + +(^.) :: s -> Getting a s a -> a +s ^. l = getConst (l Const s) +{-# INLINE (^.) #-} ===================================== testsuite/tests/simplCore/should_compile/T18346/T18346.hs ===================================== @@ -0,0 +1,18 @@ +{-# LANGUAGE RankNTypes #-} + +module GHCBug (field) where + +import MiniLens ((^.), Getting, Lens', lens, view) + +t' :: Getting () () () +t' = lens id const +{-# NOINLINE t' #-} + +mlift :: Functor f => Getting b a b -> Lens' (f a) (f b) +mlift l = lens (fmap (^. l)) const +{-# INLINE mlift #-} + +newtype Field = F (Maybe () -> Maybe ()) + +field :: Field +field = F (view (mlift t')) ===================================== testsuite/tests/simplCore/should_compile/T18346/all.T ===================================== @@ -0,0 +1,2 @@ +test('T18346', [extra_files(['MiniLens.hs'])], multimod_compile, ['T18346.hs', '-v0']) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9d871d567e8f63c63dcd4d65ae18fd42d5c5fdf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a9d871d567e8f63c63dcd4d65ae18fd42d5c5fdf 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 Tue Nov 10 16:24:07 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 11:24:07 -0500 Subject: [Git][ghc/ghc][wip/bump-ci] 283 commits: TTG for IPBind had wrong extension name Message-ID: <5faabea74efa1_10ee3ffbd58ef18c122646a@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-ci at Glasgow Haskell Compiler / GHC Commits: 0c701b69 by Alan Zimmerman at 2018-06-24T11:12:34-04:00 TTG for IPBind had wrong extension name The standard[1] for extension naming is to use the XC prefix for the internal extension points, rather than for a new constructor. This is violated for IPBind, having data IPBind id = IPBind (XIPBind id) (Either (Located HsIPName) (IdP id)) (LHsExpr id) | XCIPBind (XXIPBind id) Swap the usage of XIPBind and XCIPBind [1] https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow#Namingconventions Closes #15302 (cherry picked from commit 5f06cf6b6199c8f0e4921f4126f6eb15e2ff18ac) - - - - - abd66223 by Vladislav Zavialov at 2018-06-24T15:11:45-04:00 Do not imply NoStarIsType by TypeOperators/TypeInType Implementation of the "Embrace TypeInType" proposal was done according to the spec, which specified that TypeOperators must imply NoStarIsType. This implication was meant to prevent breakage and to be removed in 2 releases. However, compiling head.hackage has shown that this implication only magnified the breakage, so there is no reason to have it in the first place. To remain in compliance with the three-release policy, we add a workaround to define the (*) type operator even when -XStarIsType is on. Test Plan: ./validate Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4865 - - - - - 867e861b by Alan Zimmerman at 2018-06-25T18:08:56-04:00 Tweak API Annotations for ConDeclGADT (cherry picked from commit 5db9f9129e7519db0c9841fbe7c14f350c23284c) - - - - - 61adfbe6 by Simon Peyton Jones at 2018-06-27T17:07:55-04:00 Instances in no-evidence implications Trac #15290 showed that it's possible that we might attempt to use a quantified constraint to solve an equality in a situation where we don't have anywhere to put the evidence bindings. This made GHC crash. This patch stops the crash, but still rejects the pogram. See Note [Instances in no-evidence implications] in TcInteract. Finding this bug revealed another lurking bug: * An infelicity in the treatment of superclasses -- we were expanding them locally at the leaves, rather than at their binding site; see (3a) in Note [The superclass story]. As a consequence, TcRnTypes.superclassesMightHelp must look inside implications. In more detail: * Stop the crash, by making TcInteract.chooseInstance test for the no-evidence-bindings case. In that case we simply don't use the instance. This entailed a slight change to the type of chooseInstance. * Make TcSMonad.getPendingScDicts (now renamed getPendingGivenScs) return only Givens from the /current level/; and make TcRnTypes.superClassesMightHelp look inside implications. * Refactor the simpl_loop and superclass-expansion stuff in TcSimplify. The logic is much easier to understand now, and has less duplication. (cherry picked from commit 32eb41994f7448caf5fb6b06ed0678d79d029deb) - - - - - 7e19610c by Simon Peyton Jones at 2018-06-27T17:07:55-04:00 Refactor the kind-checking of tyvar binders The refactoring here is driven by the ghastly mess described in comment:24 of Trac #1520. The overall goal is to simplify the kind-checking of typev-variable binders, and in particular to narrow the use of the "in-scope tyvar binder" stuff, which is needed only for associated types: see the new Note [Kind-checking tyvar binders for associated types] in TcHsType. Now * The "in-scope tyvar binder" stuff is done only in - kcLHsQTyVars, which is used for the LHsQTyVars of a data/newtype, or type family declaration. - tcFamTyPats, which is used for associated family instances; it now calls tcImplicitQTKBndrs, which in turn usese newFlexiKindedQTyVar * tcExpicitTKBndrs (which is used only for function signatures, data con signatures, pattern synonym signatures, and expression type signatures) now does not go via the "in-scope tyvar binder" stuff at all. While I'm still not happy with all this code, the code is generally simpler, and I think this is a useful step forward. It does cure the problem too. (It's hard to trigger the problem in vanilla Haskell code, because the renamer would normally use different names for nested binders, so I can't offer a test.) (cherry picked from commit 9fc40c733ba8822a04bd92883801b214dee099ca) - - - - - 145f7c66 by Simon Peyton Jones at 2018-06-27T17:07:56-04:00 Fix TcLevel manipulation in TcDerivInfer.simplifyDeriv The level numbers we were getting simply didn't obey the invariant (ImplicInv) in TcType Note [TcLevel and untouchable type variables] That leads to chaos. Easy to fix. I improved the documentation. I also added an assertion in TcSimplify that checks that level numbers go up by 1 as we dive inside implications, so that we catch the problem at source rather than than through its obscure consequences. That in turn showed up that TcRules was also generating constraints that didn't obey (ImplicInv), so I fixed that too. I have no idea what consequences were lurking behing that bug, but anyway now it's fixed. Hooray. (cherry picked from commit 261dd83cacec71edd551e9c581d05285c9ea3226) - - - - - 4cfeca02 by Alan Zimmerman at 2018-06-27T17:07:56-04:00 API Annotations when parsing typapp Make sure the original annotations are still accessible for a promoted type. Closes #15303 (cherry picked from commit e53c113dcfeca9ee957722ede3d8b6a2c4c751a1) - - - - - 149d7912 by Simon Peyton Jones at 2018-06-27T17:07:56-04:00 Fix error recovery for pattern synonyms As Trac #15289 showed, we were carrying on after a type error in a pattern synonym, and then crashing. This patch improves error handling for pattern synonyms. I also moved a bit of code from TcBinds into TcPatSyn, which helpfully narrows the API. (cherry picked from commit 2896082ec79f02b6388e038a8dae6cb22fe72dfc) - - - - - 5059edb0 by Ben Gamari at 2018-07-10T20:21:43-04:00 Bump xhtml submodule to 3000.2.2.1 (cherry picked from commit 5a1290a8317056065f409ffd47fa6114172a1a15) - - - - - 31f7d21b by Sylvain Henry at 2018-07-11T22:02:00-04:00 Fix for built-in Natural literals desugaring The recent patch "Built-in Natural literals in Core" (https://phabricator.haskell.org/rGHCfe770c211631e7b4c9b0b1e88ef9b6046c6 585ef) introduced a regression when desugaring large numbers. This patch fixes it and adds a regression test. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15301 Differential Revision: https://phabricator.haskell.org/D4885 (cherry picked from commit 987b5e7fbacd8afd2c8463c16eac28cd68f43155) - - - - - 634c07dc by Richard Eisenberg at 2018-07-12T15:25:45-04:00 Expand and implement Note [The tcType invariant] Read that note -- it's necessary to make sure that we can always call typeKind without panicking. As discussed on #14873, there were more checks and zonking to do, implemented here. There are no known bugs fixed by this patch, but there are likely unknown ones. (cherry picked from commit cf67e59a90bcaba657a9f5db3d5defb6289c274f) - - - - - 113bdb8b by Ryan Scott at 2018-07-12T15:28:30-04:00 Make ppr_tc_args aware of -fprint-explicit-kinds Summary: `ppr_tc_args` was printing invisible kind arguments even when `-fprint-explicit-kinds` wasn't enabled. Easily fixed. Test Plan: make test TEST=T15341 Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15341 Differential Revision: https://phabricator.haskell.org/D4932 (cherry picked from commit dbdcacfc55f28d8a85484cc1cf13dd78c45bf7ee) - - - - - f663e507 by Ryan Scott at 2018-07-12T17:06:02-04:00 Fix #15331 with careful blasts of parenthesizeHsType Another `-ddump-splices` bug that can be solved with more judicious use of parentheses. Test Plan: make test TEST=T15331 Reviewers: goldfire, bgamari, alanz, tdammers Reviewed By: tdammers Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15331 Differential Revision: https://phabricator.haskell.org/D4920 (cherry picked from commit b6a3386186b77333b7a6cdc163499d7dae0dad1c) - - - - - a6a83d9a by Ryan Scott at 2018-07-12T17:06:11-04:00 Parenthesize rank-n contexts in Convert Summary: A simple oversight. Test Plan: make test TEST=T15324 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15324 Differential Revision: https://phabricator.haskell.org/D4910 (cherry picked from commit 57733978482dc1e566a7d4cd90d4cbbd1315e3b2) - - - - - 423a8eff by Matthew Pickering at 2018-07-12T17:06:11-04:00 Export findImportUsage and ImportDeclUsage Reviewers: bgamari, alpmestan Reviewed By: alpmestan Subscribers: alpmestan, rwbarton, thomie, carter GHC Trac Issues: #15335 Differential Revision: https://phabricator.haskell.org/D4927 (cherry picked from commit 2b1adaa7817c453df868d928312a9a99a0481eb1) - - - - - a39b58d5 by Alan Zimmerman at 2018-07-12T17:06:11-04:00 Fix mkGadtDecl does not set con_forall correctly A GADT declaration surrounded in parens does not det the con_forall field correctly. e.g. data MaybeDefault v where TestParens :: (forall v . (Eq v) => MaybeDefault v) Closes #15323 (cherry picked from commit 6e4e6d1c674a9d0257ca5c6caa26da18edf8ad8c) - - - - - 22c951e6 by Matthías Páll Gissurarson at 2018-07-12T17:06:11-04:00 Fix errors caused by invalid candidates leaking from hole fits This is a one line fix (and a note) that fixes four tickets, #15007, #15321 and #15202, #15314 The issue was that errors caused by illegal candidates (according to GHC stage or being internal names) were leaking to the user, causing bewildering error messages. If a candidate causes the type checker to error, it is not a valid hole fit, and should be discarded. As mentioned in #15321, this can cause a pattern of omissions, which might be hard to discover. A better approach would be to gather the error messages, and ask users to report them as GHC bugs. This will be implemented in a subsequent change. Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15007, #15321, #15202, #15314 Differential Revision: https://phabricator.haskell.org/D4909 (cherry picked from commit 39de4e3d33dd9879398062620ad00b1e3b8481ce) - - - - - 1fca115b by Ömer Sinan Ağacan at 2018-07-12T17:06:11-04:00 Add regression test for #15321 (cherry picked from commit e835fdb18cca66820728afce9c924a1c71f17fee) - - - - - eb680f2c by Ryan Scott at 2018-07-12T17:06:12-04:00 Fix newtype instance GADTs Summary: This was taken from Richard's branch, which in turn was submitted to Phab by Matthew, which in turn was commandeered by Ryan. This fixes an issue with newtype instances in which too many coercions were being applied in the worker. This fixes the issue by removing the data family instance axiom from the worker and moving to the wrapper. Moreover, we now require all newtype instances to have wrappers, for symmetry with data instances. Reviewers: goldfire, bgamari, simonpj, mpickering Reviewed By: mpickering Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15318 Differential Revision: https://phabricator.haskell.org/D4902 (cherry picked from commit 927518668111584a06f12bd9eb1b0910a38acf4f) - - - - - b52cfe41 by Matthew Pickering at 2018-07-12T17:06:12-04:00 Run the renamed source plugin after each HsGroup This allows modification of each `HsGroup` after it has been renamed. The old behaviour of keeping the renamed source until later can be recovered if desired by using the `keepRenamedSource` plugin but it shouldn't really be necessary as it can be inspected in the `TcGblEnv`. Reviewers: nboldi, bgamari, alpmestan Reviewed By: nboldi, alpmestan Subscribers: alpmestan, rwbarton, thomie, carter GHC Trac Issues: #15315 Differential Revision: https://phabricator.haskell.org/D4947 (cherry picked from commit 1a79270c72cfcd98d683cfe7b2c777d8dd353b78) - - - - - 42396113 by Simon Peyton Jones at 2018-07-12T17:06:12-04:00 Add commnent about binder order ...provoked by Trac #15308 (cherry picked from commit 3d002087dce9c61932dd17047902baa83581f4df) - - - - - 9bcbb222 by Ryan Scott at 2018-07-12T17:06:12-04:00 Fix #15308 by suppressing invisble args more rigorously Summary: There was a buglet in `stripInvisArgs` (which is part of the pretty-printing pipeline for types) in which only invisble arguments which came before any visible arguments would be suppressed, but any invisble arguments that came //after// visible ones would still be printed, even if `-fprint-explicit-kinds` wasn't enabled. The fix is simple: make `stripInvisArgs` recursively process the remaining types even after a visible argument is encountered. Test Plan: make test TEST=T15308 Reviewers: goldfire, bgamari Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15308 Differential Revision: https://phabricator.haskell.org/D4891 (cherry picked from commit 93b7ac8d73885369f61f6eb6147352d45de4e957) - - - - - 92925b3d by Ryan Scott at 2018-07-12T17:06:12-04:00 Fix #15307 by making nlHsFunTy parenthesize more Summary: `nlHsFunTy` wasn't parenthesizing its arguments at all, which led to `-ddump-deriv` producing incorrectly parenthesized types (since it uses `nlHsFunTy` to construct those types), as demonstrated in #15307. Fix this by changing `nlHsFunTy` to add parentheses à la `ppr_ty`: always parenthesizing the argument type with function precedence, and recursively processing the result type, adding parentheses for each function type it encounters. Test Plan: make test TEST=T14578 Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15307 Differential Revision: https://phabricator.haskell.org/D4890 (cherry picked from commit 59a15a56e180b59656e45df04f7df61de8298881) - - - - - cfc4afad by Simon Peyton Jones at 2018-07-12T17:06:12-04:00 Add nakedSubstTy and use it in TcHsType.tcInferApps This was a tricky one. During type checking we maintain TcType: Note [The well-kinded type invariant] That is, types are well-kinded /without/ zonking. But in tcInferApps we were destroying that invariant by calling substTy, which in turn uses smart constructors, which eliminate apparently-redundant Refl casts. This is horribly hard to debug beause they really are Refls and so it "ought" to be OK to discard them. But it isn't, as the above Note describes in some detail. Maybe we should review the invariant? But for now I just followed it, tricky thought it is. This popped up because (for some reason) when I fixed Trac #15343, that exposed this bug by making test polykinds/T14174a fail (in Trac #14174 which indeed has the same origin). So this patch fixes a long standing and very subtle bug. One interesting point: I defined nakedSubstTy in a few lines by using the generic mapType stuff. I note that the "normal" TyCoRep.substTy does /not/ use mapType. But perhaps it should: substTy has lots of $! strict applications in it, and they could all be eliminated just by useing the StrictIdentity monad. And that'd make it much easier to experiment with switching between strict and lazy versions. (cherry picked from commit 5067b205a8abb5a9f98335d3a929f647c88c0aa2) - - - - - d0dfc5cc by Richard Eisenberg at 2018-07-12T17:06:12-04:00 Kind-check CUSK associated types separately Previously, we kind-checked associated types while while still figuring out the kind of a CUSK class. This caused trouble, as documented in Note [Don't process associated types in kcLHsQTyVars] in TcTyClsDecls. This commit moves this process after the initial kind of the class is determined. Fixes #15142. Test case: indexed-types/should_compile/T15142.hs (cherry picked from commit 030211d21207dabb7a4bf21cc9af6fa5eb066db1) - - - - - 23b4d83f by Ömer Sinan Ağacan at 2018-07-12T17:06:12-04:00 Fix nptr field alignment in RtClosureInspect `extractSubTerms` (which is extracting pointer and non-pointer fields of a closure) was computing the alignment incorrectly when aligning a 64-bit value (e.g. a Double) on i386 by aligning it to 64-bits instead of to word size (32-bits). This is documented in `mkVirtHeapOffsetsWithPadding`: > Align the start offset (eg, 2-byte value should be 2-byte aligned). > But not more than to a word. Fixes #15061 Test Plan: Validated on both 32-bit and 64-bit. 32-bit fails with various unrelated stat failures, but no actual test failures. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15061 Differential Revision: https://phabricator.haskell.org/D4906 (cherry picked from commit 15bb4e0b6c08b1f8f5511f04af14242f13833ed1) - - - - - c0323d97 by Ryan Scott at 2018-07-12T17:22:26-04:00 Instantiate GND bindings with an explicit type signature Summary: Before, we were using visible type application to apply impredicative types to `coerce` in `GeneralizedNewtypeDeriving`-generated bindings. This approach breaks down when combined with `QuantifiedConstraints` in certain ways, which #14883 and #15290 provide examples of. See Note [GND and QuantifiedConstraints] for all the gory details. To avoid this issue, we instead use an explicit type signature to instantiate each GND binding, and use that to bind any type variables that might be bound by a class method's type signature. This reduces the need to impredicative type applications, and more importantly, makes the programs from #14883 and #15290 work again. Test Plan: make test TEST="T15290b T15290c T15290d T14883" Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14883, #15290 Differential Revision: https://phabricator.haskell.org/D4895 (cherry picked from commit 132273f34e394bf7e900d0c15e01e91edd711890) - - - - - e5b1ec95 by Simon Marlow at 2018-07-14T11:58:19-04:00 submodule update (cherry picked from commit e40eb738bb15795a22b2765e12c3add20efa91a5) - - - - - 148310fd by Ben Gamari at 2018-07-14T11:58:19-04:00 Bump haskeline submodule to 0.7.4.3 (cherry picked from commit cbd4b33317b6cd3751878bbe7a0cc7601bd169e7) - - - - - 736f4bce by Ben Gamari at 2018-07-14T11:58:19-04:00 Bump mtl submodule to v2.2.2 (cherry picked from commit c67cf9e9e66f629440c80ae3bf1616e2aac7002b) - - - - - ca59fa76 by Ben Gamari at 2018-07-14T11:58:19-04:00 Bump directory submodule to v1.3.3.0 (cherry picked from commit b794c7ed7d515a98b350417143fb46dd5e6d39df) - - - - - 3f965941 by Ben Gamari at 2018-07-14T11:58:19-04:00 Bump unix submodule (cherry picked from commit c3328ff354db2be5994807fed6b5b132489a9e3e) - - - - - 391ee977 by Ben Gamari at 2018-07-14T11:58:19-04:00 Remove random submodule I believe this was originally introduced to help test DPH, which is now gone. (cherry picked from commit 0905fec089b3270f540c7ee33959cbf8ecfcb4d7) - - - - - 5b10d537 by Simon Peyton Jones at 2018-07-14T14:22:20-04:00 Fix decompsePiCos and visible type application Trac #15343 was caused by two things First, in TcHsType.tcHsTypeApp, which deals with the type argment in visible type application, we were failing to call solveLocalEqualities. But the type argument is like a user type signature so it's at least inconsitent not to do so. I thought that would nail it. But it didn't. It turned out that we were ended up calling decomposePiCos on a type looking like this (f |> co) Int where co :: (forall a. ty) ~ (t1 -> t2) Now, 'co' is insoluble, and we'll report that later. But meanwhile we don't want to crash in decomposePiCos. My fix involves keeping track of the type on both sides of the coercion, and ensuring that the outer shape matches before decomposing. I wish there was a simpler way to do this. But I think this one is at least robust. I suppose it is possible that the decomposePiCos fix would have cured the original report, but I'm leaving the one-line tcHsTypeApp fix in too because it just seems more consistent. (cherry picked from commit aedbf7f1c402ecbcb5ff192d5fb4dd6dd4771bf8) - - - - - 1cdc3ecc by Simon Marlow at 2018-07-14T14:22:20-04:00 Fix deadlock between STM and throwTo There was a lock-order reversal between lockTSO() and the TVar lock, see #15136 for the details. It turns out we can fix this pretty easily by just deleting all the locking code(!). The principle for unblocking a `BlockedOnSTM` thread then becomes the same as for other kinds of blocking: if the TSO belongs to this capability then we do it directly, otherwise we send a message to the capability that owns the TSO. That is, a thread blocked on STM is owned by its capability, as it should be. The possible downside of this is that we might send multiple messages to wake up a thread when the thread is on another capability. This is safe, it's just not very efficient. I'll try to do some experiments to see if this is a problem. Test Plan: Test case from #15136 doesn't deadlock any more. Reviewers: bgamari, osa1, erikd Reviewed By: osa1 Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15136 Differential Revision: https://phabricator.haskell.org/D4956 (cherry picked from commit 7fc418df856d9b58034eeec48915646e67a7a562) - - - - - 30a4bcc3 by Ömer Sinan Ağacan at 2018-07-14T14:22:20-04:00 Fix processHeapClosureForDead CONSTR_NOCAF case CONSTR_NOCAF was introduced with 55d535da10d as a replacement for CONSTR_STATIC and CONSTR_NOCAF_STATIC, however, as explained in Note [static constructors], we copy CONSTR_NOCAFs (which can also be seen in evacuate) during GC, and they can become dead, like other CONSTR_X_Ys. processHeapClosureForDead is updated to reflect this. Test Plan: Validates on x86_64. Existing failures on i386. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #7836, #15063, #15087, #15165 Differential Revision: https://phabricator.haskell.org/D4928 (cherry picked from commit 2625f1310edeff62eb3876cc6efbe105a80fe4ad) - - - - - c15ba1fb by Simon Marlow at 2018-07-16T18:26:56-04:00 Optimise wakeups for STM Avoids repeated wakeup messages being sent when a TVar is written to multiple times. See comments for details. Test Plan: * Test from #15136 (will be added to stm shortly) * existing stm tests Reviewers: bgamari, osa1, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15136 Differential Revision: https://phabricator.haskell.org/D4961 (cherry picked from commit 502640c90c3d0fbb6c46257be14fdc7e3c694c6c) - - - - - 655c6175 by Antti Siponen at 2018-07-16T18:36:15-04:00 #15387 Fix setting testsuite verbose to zero (cherry picked from commit 0d6ef6d71e5077eb217456fdd8a515a8cab724ad) - - - - - c6774421 by Ben Gamari at 2018-07-16T19:32:23-04:00 Revert "Do not imply NoStarIsType by TypeOperators/TypeInType" This reverts commit abd6622324733c67b05e0cbd0c8c3d12c6332f61. - - - - - bb5aa616 by Vladislav Zavialov at 2018-07-16T19:32:35-04:00 Do not imply NoStarIsType by TypeOperators/TypeInType Implementation of the "Embrace TypeInType" proposal was done according to the spec, which specified that TypeOperators must imply NoStarIsType. This implication was meant to prevent breakage and to be removed in 2 releases. However, compiling head.hackage has shown that this implication only magnified the breakage, so there is no reason to have it in the first place. To remain in compliance with the three-release policy, we add a workaround to define the (*) type operator even when -XStarIsType is on. Test Plan: ./validate Reviewers: bgamari, RyanGlScott, goldfire, phadej, hvr Reviewed By: bgamari, RyanGlScott Subscribers: harpocrates, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4865 (cherry picked from commit 65c186f0fdde95fd7c63ab9bd9b33a0213dba7d1) - - - - - 10fa8041 by Alan Zimmerman at 2018-07-30T17:46:45-04:00 TTG typo: XFieldOcc should be XCFieldOcc In the following data FieldOcc pass = FieldOcc { extFieldOcc :: XFieldOcc pass , rdrNameFieldOcc :: Located RdrName -- ^ See Note [Located RdrNames] in HsExpr } | XFieldOcc (XXFieldOcc pass) we are using XFieldOcc for both the extFieldOcc type and the extra constructor. The first one should be XCFieldOcc Updates haddock submodule closes #15386 (cherry picked from commit 926954196f9ffd7b89cba53061b39ef996e1650c) - - - - - f14c087a by Tamar Christina at 2018-07-30T17:46:45-04:00 split-obj: disable split-objects on Windows. A change has caused GHC to generate excessive specializations. This is making GHC generate 1800 splits for a simple GHC.Prim module, which means 1800 fork/exec calls. Due to this compilation times on Windows with split-objs on take over 24 hours to complete depending on your disk speed. Also the end compiler compiling medium to large project is also much slower. So I think we need to just disable split-objects. As there's nothing that can be done about this. Test Plan: ./validate Reviewers: bgamari Subscribers: tdammers, rwbarton, thomie, erikd, carter GHC Trac Issues: #15051 Differential Revision: https://phabricator.haskell.org/D4915 (cherry picked from commit 53649947223f197cf93e26393486f578d56c46c6) - - - - - dafffdc0 by Krzysztof Gogolewski at 2018-07-30T17:46:45-04:00 Add an expect_broken test for #14185 Test Plan: validate Reviewers: goldfire, bgamari, alpmestan Reviewed By: alpmestan Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14185 Differential Revision: https://phabricator.haskell.org/D4981 (cherry picked from commit 3581212e3a5ba42114f47ed83a96322e0e8028ab) - - - - - 72dc7989 by Ömer Sinan Ağacan at 2018-07-30T17:46:45-04:00 Run StgCse after unarise, fixes #15300 Given two unboxed sum terms: (# 1 | #) :: (# Int | Int# #) (# 1 | #) :: (# Int | Int #) These two terms are not equal as they unarise to different unboxed tuples. However StgCse was thinking that these are equal, and replacing one of these with a binder to the other. To not deal with unboxed sums in StgCse we now do it after unarise. For StgCse to maintain post-unarise invariants we factor-out case binder in-scopeness check to `stgCaseBndrInScope` and use it in StgCse. Also did some refactoring in SimplStg. Another way to fix this would be adding a special case in StgCse to not bring unboxed sum binders in scope: diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs index 6c740ca4cb..93a0f8f6ad 100644 --- a/compiler/simplStg/StgCse.hs +++ b/compiler/simplStg/StgCse.hs @@ -332,7 +332,11 @@ stgCseExpr env (StgLetNoEscape binds body) stgCseAlt :: CseEnv -> OutId -> InStgAlt -> OutStgAlt stgCseAlt env case_bndr (DataAlt dataCon, args, rhs) = let (env1, args') = substBndrs env args - env2 = addDataCon case_bndr dataCon (map StgVarArg args') env1 + env2 + | isUnboxedSumCon dataCon + = env1 + | otherwise + = addDataCon case_bndr dataCon (map StgVarArg args') env1 -- see note [Case 2: CSEing case binders] rhs' = stgCseExpr env2 rhs in (DataAlt dataCon, args', rhs') I think this patch seems better in that it doesn't add a special case to StgCse. Test Plan: Validate. I tried to come up with a minimal example but failed. I thought a simple program like data T = T (# Int | Int #) (# Int# | Int #) case T (# 1 | #) (# 1 | #) of ... should be enough to trigger this bug, but for some reason StgCse doesn't do anything on this program. Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15300 Differential Revision: https://phabricator.haskell.org/D4962 (cherry picked from commit 3c311e50e760c3ba00dc9692ad1536c79820598d) - - - - - 50e4e48b by Mitsutoshi Aoe at 2018-07-30T17:46:45-04:00 rts: Flush eventlog in hs_init_ghc (fixes #15440) Without this change RTS typically doesn't flush some important events until the process terminates or it doesn't write them at all in case it terminates abnormally. Here is a list of such events: * EVENT_WALL_CLOCK_TIME * EVENT_OS_PROCESS_PID * EVENT_OS_PROCESS_PPID * EVENT_RTS_IDENTIFIER * EVENT_PROGRAM_ARGS * EVENT_PROGRAM_ENV (cherry picked from commit 7a3e1b25ff9a570851a59c4cf3600daa49867b9b) - - - - - 9a190caf by Ben Gamari at 2018-07-30T17:46:45-04:00 Bump terminfo submodule to 0.4.1.2 (cherry picked from commit b2852a440cac3310bbe443a9010949dbea94e7db) - - - - - 3795b454 by Peter Trommler at 2018-07-30T17:46:45-04:00 Fix endian issues in ghc-heap In test heap_all arity and n_args were swapped on big endian systems. Take care of endianness when reading parts of a machine word from a `Word`. This fixes one out of 36 failing tests reported in #15399. Test Plan: validate Reviewers: simonmar, bgamari, hvr, erikd Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15399 Differential Revision: https://phabricator.haskell.org/D5001 (cherry picked from commit d7cb1bbc26719cf6082abe0d91d80be466e25bfc) - - - - - 4c158eeb by Josh Price at 2018-07-30T17:46:46-04:00 Fix minor formatting issue in users_guide/bugs.rst (cherry picked from commit fb11a104018dfb4065fd91c549fec6d46fa77945) - - - - - 3ec1d931 by Ben Gamari at 2018-07-30T17:46:46-04:00 base: Make Foreign.Marshal.Alloc.allocBytes[Aligned] NOINLINE As noted in #14346, touch# may be optimized away when the simplifier can see that the continuation passed to allocaBytes will not return. Marking CPS-style functions with NOINLINE ensures that the simplier can't draw any unsound conclusions. Ultimately the right solution here will be to do away with touch# and instead introduce a scoped primitive as is suggested in #14375. (cherry picked from commit 404bf05ed3193e918875cd2f6c95ae0da5989be2) - - - - - 386aad8a by Ben Gamari at 2018-07-30T17:46:46-04:00 base: Fix documentation of System.Environment.Blank - - - - - 26a7f850 by Ben Gamari at 2018-07-30T17:46:46-04:00 testsuite: Fix up testsuite - - - - - 96609122 by Sylvain Henry at 2018-07-31T13:18:41-04:00 testsuite: Add test for #14346 (cherry picked from commit f8e5da92c0160a675e1666a5d6ed6a8ffcae193c) - - - - - a107cced by Simon Peyton Jones at 2018-07-31T14:18:32-04:00 Fix a nasty bug in piResultTys I was failing to instantiate vigorously enough in Type.piResultTys and in the very similar function ToIface.toIfaceAppArgsX This caused Trac #15428. The fix is easy. See Note [Care with kind instantiation] in Type.hs (cherry picked from commit e1b5a1174e42e390855b153015ce5227b3251d89) - - - - - b6a2c0d9 by Tamar Christina at 2018-07-31T14:18:37-04:00 stack: fix stack allocations on Windows Summary: On Windows one is not allowed to drop the stack by more than a page size. The reason for this is that the OS only allocates enough stack till what the TEB specifies. After that a guard page is placed and the rest of the virtual address space is unmapped. The intention is that doing stack allocations will cause you to hit the guard which will then map the next page in and move the guard. This is done to prevent what in the Linux world is known as stack clash vulnerabilities https://access.redhat.com/security/cve/cve-2017-1000364. There are modules in GHC for which the liveliness analysis thinks the reserved 8KB of spill slots isn't enough. One being DynFlags and the other being Cabal. Though I think the Cabal one is likely a bug: ``` 4d6544: 81 ec 00 46 00 00 sub $0x4600,%esp 4d654a: 8d 85 94 fe ff ff lea -0x16c(%ebp),%eax 4d6550: 3b 83 1c 03 00 00 cmp 0x31c(%ebx),%eax 4d6556: 0f 82 de 8d 02 00 jb 4ff33a <_cLpg_info+0x7a> 4d655c: c7 45 fc 14 3d 50 00 movl $0x503d14,-0x4(%ebp) 4d6563: 8b 75 0c mov 0xc(%ebp),%esi 4d6566: 83 c5 fc add $0xfffffffc,%ebp 4d6569: 66 f7 c6 03 00 test $0x3,%si 4d656e: 0f 85 a6 d7 02 00 jne 503d1a <_cLpb_info+0x6> 4d6574: 81 c4 00 46 00 00 add $0x4600,%esp ``` It allocates nearly 18KB of spill slots for a simple 4 line function and doesn't even use it. Note that this doesn't happen on x64 or when making a validate build. Only when making a build without a validate and build.mk. This and the allocation in DynFlags means the stack allocation will jump over the guard page into unmapped memory areas and GHC or an end program segfaults. The pagesize on x86 Windows is 4KB which means we hit it very easily for these two modules, which explains the total DOA of GHC 32bit for the past 3 releases and the "random" segfaults on Windows. ``` 0:000> bp 00503d29 0:000> gn Breakpoint 0 hit WARNING: Stack overflow detected. The unwound frames are extracted from outside normal stack bounds. eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40 eip=00503d29 esp=013e96fc ebp=03cf8f70 iopl=0 nv up ei pl nz na po nc cs=0023 ss=002b ds=002b es=002b fs=0053 gs=002b efl=00000202 setup+0x103d29: 00503d29 89442440 mov dword ptr [esp+40h],eax ss:002b:013e973c=???????? WARNING: Stack overflow detected. The unwound frames are extracted from outside normal stack bounds. WARNING: Stack overflow detected. The unwound frames are extracted from outside normal stack bounds. 0:000> !teb TEB at 00384000 ExceptionList: 013effcc StackBase: 013f0000 StackLimit: 013eb000 ``` This doesn't fix the liveliness analysis but does fix the allocations, by emitting a function call to `__chkstk_ms` when doing allocations of larger than a page, this will make sure the stack is probed every page so the kernel maps in the next page. `__chkstk_ms` is provided by `libGCC`, which is under the `GNU runtime exclusion license`, so it's safe to link against it, even for proprietary code. (Technically we already do since we link compiled C code in.) For allocations smaller than a page we drop the stack and probe the new address. This avoids the function call and still makes sure we hit the guard if needed. PS: In case anyone is Wondering why we didn't notice this before, it's because we only test x86_64 and on Windows 10. On x86_64 the page size is 8KB and also the kernel is a bit more lenient on Windows 10 in that it seems to catch the segfault and resize the stack if it was unmapped: ``` 0:000> t eax=03b6b9c9 ebx=00dc90f0 ecx=03cac48c edx=03cac43d esi=03b6b9c9 edi=03abef40 eip=00503d2d esp=013e96fc ebp=03cf8f70 iopl=0 nv up ei pl nz na po nc cs=0023 ss=002b ds=002b es=002b fs=0053 gs=002b efl=00000202 setup+0x103d2d: 00503d2d 8b461b mov eax,dword ptr [esi+1Bh] ds:002b:03b6b9e4=03cac431 0:000> !teb TEB at 00384000 ExceptionList: 013effcc StackBase: 013f0000 StackLimit: 013e9000 ``` Likely Windows 10 has a guard page larger than previous versions. This fixes the stack allocations, and as soon as I get the time I will look at the liveliness analysis. I find it highly unlikely that simple Cabal function requires ~2200 spill slots. Test Plan: ./validate Reviewers: simonmar, bgamari Reviewed By: bgamari Subscribers: AndreasK, rwbarton, thomie, carter GHC Trac Issues: #15154 Differential Revision: https://phabricator.haskell.org/D4917 (cherry picked from commit d0bbe1bf351c8b85c310afb0dd1fb1f12f9474bf) - - - - - 9a4ac756 by Krzysztof Gogolewski at 2018-07-31T14:18:37-04:00 Fix a major copy'n'paste error in LLVM CodeGen Summary: In D4592, `AddWordC` is lowered as an unsigned subtraction instead of an unsigned addition when compiling with LLVM. This patch rectifies that. Reviewers: angerman, bgamari, monoidal Reviewed By: angerman, bgamari, monoidal Subscribers: osa1, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4969 (cherry picked from commit f629442be93f4608e6bb53bfe2264a406230c546) - - - - - 39ab54c9 by David Feuer at 2018-07-31T15:53:19-04:00 Harden fixST Trac #15349 reveals that lazy blackholing can cause trouble for `fixST` much like it can for `fixIO`. Make `fixST` work just like `fixIO`. Reviewers: simonmar, hvr, bgamari Reviewed By: simonmar Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15349 Differential Revision: https://phabricator.haskell.org/D4948 (cherry picked from commit 5a49651f3161473b383ec497af38e9daa022b9ac) - - - - - 4c044ed1 by Krzysztof Gogolewski at 2018-07-31T15:53:19-04:00 Fix pretty-printing of data declarations in splices Test Plan: validate Reviewers: RyanGlScott, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15365 Differential Revision: https://phabricator.haskell.org/D4998 (cherry picked from commit 3aa09cc5af9cacba91915c095f9652ee5ed31ec7) - - - - - 04805078 by Krzysztof Gogolewski at 2018-07-31T15:53:19-04:00 Fix Ar crashing on odd-sized object files (Trac #15396) Summary: All the work was done by Moritz Angermann. Test Plan: validate Reviewers: angerman, RyanGlScott, bgamari Reviewed By: angerman Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15396 Differential Revision: https://phabricator.haskell.org/D5013 (cherry picked from commit 754c3a55a603b155fa5d9a282de73d41a4694ffc) - - - - - 8bed1400 by Ryan Scott at 2018-07-31T15:53:19-04:00 Suppress -Winaccessible-code in derived code Summary: It's rather unfortunate that derived code can produce inaccessible code warnings (as demonstrated in #8128, #8740, and #15398), since the programmer has no control over the generated code. This patch aims to suppress `-Winaccessible-code` in all derived code. It accomplishes this by doing the following: * Generalize the `ic_env :: TcLclEnv` field of `Implication` to be of type `Env TcGblEnc TcLclEnv` instead. This way, it also captures `DynFlags`, which record the flag state at the time the `Implication` was created. * When typechecking derived code, turn off `-Winaccessible-code`. This way, any insoluble given `Implication`s that are created when typechecking this derived code will remember that `-Winaccessible-code` was disabled. * During error reporting, consult the `DynFlags` of an `Implication` before making the decision to report an inaccessible code warning. Test Plan: make test TEST="T8128 T8740 T15398" Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: monoidal, rwbarton, thomie, carter GHC Trac Issues: #8128, #8740, #15398 Differential Revision: https://phabricator.haskell.org/D4993 (cherry picked from commit 44a7b9baa45c4ab939c7d996519b5e3de3e13c5a) - - - - - d170083b by Simon Marlow at 2018-07-31T15:53:19-04:00 Fix the GHCi debugger with ApplicativeDo Summary: `collectLStmtsBinders` was returning nothing for `ApplicativeStmts`, which caused the debugger to not track free variables in many cases when using `ApplicativeDo`. Test Plan: * new test case * validate Reviewers: bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15422 Differential Revision: https://phabricator.haskell.org/D4991 (cherry picked from commit 4ea9311cc5c3b99ea6915bee23f0a6776731f20e) - - - - - ff839f20 by Ryan Scott at 2018-07-31T15:53:19-04:00 Fix #15423 by using pprAStmtContext Summary: Previously, we were using `pprStmtContext` instead, which led to error messages missing indefinite articles where they were required. Test Plan: make test TEST="T13242a T7786 Typeable1" Reviewers: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15423 Differential Revision: https://phabricator.haskell.org/D4992 (cherry picked from commit 99f45e2a751dda4fdf00256d397a2932d430f3a7) - - - - - 09abd1c4 by Simon Peyton Jones at 2018-07-31T15:53:19-04:00 Stop marking soluble ~R# constraints as insoluble We had a constraint (a b ~R# Int), and were marking it as 'insoluble'. That's bad; it isn't. And it caused Trac #15431. Soultion is simple. I did a tiny refactor on can_eq_app, so that it is used only for nominal equalities. (cherry picked from commit f0d27f515ffbc476144d1d1dd1a71bf9fa93c94b) - - - - - 851f3341 by Simon Peyton Jones at 2018-07-31T15:53:19-04:00 Fix PrelRules.caseRules to account for out-of-range tags As Trac #15436 points out, it is possible to get case dataToTag# (x :: T) of DEFAULT -> blah1 -1# -> blah2 0 -> blah3 The (-1#) alterantive is unreachable, because dataToTag# returns tags in the range [0..n-1] where n is the number of data constructors in type T. This actually made GHC crash; now we simply discard the unreachable alterantive. See Note [Unreachable caseRules alternatives] in PrelRules (cherry picked from commit 9897f6783a58265d5eaef5fb06f04320c7737e87) - - - - - 2a162eba by Sylvain Henry at 2018-07-31T15:53:19-04:00 Fix Git commit ID detection in Git worktrees Summary: When using a Git worktree, ".git" is a file, not a directory Reviewers: bgamari, monoidal Reviewed By: monoidal Subscribers: rwbarton, thomie, erikd, carter Differential Revision: https://phabricator.haskell.org/D5016 (cherry picked from commit 3539561b24b78aee2b37280ddf6bb64e2db3a67d) - - - - - 06c29ddc by Ben Gamari at 2018-07-31T16:44:12-04:00 Fix some casts. This fixes #15346, and is a team effort between Ryan Scott and myself (mostly Ryan). We discovered two errors related to FC's "push" rules, one in the TPush rule (as implemented in pushCoTyArg) and one in KPush rule (it shows up in liftCoSubstVarBndr). The solution: do what the paper says, instead of whatever random thoughts popped into my head as I was actually implementing. Note that this is a backport of the fix merged to master, af624071fa063158d6e963e171280676f9c0a0b0. Also fixes #15419, which is actually the same underlying problem. Test case: dependent/should_compile/T{15346,15419}. - - - - - f579162a by Richard Eisenberg at 2018-07-31T16:46:44-04:00 testsuite: Add test for #15346 Test case: dependent/should_compile/T{15346,15419}. - - - - - 79e13610 by Ben Gamari at 2018-07-31T20:22:49-04:00 Enable two-step allocator on FreeBSD Simplify #ifdef nesting and use MAP_GUARD on FreeBSD and similar systems. This allows the two-step allocator to be used on FreeBSD, fixing #15348. (cherry picked from commit 123aeb916cba93018039e583d42408dae80a6dc9) - - - - - eb2b71c5 by Ningning Xie at 2018-07-31T20:24:39-04:00 Fix #15453: bug in ForAllCo case in opt_trans_rule Summary: Given ``` co1 = \/ tv1 : eta1. r1 co2 = \/ tv2 : eta2. r2 ``` We would like to optimize `co1; co2` so we push transitivity inside forall. It should be ``` \/tv1 : (eta1;eta2). (r1; r2[tv2 |-> tv1 |> eta1]) ``` It is implemented in the ForAllCo case in opt_trans_rule in OptCoercion. However current implementation is not right: ``` r2' = substCoWithUnchecked [tv2] [TyVarTy tv1] r2 -- ill-kinded! ``` This patch corrects it to be ``` r2' = substCoWithUnchecked [tv2] [mkCastTy (TyVarTy tv1) eta1] r2 ``` Test Plan: validate Reviewers: bgamari, goldfire, RyanGlScott Reviewed By: RyanGlScott Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15453 Differential Revision: https://phabricator.haskell.org/D5018 (cherry picked from commit 11de4380c2f16f374c6e8fbacf8dce00376e7efb) - - - - - c9be8596 by Moritz Angermann at 2018-08-01T19:40:45-04:00 linker: Nub rpaths When compiling and linking files in `ghci`, we keep adding rpath arguments to the linker command invoation. If those are identical we should `nub` them out. Otherwise we not only risk overflowing the argument limit, but also embed huge amounts of identical rpath values into the dynamic library, eventually leading to the overflow of the load command size limit, due to the number of rpath entries alone. A further improvement could be to pass `-Xlinker -dead_strip_dylibs`; that however might be stipping too aggressively, and potentially lead to missing symbols? For the time being I suggest to only do the nubbing and if need be to provide -Wl,-dead_strip_dylibs when invoking ghci. Test Plan: ./validate Reviewers: bgamari, hvr Reviewed By: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15446 Differential Revision: https://phabricator.haskell.org/D5021 (cherry picked from commit b803c40608119469bdda330cb88860be2cbed25b) - - - - - a97ead78 by Vladislav Zavialov at 2018-08-01T19:40:45-04:00 Fix #15415 and simplify tcWildCardBinders Test Plan: Validate Reviewers: goldfire, simonpj, bgamari Reviewed By: simonpj Subscribers: RyanGlScott, rwbarton, thomie, carter GHC Trac Issues: #15415 Differential Revision: https://phabricator.haskell.org/D5022 (cherry picked from commit 120cc9f85ee1120072eb44c5bf37ac3055883605) - - - - - ebd773a0 by Ryan Scott at 2018-08-01T19:41:21-04:00 Fix #15450 by refactoring checkEmptyCase' `checkEmptyCase'` (the code path for coverage-checking `EmptyCase` expressions) had a fair bit of code duplication from the code path for coverage-checking non-`EmptyCase` expressions, and to make things worse, it behaved subtly different in some respects (for instance, emitting different warnings under unsatisfiable constraints, as shown in #15450). This patch attempts to clean up both this discrepancy and the code duplication by doing the following: * Factor out a `pmInitialTmTyCs` function, which returns the initial set of term and type constraints to use when beginning coverage checking. If either set of constraints is unsatisfiable, we use an empty set in its place so that we can continue to emit as many warnings as possible. (The code path for non-`EmptyCase` expressions was doing this already, but not the code path for `EmptyCase` expressions, which is the root cause of #15450.) Along the way, I added a `Note` to explain why we do this. * Factor out a `pmIsSatisfiable` constraint which checks if a set of term and type constraints are satisfiable. This does not change any existing behavior; this is just for the sake of deduplicating code. Test Plan: make test TEST=T15450 Reviewers: simonpj, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15450 Differential Revision: https://phabricator.haskell.org/D5017 (cherry picked from commit 7f3cb50dd311caefb536d582f1e3d1b33d6650f6) - - - - - ff086cc1 by Ben Gamari at 2018-08-01T20:35:19-04:00 Bump Cabal submodule to 2.4 - - - - - 59f38587 by Richard Eisenberg at 2018-08-01T20:54:11-04:00 Remove the type-checking knot. Bug #15380 hangs because a knot-tied TyCon ended up in a kind. Looking at the code in tcInferApps, I'm amazed this hasn't happened before! I couldn't think of a good way to fix it (with dependent types, we can't really keep types out of kinds, after all), so I just went ahead and removed the knot. This was remarkably easy to do. In tcTyVar, when we find a TcTyCon, just use it. (Previously, we looked up the knot-tied TyCon and used that.) Then, during the final zonk, replace TcTyCons with the real, full-blooded TyCons in the global environment. It's all very easy. The new bit is explained in the existing Note [Type checking recursive type and class declarations] in TcTyClsDecls. Naturally, I removed various references to the knot and the zonkTcTypeInKnot (and related) functions. Now, we can print types during type checking with abandon! NB: There is a teensy error message regression with this patch, around the ordering of quantified type variables. This ordering problem is fixed (I believe) with the patch for #14880. The ordering affects only internal variables that cannot be instantiated with any kind of visible type application. There is also a teensy regression around the printing of types in TH splices. I think this is really a TH bug and will file separately. Test case: dependent/should_fail/T15380 (cherry picked from commit f8618a9b15177ee8c84771b927cb3583c9cd8408) - - - - - 42c51e2f by Simon Peyton Jones at 2018-08-01T20:54:51-04:00 Small refactor in desugar of pattern matching In reviewing Phab:D4968 for Trac #15385 I saw a small but simple refactor to avoid unnecessary work in the desugarer. This patch just arranges to call matchSinglePatVar v ... rather than matchSinglePat (Var v) ... The more specialised function already existed, as match_single_pat_var I also added more comments about decideBangHood (cherry picked from commit 45cfe6514afb47c26883687e25ff7eb1e40c5a52) - - - - - e649085b by Ryan Scott at 2018-08-01T20:55:32-04:00 Fix #15385 by using addDictsDs in matchGuards When coverage checking pattern-matches, we rely on the call sites in the desugarer to populate the local dictionaries and term evidence in scope using `addDictsDs` and `addTmCsDs`. But it turns out that only the call site for desugaring `case` expressions was actually doing this properly. In another part of the desugarer, `matchGuards` (which handles pattern guards), it did not update the local dictionaries in scope at all, leading to #15385. Fixing this is relatively straightforward: just augment the `BindStmt` case of `matchGuards` to use `addDictsDs` and `addTmCsDs`. Accomplishing this took a little bit of import/export tweaking: * We now need to export `collectEvVarsPat` from `HsPat.hs`. * To avoid an import cycle with `Check.hs`, I moved `isTrueLHsExpr` from `DsGRHSs.hs` to `DsUtils.hs`, which resides lower on the import chain. Test Plan: make test TEST=T15385 Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15385 Differential Revision: https://phabricator.haskell.org/D4968 (cherry picked from commit 9d388eb83e797fd28e14868009c4786f3f1a8aa6) - - - - - 6a7cb806 by Simon Peyton Jones at 2018-08-01T22:42:22-04:00 Treat isConstraintKind more consistently It turned out that we were not being consistent about our use of isConstraintKind. It's delicate, because the typechecker treats Constraint and Type as /distinct/, whereas they are the /same/ in the rest of the compiler (Trac #11715). And had it wrong, which led to Trac #15412. This patch does the following: * Rename isConstraintKind to tcIsConstraintKind returnsConstraintKind to tcReturnsConstraintKind to emphasise that they use the 'tcView' view of types. * Move these functions, and some related ones (tcIsLiftedTypeKind), from Kind.hs, to group together in Type.hs, alongside isPredTy. It feels very unsatisfactory that these 'tcX' functions live in Type, but it happens because isPredTy is called later in the compiler too. But it's a consequence of the 'Constraint vs Type' dilemma. (cherry picked from commit c5d31df70b16dc346b5860077c8bbe585ddb7a78) - - - - - e86db0d5 by Christiaan Baaij at 2018-08-01T22:42:22-04:00 Plugin dependency information is stored separately We need to store the used plugins so that we recompile a module when a plugin that it uses is recompiled. However, storing the `ModuleName`s of the plugins used by a module in the `dep_mods` field made the rest of GHC think that they belong in the HPT, causing at least the issues reported in #15234 We therefor store the `ModuleName`s of the plugins in a new field, `dep_plgins`, which is only used the the recompilation logic. Reviewers: mpickering, bgamari Reviewed By: mpickering, bgamari Subscribers: alpmestan, rwbarton, thomie, carter GHC Trac Issues: #15234 Differential Revision: https://phabricator.haskell.org/D4937 (cherry picked from commit 52065e95c6df89d0048c6e3f35d6cc26ce8246f9) - - - - - 588364c3 by Matthías Páll Gissurarson at 2018-08-01T22:45:04-04:00 Clone relevant constraints to avoid side-effects on HoleDests. Fixes #15370. Summary: When looking for valid hole fits, the constraints relevant to the hole may sometimes contain a HoleDest. Previously, these were not cloned, which could cause the filling of filled coercion hole being, which would cause an assert to fail. This is now fixed. Test Plan: Regression test included. Reviewers: simonpj, bgamari, goldfire Reviewed By: simonpj Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15370 Differential Revision: https://phabricator.haskell.org/D5004 (cherry picked from commit 0dc86f6bc454253969dedc31bed477eded4cf82d) - - - - - 48fe84e2 by Krzysztof Gogolewski at 2018-08-03T16:18:24-04:00 fixup! Disable T10962 on llvm for now (cherry picked from commit a606750b36862367d038813f9fe7170f93c36222) - - - - - d53e51ff by Ben Gamari at 2018-08-06T18:23:35-04:00 Bump Cabal submodule - - - - - e384b96d by Ben Gamari at 2018-08-06T18:23:35-04:00 Bump binary submodule (cherry picked from commit 3110428dd63a2014fe131cb2abff192570cc89e9) - - - - - 751febe4 by Ben Gamari at 2018-08-06T18:23:35-04:00 Bump filepath submodule (cherry picked from commit 9472db132d2e455c106778c7daa30af71fbf6fee) - - - - - 26b6ffb3 by Herbert Valerio Riedel at 2018-08-06T18:23:35-04:00 Turn on MonadFail desugaring by default This contains two commits: ---- Make GHC's code-base compatible w/ `MonadFail` There were a couple of use-sites which implicitly used pattern-matches in `do`-notation even though the underlying `Monad` didn't explicitly support `fail` This refactoring turns those use-sites into explicit case discrimations and adds an `MonadFail` instance for `UniqSM` (`UniqSM` was the worst offender so this has been postponed for a follow-up refactoring) --- Turn on MonadFail desugaring by default This finally implements the phase scheduled for GHC 8.6 according to https://prime.haskell.org/wiki/Libraries/Proposals/MonadFail#Transitiona lstrategy This also preserves some tests that assumed MonadFail desugaring to be active; all ghc boot libs were already made compatible with this `MonadFail` long ago, so no changes were needed there. Test Plan: Locally performed ./validate --fast Reviewers: bgamari, simonmar, jrtc27, RyanGlScott Reviewed By: bgamari Subscribers: bgamari, RyanGlScott, rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D5028 - - - - - f4e54330 by Matthías Páll Gissurarson at 2018-08-06T18:23:35-04:00 Fix the TcLevel not being set correctly when finding valid hole fits Summary: This fixes the problem revealed by a new assert as it relates to valid hole fits. However, tests `T10384`, `T14040a` and `TcStaticPointersFail02` still fail the assert, but they are unrelated to valid hole fits. Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, thomie, carter GHC Trac Issues: #15384 Differential Revision: https://phabricator.haskell.org/D4994 (cherry picked from commit b202e7a48401bd8e805a92dcfe5ea059cbd8e41c) - - - - - f6e889fd by vrom911 at 2018-08-06T18:23:35-04:00 Refactor printMinimalImports (#15439) Summary: Split into getMinimalImports and printMinimalImports. Export both functions from RnNames module. Reviewers: bgamari, mpickering Reviewed By: mpickering Subscribers: mpickering, rwbarton, carter GHC Trac Issues: #15439 Differential Revision: https://phabricator.haskell.org/D5045 (cherry picked from commit 73683f143d352343b00b1ab4f3abeb38b81794be) - - - - - 9f1b1abe by Ben Gamari at 2018-08-06T18:23:35-04:00 circleci: Don't build validate-x86_64-linux-debug unregisterised Summary: This was a cut-and-paste error. Reviewers: alpmestan Reviewed By: alpmestan Subscribers: alpmestan, rwbarton, thomie, carter GHC Trac Issues: #15466 Differential Revision: https://phabricator.haskell.org/D5037 (cherry picked from commit f355b72113e646cb3785937f5506ee4c084c127f) - - - - - 87a79e39 by Ben Gamari at 2018-08-06T18:32:44-04:00 rts: Ensure that the_gc_thread is aligned Since we cast this to a gc_thread the compiler may assume that it's aligned. Make sure that this is so. Fixes #15482. (cherry picked from commit c6cc93bca69abc258513af8cf2370b14e70fd8fb) - - - - - b4302fd5 by Alexander Biehl at 2018-08-06T18:32:44-04:00 Add since annotation to GHC.ByteOrder (cherry picked from commit 6fb2620dbc420c976dc9da90b0efc6eae533ebff) (cherry picked from commit 8b357c6ad17bfe802c4a818b0cd7440bced024a3) - - - - - 6369aab2 by Mathieu Boespflug at 2018-08-06T18:32:44-04:00 docs: Fix wrong module name in hsig example In the module signatures section, two modules were defined, `Str` and `A`, but `A` was importing `Text`, not `Str`. (cherry picked from commit 26ab3635ca342c88310321d7f310f1c12c23ec4c) (cherry picked from commit ce9b459de30e15f2d65518ca12974a692256d477) - - - - - eefac048 by Simon Jakobi at 2018-08-06T18:32:44-04:00 Unhide GHC.List for haddock The unhidden module GHC.OldList recommends using GHC.List instead. In consequence we should also have haddocks for GHC.List. (cherry picked from commit e3df129c8bf4c35693d01ea66238882f3e3b6fe1) (cherry picked from commit 672f177300b2df1b8a4cd49d560a6fd6da2415d2) - - - - - 8edc4b4b by Maximilian Tagher at 2018-08-06T18:32:45-04:00 [docs] Add missed specialisations warnings to list of those not enabled by -Wall Enabling `-Weverything` does enable those warnings. (cherry picked from commit b062bd10a88ea407ae91610f822f0c352909bcce) (cherry picked from commit 24b76d1bef7e61791907fbd063f85643eeb1211a) - - - - - 2bbff4dc by Krzysztof Gogolewski at 2018-08-06T18:32:45-04:00 Testsuite driver: fix encoding issue when calling ghc-pkg Summary: In Python 3, subprocess.communicate() returns a pair of bytes, which need to be decoded. In runtests.py, we were just calling str() instead, which converts b'x' to "b'x'". As a result, the loop that was checking pkginfo for lines starting with 'library-dirs' couldn't work. Reviewers: bgamari, thomie, Phyx Reviewed By: thomie Subscribers: Phyx, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5046 (cherry picked from commit 36a4c19494e2cb7e968f1d0e0c09926a660e1a56) - - - - - 5140b23a by Ben Gamari at 2018-08-07T09:22:24-04:00 Bump hadrian submodule - - - - - d0923219 by Ben Gamari at 2018-08-07T13:26:09-04:00 Bump binary submodule to 0.8.6.0 This is actually a decrease in the version number since a bump to 0.10 wasn't actually necessary. (cherry picked from commit 960a7d17a79417300ee81e884e867bf3de4e535b) - - - - - 68268150 by Ben Gamari at 2018-08-07T20:10:01-04:00 Bump Cabal submodule - - - - - 6328e89f by Ben Gamari at 2018-08-08T23:17:39-04:00 Allow arbitrary options to be passed to tar compression (cherry picked from commit 4d6dfc35c06abb747de318ada2f27985c9369a6d) - - - - - d414a115 by Ben Gamari at 2018-08-08T23:17:39-04:00 circleci: Fix documentation building (cherry picked from commit 9f937142f67ccf1c8bff9bb809539deca39a7a6f) - - - - - 1741e858 by Ben Gamari at 2018-08-08T23:18:20-04:00 circleci: Reduce build verbosity (cherry picked from commit 5be646f251b25c22ba24ad2a4eb5af66b3f95d74) - - - - - e734b8c5 by Ben Gamari at 2018-08-08T23:18:21-04:00 circleci: Reduce compression effort to 3 (cherry picked from commit 60e12f26a28ce4ed0ecb905baef207a0388947f1) - - - - - 38932150 by Viktor Dukhovni at 2018-08-09T09:23:20-04:00 Add FreeBSD amd64 LLVM target (cherry picked from commit 396aac4c65a47b6252e0a73d2a3066e924d53f11) - - - - - fd7cedc8 by Ben Gamari at 2018-08-09T12:31:59-04:00 Bump unix submodule - - - - - 1a0a971b by Ben Gamari at 2018-08-09T12:31:59-04:00 testsuite: Bump for unix 2.7 - - - - - da117270 by Ben Gamari at 2018-08-10T09:21:05-04:00 Revert "rts: Ensure that the_gc_thread is aligned" This reverts commit 87a79e394013e5f722496900227b126015d0d780. - - - - - 15b53479 by Ben Gamari at 2018-08-11T12:00:44-04:00 Bump parsec submodule - - - - - 13105a1a by Christiaan Baaij at 2018-08-19T08:31:46-04:00 Filter plugin dylib locations Summary: Previously we just created a cartesian product of the library paths of the plugin package and the libraries of the package. Of course, some of these combinations result in a filepath of a file doesn't exists, leading to #15475. Instead of making `haskFile` return Nothing in case a file doesn't exist (which would hide errors), we look at all the possible dylib locations and ensure that at least one of those locations is an existing file. If the list turns out to be empty however, we panic. Reviewers: mpickering, bgamari Reviewed By: mpickering Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15475 Differential Revision: https://phabricator.haskell.org/D5048 (cherry picked from commit b324c5624432f2c3d5b0a689fdff75a1ccc563f5) - - - - - fb8b2cb1 by Ryan Scott at 2018-08-19T08:32:10-04:00 Fix #15527 by pretty-printing an RdrName prefixly Summary: When `(.) @Int` is used without enabling `TypeApplications`, the resulting error message will pretty-print the (symbolic) `RdrName` `(.)`. However, it does so without parenthesizing it, which causes the pretty-printed expression to appear as `. at Int`. Yuck. Since the expression in a type application will always be prefix, we can fix this issue by using `pprPrefixOcc` instead of plain ol' `ppr`. Test Plan: make test TEST=T15527 Reviewers: bgamari, monoidal, simonpj Reviewed By: monoidal, simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15527 Differential Revision: https://phabricator.haskell.org/D5071 (cherry picked from commit 5238f204482ac7f05f4e2d2e92576288cc00d42d) - - - - - 033d6ac7 by Zubin Duggal at 2018-08-19T08:32:19-04:00 Check if files are same in combineSrcSpans Summary: If this is not checked, SrcSpans are sometimes mangled by CPP. Test Plan: ./validate Reviewers: bgamari, dfeuer Reviewed By: bgamari Subscribers: dfeuer, rwbarton, thomie, carter GHC Trac Issues: #15279 Differential Revision: https://phabricator.haskell.org/D4866 (cherry picked from commit f7f9820e8f5601e9a072e504f3d772fd78df6700) - - - - - beca6421 by Ben Gamari at 2018-08-20T15:04:31-04:00 Bump stm submodule - - - - - 2d308da2 by Ryan Scott at 2018-08-21T16:35:22-04:00 Be mindful of GADT tyvar order when desugaring record updates After commit ef26182e2014b0a2a029ae466a4b121bf235e4e4, the type variable binders in GADT constructor type signatures are now quantified in toposorted order, instead of always having all the universals before all the existentials. Unfortunately, that commit forgot to update some code (which was assuming the latter scenario) in `DsExpr` which desugars record updates. This wound up being the cause of #15499. This patch makes up for lost time by desugaring record updates in a way such that the desugared expression applies type arguments to the right-hand side constructor in the correct order—that is, the order in which they were quantified by the user. Test Plan: make test TEST=T15499 Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15499 Differential Revision: https://phabricator.haskell.org/D5060 (cherry picked from commit 63b6a1d44849c479d2a7cb59211f5c64d133bc62) - - - - - b81fc821 by Simon Peyton Jones at 2018-08-21T16:40:02-04:00 Set strictness correctly for JoinIds We were failing to keep correct strictness info when eta-expanding join points; Trac #15517. The situation was something like \q v eta -> let j x = error "blah -- STR Lx bottoming! in case y of A -> j x eta B -> blah C -> j x eta So we spot j as a join point and eta-expand it. But we must also adjust the stricness info, else it vlaimes to bottom after one arg is applied but now it has become two. I fixed this in two places: - In CoreOpt.joinPointBinding_maybe, adjust strictness info - In SimplUtils.tryEtaExpandRhs, return consistent values for arity and bottom-ness (cherry picked from commit ce6ce788251b6102f5c1b878ffec53ba7ad678b5) - - - - - c3e50b05 by Ben Gamari at 2018-08-21T19:03:43-04:00 rts: Align the_gc_thread to 64 bytes In a previous attempt (c6cc93bca69abc258513af8cf2370b14e70fd8fb) I had tried aligning to 8 bytes under the assumption that the problem was that the_gc_thread, a StgWord8[], wasn't being aligned to 8-bytes as the gc_thread struct would expect. However, we actually need even stronger alignment due to the alignment attribute attached to gen_workspace, which claims it should be aligned to a 64-byte boundary. This fixes #15482. Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15482 Differential Revision: https://phabricator.haskell.org/D5052 (cherry picked from commit 68a1fc29b4bb3eae54e4d96c9aec20e700040f34) - - - - - 767f5660 by Bodigrim at 2018-08-23T15:16:21-04:00 Fix gcdExtInteger (trac#15350) (cherry picked from commit 7c207c86ab0de955ebec70eeeb366ba0d94acc4a) - - - - - c53a9f73 by DavidEichamnn at 2018-08-23T15:16:22-04:00 Correct limb length and assertion for gcdExtInteger Reviewers: hvr, bgamari, monoidal Reviewed By: monoidal Subscribers: monoidal, rwbarton, thomie, carter GHC Trac Issues: #15350 Differential Revision: https://phabricator.haskell.org/D5042 (cherry picked from commit c331592130ef592b92084e7417581a4039bfa7d2) - - - - - 18cb44df by Alec Theriault at 2018-08-23T15:16:22-04:00 Explicitly tell 'getNameToInstances' mods to load Calculating which modules to load based on the InteractiveContext means maintaining a potentially very large GblRdrEnv. In Haddock's case, it is much cheaper (from a memory perspective) to just keep track of which modules interfaces we want loaded then hand these off explicitly to 'getNameToInstancesIndex'. Bumps haddock submodule. Reviewers: alexbiehl, bgamari Reviewed By: alexbiehl Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D5003 (cherry picked from commit c971e1193fa44bb507d1806d5bb61768670dc912) - - - - - 7c819cbe by Ben Gamari at 2018-08-23T15:48:58-04:00 testsuite: Add (broken) test for #15473 (cherry picked from commit 5487f305d9dea298f0822082389d8a0225956c55) - - - - - d3ce8842 by Simon Peyton Jones at 2018-08-23T16:19:37-04:00 Turn infinite loop into a panic In these two functions * TcIface.toIfaceAppTyArgsX * Type.piResultTys we take a type application (f t1 .. tn) and try to find its kind. It turned out that, if (f t1 .. tn) was ill-kinded the function would go into an infinite loop. That's not good: it caused the loop in Trac #15473. This patch doesn't fix the bug in #15473, but it does turn the loop into a decent panic, which is a step forward. (cherry picked from commit db6f1d9cfc74690798645a7cc5b25040c36bb35d) - - - - - 047c17a4 by Simon Peyton Jones at 2018-08-23T18:39:34-04:00 Fix a typo in TcValidity.checkFamInstRhs In error message generation we were using the wrong type constructor in inst_head. Result: the type became ill-kinded, and that sent the compiler into a loop. A separate patch fixes the loop. This patch fixes the actual bug -- Trac #15473. I also improved the "occurs more often" error message a bit. But it's still pretty terrible: * Variable ‘a’ occurs more often in the type family application ‘Undefined’ than in the instance head ‘LetInterleave xs t ts is y z’ It looks like nonsense, but all becomes clear if you use -fprint-explicit-kinds. Really we should fix this by spotting when invisible arguments are involved and at least suggesting -fprint-explicit-kinds. (cherry picked from commit 8c7f90abcc1e8f9f29b751f23174e8db89ba6983) - - - - - 02829747 by Simon Peyton Jones at 2018-08-23T18:39:34-04:00 Accommodate API change in transSuperClasses In this patch commit 6eabb6ddb7c53784792ee26b1e0657bde7eee7fb Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Tue Dec 15 14:26:13 2015 +0000 Allow recursive (undecidable) superclasses I changed (transSuperClasses p) to return only the superclasses of p, but not p itself. (Previously it always returned p as well.) The use of transSuperClasses in TcErrors.warnRedundantConstraints really needs 'p' in the result -- but I faild to fix this call site, and instead crippled the test for Trac #10100. This patch sets things right * Accomodates the API change * Re-enables T10100 * And thereby fixes Trac #11474 (cherry picked from commit 4293a80a3ea835412737911bcb2a6703e9af378b) - - - - - c69c9d39 by Simon Jakobi at 2018-08-23T18:39:34-04:00 --show-iface: Qualify all non-local names Summary: In order to disambiguate names from different modules, qualify all names that don't originate in the current module. Also update docs for QueryQualifyName Test Plan: validate Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, thomie, carter, tdammers GHC Trac Issues: #15269 Differential Revision: https://phabricator.haskell.org/D4852 (cherry picked from commit d42eef344a71990d12f27e88cdf10ba0b2a2f34b) - - - - - 89ad5fed by Ryan Scott at 2018-08-23T18:50:23-04:00 Suppress redundant givens during error reporting Summary: When GHC reports that it cannot solve a constraint in error messages, it often reports what given constraints it has in scope. Unfortunately, sometimes redundant constraints (like `* ~ *`, from #15361) can sneak in. The fix is simple: blast away these redundant constraints using `mkMinimalBySCs`. Test Plan: make test TEST=T15361 Reviewers: simonpj, bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #15361 Differential Revision: https://phabricator.haskell.org/D5002 (cherry picked from commit c552feea127d8ed8cbf4994a157c4bbe254b96c3) - - - - - e57a15d8 by Ryan Scott at 2018-08-23T18:50:28-04:00 Properly designate LambdaCase alts as CaseAlt in TH Summary: When `\case` expressions are parsed normally, their alternatives are marked as `CaseAlt` (which means that they are pretty-printed without a `\` character in front of them, unlike for lambda expressions). However, `\case` expressions created by way of Template Haskell (in `Convert`) inconsistently designated the case alternatives as `LambdaExpr`, causing them to be pretty-printed poorly (as shown in #15518). The fix is simple: use `CaseAlt` consistently. Test Plan: make test TEST=T15518 Reviewers: goldfire, bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15518 Differential Revision: https://phabricator.haskell.org/D5069 (cherry picked from commit 32008a9d0e09f0cc8899aa871d9a6b63fcc28a1a) - - - - - 768cc53d by David Feuer at 2018-08-23T18:50:28-04:00 Expose the StableName constructor * Move the definition of `StableName` from `System.Mem.StableName` to a new `GHC.StableName` module. * Expose the `StableName` data constructor from `GHC.StableName`. Once we have `UnliftedArray#`, this will enable `StableName`s to be stored in `UnliftedArray`s (from `primitive`) without unsafe coercions. Reviewers: hvr, bgamari, andrewthad, osa1 Reviewed By: osa1 Subscribers: osa1, rwbarton, carter GHC Trac Issues: #15535 Differential Revision: https://phabricator.haskell.org/D5078 (cherry picked from commit 9c4e6c6b1affd410604f8f76ecf56abfcc5cccb6) - - - - - e8f79c95 by Ben Gamari at 2018-09-07T07:18:19-04:00 Do a final pass over the changelogs - - - - - 3b998a93 by Ben Gamari at 2018-09-07T08:11:48-04:00 Bump Cabal submodule to 2.4.0.0 - - - - - d46dd452 by Ömer Sinan Ağacan at 2018-09-07T08:11:48-04:00 Fix a race between GC threads in concurrent scavenging While debugging #15285 I realized that free block lists (free_list in BlockAlloc.c) get corrupted when multiple scavenge threads allocate and release blocks concurrently. Here's a picture of one such race: Thread 2 (Thread 32573.32601): #0 check_tail (bd=0x940d40 <stg_TSO_info>) at rts/sm/BlockAlloc.c:860 #1 0x0000000000928ef7 in checkFreeListSanity () at rts/sm/BlockAlloc.c:896 #2 0x0000000000928979 in freeGroup (p=0x7e998ce02880) at rts/sm/BlockAlloc.c:721 #3 0x0000000000928a17 in freeChain (bd=0x7e998ce02880) at rts/sm/BlockAlloc.c:738 #4 0x0000000000926911 in freeChain_sync (bd=0x7e998ce02880) at rts/sm/GCUtils.c:80 #5 0x0000000000934720 in scavenge_capability_mut_lists (cap=0x1acae80) at rts/sm/Scav.c:1665 #6 0x000000000092b411 in gcWorkerThread (cap=0x1acae80) at rts/sm/GC.c:1157 #7 0x000000000090be9a in yieldCapability (pCap=0x7f9994e69e20, task=0x7e9984000b70, gcAllowed=true) at rts/Capability.c:861 #8 0x0000000000906120 in scheduleYield (pcap=0x7f9994e69e50, task=0x7e9984000b70) at rts/Schedule.c:673 #9 0x0000000000905500 in schedule (initialCapability=0x1acae80, task=0x7e9984000b70) at rts/Schedule.c:293 #10 0x0000000000908d4f in scheduleWorker (cap=0x1acae80, task=0x7e9984000b70) at rts/Schedule.c:2554 #11 0x000000000091a30a in workerStart (task=0x7e9984000b70) at rts/Task.c:444 #12 0x00007f99937fa6db in start_thread (arg=0x7f9994e6a700) at pthread_create.c:463 #13 0x000061654d59f88f in clone () at ../sysdeps/unix/sysv/linux/x86_64/clone.S:95 Thread 1 (Thread 32573.32573): #0 checkFreeListSanity () at rts/sm/BlockAlloc.c:887 #1 0x0000000000928979 in freeGroup (p=0x7e998d303540) at rts/sm/BlockAlloc.c:721 #2 0x0000000000926f23 in todo_block_full (size=513, ws=0x1aa8ce0) at rts/sm/GCUtils.c:264 #3 0x00000000009583b9 in alloc_for_copy (size=513, gen_no=0) at rts/sm/Evac.c:80 #4 0x000000000095850d in copy_tag_nolock (p=0x7e998c675f28, info=0x421d98 <Main_Large_con_info>, src=0x7e998d075d80, size=513, gen_no=0, tag=1) at rts/sm/Evac.c:153 #5 0x0000000000959177 in evacuate (p=0x7e998c675f28) at rts/sm/Evac.c:715 #6 0x0000000000932388 in scavenge_small_bitmap (p=0x7e998c675f28, size=1, bitmap=0) at rts/sm/Scav.c:271 #7 0x0000000000934aaf in scavenge_stack (p=0x7e998c675f28, stack_end=0x7e998c676000) at rts/sm/Scav.c:1908 #8 0x0000000000934295 in scavenge_one (p=0x7e998c66e000) at rts/sm/Scav.c:1466 #9 0x0000000000934662 in scavenge_mutable_list (bd=0x7e998d300440, gen=0x1b1d880) at rts/sm/Scav.c:1643 #10 0x0000000000934700 in scavenge_capability_mut_lists (cap=0x1aaa340) at rts/sm/Scav.c:1664 #11 0x00000000009299b6 in GarbageCollect (collect_gen=0, do_heap_census=false, gc_type=2, cap=0x1aaa340, idle_cap=0x1b38aa0) at rts/sm/GC.c:378 #12 0x0000000000907a4a in scheduleDoGC (pcap=0x7ffdec5b5310, task=0x1b36650, force_major=false) at rts/Schedule.c:1798 #13 0x0000000000905de7 in schedule (initialCapability=0x1aaa340, task=0x1b36650) at rts/Schedule.c:546 #14 0x0000000000908bc4 in scheduleWaitThread (tso=0x7e998c0067c8, ret=0x0, pcap=0x7ffdec5b5430) at rts/Schedule.c:2537 #15 0x000000000091b5a0 in rts_evalLazyIO (cap=0x7ffdec5b5430, p=0x9c11f0, ret=0x0) at rts/RtsAPI.c:530 #16 0x000000000091ca56 in hs_main (argc=1, argv=0x7ffdec5b5628, main_closure=0x9c11f0, rts_config=...) at rts/RtsMain.c:72 #17 0x0000000000421ea0 in main () In particular, dbl_link_onto() which is used to add a freed block to a doubly-linked free list is not thread safe and corrupts the list when called concurrently. Note that thread 1 is to blame here as thread 2 is properly taking the spinlock. With this patch we now take the spinlock when freeing a todo block in GC, avoiding this race. Test Plan: - Tried slow validate locally: this patch does not introduce new failures. - circleci: https://circleci.com/gh/ghc/ghc-diffs/283 The test got killed because it took 5 hours but T7919 (which was previously failing on circleci) passed. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15285 Differential Revision: https://phabricator.haskell.org/D5115 (cherry picked from commit c6fbac6a6a69a2f4be89701b2c386ae53214f9a3) - - - - - aeb24707 by Ömer Sinan Ağacan at 2018-09-07T08:11:48-04:00 Skip eventlog tests in GHCi way Summary: (GHCi doesn't generate event logs) Test Plan: These tests were failing in GHCi way, they're now skipped in GHCi way as GHCi doesn't generate eventlogs Reviewers: bgamari, simonmar, maoe, alpmestan Reviewed By: alpmestan Subscribers: rwbarton, carter GHC Trac Issues: #15587 Differential Revision: https://phabricator.haskell.org/D5119 (cherry picked from commit c0e5087d01e2912f00feede6c259a2ee87685c90) - - - - - 21545666 by Krzysztof Gogolewski at 2018-09-07T08:11:48-04:00 Fix typo in 8.6.1 notes (cherry picked from commit 34b8e613606653187f1ffae36a83e33f0c673720) - - - - - f6595773 by Andrey Mokhov at 2018-09-07T08:11:48-04:00 Fix a constant folding rule Summary: One of the constant folding rules introduced in D2858 is: ``` (L y :-: v) :-: (L x :-: w) -> return $ mkL (y-x) `add` (w `add` v) ``` Or, after removing syntactic noise: `(y - v) - (x - w) ==> (y - x) + (w + v)`. This is incorrect, since the sign of `v` is changed from negative to positive. As a consequence, the following program prints `3` when compiled with `-O`: ``` -- This is just subtraction in disguise minus :: Int -> Int -> Int minus x y = (8 - y) - (8 - x) {-# NOINLINE minus #-} main :: IO () main = print (2 `minus` 1) ``` The correct rule is: `(y - v) - (x - w) ==> (y - x) + (w - v)`. This commit does the fix. I haven't found any other issues with the constant folding code, but it's difficult to be certain without some automated checking. Reviewers: bgamari, tdammers Subscribers: hsyl20, tdammers, rwbarton, carter GHC Trac Issues: #15569 Differential Revision: https://phabricator.haskell.org/D5109 (cherry picked from commit 65eec9cfd4410c0e30b0ed06116c15f8ce3de49d) - - - - - 95b7b0a0 by chris-bacon at 2018-09-07T08:11:48-04:00 Fixed typo in exponent example (cherry picked from commit 36c1431d9d2d06049190cc0888dbfaee8e2179d6) - - - - - 76a23314 by Ben Gamari at 2018-09-07T08:11:48-04:00 rts: Handle SMALL_MUT_ARR_PTRS in retainer profilter Summary: These can be treated similarly to MUT_ARRY_PTRS. Fixes #15529. Reviewers: erikd, simonmar Reviewed By: simonmar Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15529 Differential Revision: https://phabricator.haskell.org/D5075 (cherry picked from commit 2cf98e2207421200fc73c25a08f6435859cdff92) - - - - - d2ac6e95 by Ben Gamari at 2018-09-12T19:26:35-04:00 template-haskell: Fix typo in changelog - - - - - 75d3415b by Simon Marlow at 2018-09-12T19:26:35-04:00 Fix gcCAFs() The test here should have been changed after D1106. It was harmless but we caught fewer GC'd CAFs than we should have. Test Plan: Using `nofib/imaginary/primes` compiled with `-debug`. Before: ``` > ./primes 100 +RTS -G1 -A32k -DG CAF gc'd at 0x0x7b0960 CAF gc'd at 0x0x788728 CAF gc'd at 0x0x790db0 CAF gc'd at 0x0x790de0 12 CAFs live CAF gc'd at 0x0x788880 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 547 CAF gc'd at 0x0x7995c8 13 CAFs live ``` After: ``` > ./primes 100 +RTS -G1 -A32k -DG CAF gc'd at 0x0x7b0960 CAF gc'd at 0x0x788728 CAF gc'd at 0x0x790db0 CAF gc'd at 0x0x790de0 12 CAFs live CAF gc'd at 0x0x788880 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 12 CAFs live 547 CAF gc'd at 0x0x7995c8 CAF gc'd at 0x0x790ea0 12 CAFs live ``` Reviewers: bgamari, osa1, erikd, noamz Reviewed By: bgamari Subscribers: rwbarton, thomie, carter Differential Revision: https://phabricator.haskell.org/D4963 (cherry picked from commit e431d75f8350f25159f9aaa49fe9a504e94bc0a4) - - - - - 279d69d3 by Ömer Sinan Ağacan at 2018-09-13T13:44:31-04:00 Revert incorrect STM wakeup optimisation Summary: (see the comments) Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5144 (cherry picked from commit 36740b4c346c619e31d24d6672caa6f4f7fea123) - - - - - c15d44f8 by Simon Marlow at 2018-09-13T13:44:31-04:00 Revert "Disable the SRT offset optimisation on MachO platforms" This reverts commit bf10456edaa03dc010821cd4c3d9f49cb11d89da. - - - - - d82e8af8 by Ben Gamari at 2018-09-13T13:44:31-04:00 Revert "Fix a bug in SRT generation" This reverts commit d424d4a46a729f8530e9273282d22b6b8f34daaa. - - - - - 25765469 by Ben Gamari at 2018-09-13T13:44:31-04:00 Revert "Fix retainer profiling after SRT overhaul" This reverts commit d78dde9ff685830bc9d6bb24a158eb31bb8a7028. - - - - - b0f06f53 by Ben Gamari at 2018-09-13T13:44:31-04:00 Revert "Comments and refactoring only" This reverts commit f2d27c1ad69321872a87a37144fe41e815301f5b. - - - - - 6f2596b4 by Ben Gamari at 2018-09-13T13:44:31-04:00 Revert "Merge FUN_STATIC closure with its SRT" This reverts commit 838b69032566ce6ab3918d70e8d5e098d0bcee02. - - - - - dee22948 by Ben Gamari at 2018-09-13T13:44:31-04:00 Revert "Save a word in the info table on x86_64" This reverts commit 2b0918c9834be1873728176e4944bec26271234a. - - - - - ceffd7fe by Ben Gamari at 2018-09-13T13:44:32-04:00 Revert "An overhaul of the SRT representation" This reverts commit eb8e692cab7970c495681e14721d05ecadd21581. - - - - - 8344588e by Ryan Scott at 2018-09-16T12:31:14-04:00 Fix #15502 by not casting to Int during TH conversion Summary: When turning an `IntegerL` to an `IntegralLit` during TH conversion, we were stupidly casting an `Integer` to an `Int` in order to determine how it should be pretty-printed. Unsurprisingly, this causes problems when the `Integer` doesn't lie within the bounds of an `Int`, as demonstrated in #15502. The fix is simple: don't cast to an `Int`. Test Plan: make test TEST=T15502 Reviewers: bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15502 Differential Revision: https://phabricator.haskell.org/D5089 (cherry picked from commit 7a3cda534d1447c813aa37cdd86e20b8d782cb02) - - - - - 83ca9bb2 by Simon Peyton Jones at 2018-09-16T12:31:17-04:00 canCFunEqCan: use isTcReflexiveCo (not isTcReflCo) As Trac #15577 showed, it was possible for a /homo-kinded/ constraint to trigger the /hetero-kinded/ branch of canCFunEqCan, and that triggered an infinite loop. The fix is easier, but there remains a deeper questions: why is the flattener producing giant refexive coercions? (cherry picked from commit 2e226a46c422c12f78dc3d3f62fe5a15e22bd986) - - - - - 2cdb2de1 by Ryan Scott at 2018-09-16T12:31:17-04:00 Fix #15550 by quoting RULE names during TH conversion Summary: When converting a `RuleP` to a GHC source `RuleD` during TH conversion, we were stupidly not double-quoting the name of the rule. Easily fixed. Test Plan: make test TEST=T15550 Reviewers: goldfire, bgamari, simonpj Reviewed By: simonpj Subscribers: simonpj, rwbarton, carter GHC Trac Issues: #15550 Differential Revision: https://phabricator.haskell.org/D5090 (cherry picked from commit 5e6cf2a9301a5473ff9c5319b96de941b1ad72dd) - - - - - ebc8ebf8 by Ryan Scott at 2018-09-16T12:31:17-04:00 Fix #15572 by checking for promoted names in ConT Summary: When converting `ConT`s to `HsTyVar`s in `Convert`, we were failing to account for the possibility of promoted data constructor names appearing in a `ConT`, which could result in improper pretty-printing results (as observed in #15572). The fix is straightforward: use `Promoted` instead of `NotPromoted` when the name of a `ConT` is a data constructor name. Test Plan: make test TEST=T15572 Reviewers: goldfire, bgamari, simonpj, monoidal Reviewed By: goldfire, simonpj Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15572 Differential Revision: https://phabricator.haskell.org/D5112 (cherry picked from commit c46a5f2002f6694ea58f79f505d57f3b7bd450e7) - - - - - bc907262 by Chaitanya Koparkar at 2018-09-16T12:31:17-04:00 Fix #10859 by using foldr1 while deriving Eq instances Summary: Previously, we were using foldl1 instead, which led to the derived code to be wrongly associated. Test Plan: ./validate Reviewers: RyanGlScott, nomeata, simonpj, bgamari Reviewed By: RyanGlScott, nomeata Subscribers: rwbarton, carter GHC Trac Issues: #10859 Differential Revision: https://phabricator.haskell.org/D5104 (cherry picked from commit 2d953a60489ba30433e5f2fe27c50aa9da75f802) - - - - - 2116932e by Ben Gamari at 2018-09-16T15:46:29-04:00 base: showEFloat: Handle negative precisions the same of zero precision Test Plan: Validate Reviewers: hvr, alpmestan Reviewed By: alpmestan Subscribers: rwbarton, carter GHC Trac Issues: #15509 Differential Revision: https://phabricator.haskell.org/D5083 (cherry picked from commit e71e341f87c055ecc01f85ddd8d7a2094dfa8e9a) - - - - - c5debde5 by Chaitanya Koparkar at 2018-09-16T15:46:29-04:00 Update hsc2hs submodule Test Plan: ./validate Reviewers: bgamari, hvr, RyanGlScott Reviewed By: RyanGlScott Subscribers: monoidal, rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5114 (cherry picked from commit ce240b3f998b68853c47ab131126eb9a245256c5) - - - - - f458bca3 by Ben Gamari at 2018-09-16T16:54:10-04:00 Bump stm submodule - - - - - a512f1e3 by Ben Gamari at 2018-09-16T16:56:33-04:00 Bump text submodule - - - - - 4b094c6d by Ben Gamari at 2018-09-16T16:56:33-04:00 Bump Cabal submodule - - - - - c4209ba8 by Ben Gamari at 2018-09-16T16:56:33-04:00 Bump deepseq submodule - - - - - 6cad8e31 by Krzysztof Gogolewski at 2018-09-18T09:27:42-04:00 Fix T15502 on 32-bit Summary: The expected output uses a hardcoded value for maxBound :: Int. This should fix one of circleci failures on i386. Test Plan: make test TEST=T15502 Reviewers: RyanGlScott, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, carter GHC Trac Issues: #15502 Differential Revision: https://phabricator.haskell.org/D5151 (cherry picked from commit ecbe26b6966a3a64f4e22e862370536b1dd4440f) - - - - - 058e3b7d by Ben Gamari at 2018-09-18T11:45:21-04:00 Revert "Revert "An overhaul of the SRT representation"" This reverts commit ceffd7fe3f310cb30fec870f768e8047af309d99. - - - - - 547ccb52 by Ben Gamari at 2018-09-18T11:45:22-04:00 Revert "Revert "Save a word in the info table on x86_64"" This reverts commit dee229487fccc6a994d4bb9c4ceda0903bec707b. - - - - - c0eb1abf by Ben Gamari at 2018-09-18T11:45:23-04:00 Revert "Revert "Merge FUN_STATIC closure with its SRT"" This reverts commit 6f2596b432a9915d648286195b48c48ccdd14a2c. - - - - - 5e6c217d by Ben Gamari at 2018-09-18T11:45:25-04:00 Revert "Revert "Comments and refactoring only"" This reverts commit b0f06f53761820167e8b2cda61bc8c3137a83f92. - - - - - b97867cd by Ben Gamari at 2018-09-18T11:45:25-04:00 Revert "Revert "Fix retainer profiling after SRT overhaul"" This reverts commit 25765469b312aa21422c635aa5852a69e29f24f1. - - - - - aef47537 by Ben Gamari at 2018-09-18T11:45:26-04:00 Revert "Revert "Fix a bug in SRT generation"" This reverts commit d82e8af82d4be11252294290564044ef956ec2a4. - - - - - f442bc6c by Ben Gamari at 2018-09-18T11:45:27-04:00 Revert "Revert "Disable the SRT offset optimisation on MachO platforms"" This reverts commit c15d44f8b3f00bfe152c2f9d3c6f60efd204fb23. - - - - - 28356f21 by Simon Marlow at 2018-09-18T11:49:05-04:00 Don't shortcut SRTs for static functions (#15544) Shortcutting the SRT for a static function can lead to resurrecting a static object at runtime, which violates assumptions in the GC. See comments for details. Test Plan: - manual testing (in progress) - validate Reviewers: osa1, bgamari, erikd Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15544 Differential Revision: https://phabricator.haskell.org/D5145 (cherry picked from commit a324dfdf3b505ea30d134dc8183d7b4bb441ced4) - - - - - 14e58640 by Takenobu Tani at 2018-09-19T10:29:13-04:00 users-guide: Fix code-block layout for QuantifiedConstraints Summary: Fix code-block layout for QuantifiedConstraints. [ci skip] Test Plan: build Reviewers: bgamari, monoidal Reviewed By: monoidal Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5121 (cherry picked from commit 43967c0c7d2d0110cfc5f9d64a7dab3a3dda8953) - - - - - be14113c by Ben Gamari at 2018-09-19T14:56:41-04:00 Bump stm submodule - - - - - 35959490 by Ben Gamari at 2018-09-19T15:30:39-04:00 users-guide: Fill out release highlights - - - - - 6f717bc6 by Ben Gamari at 2018-09-20T10:25:58-04:00 users-guide: Fix build with sphinx 1.8 It seems that both add_object_type and add_directive_to_domain both register a directive. Previously sphinx didn't seem to mind this but as of Sphinx 1.8 it crashes with an exception. (cherry picked from commit 4eebc8016f68719e1ccdf460754a97d1f4d6ef05) - - - - - 5ed9c861 by Zejun Wu at 2018-09-20T16:06:01-04:00 users_guide: fix sphinx error caused by non-explicit override Encouter following error when `make`: ``` Extension error: The 'ghc-flag' directive is already registered to domain std ``` as we register `ghc-flag` to `std` in `add_object_type` first and then overtride it in `add_directive_to_domain`. Test Plan: make -C utils/haddock/doc html SPHINX_BUILD=/usr/bin/sphinx-build Reviewers: austin, bgamari, patrickdoc Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5161 (cherry picked from commit 8c7d33a8ff6d3ea55b5dc8108d9441521af68ab8) - - - - - af0bf169 by Ben Gamari at 2018-09-20T18:18:23-04:00 user-guide: Allow build with sphinx < 1.8 Apparently the override argument to add_directive_to_domain was added in sphinx 1.8. (cherry picked from commit a257782f56e5e330349d4cc7db71e297d8396c67) - - - - - 0d2cdec7 by Ben Gamari at 2018-09-21T12:39:51-04:00 Set RELEASE=YES - - - - - f28b05b5 by Ben Gamari at 2018-09-21T16:05:30-04:00 circleci: Run cabal update with -v The cabal update command appears to be timing out with no output after 10 minutes. - - - - - 94cadce6 by Ben Gamari at 2018-10-05T18:47:47-04:00 Add testcase for #14251 (cherry picked from commit ba086ca72ee6c77abba685f3100ad513e38a1a87) - - - - - 4338398f by Ben Gamari at 2018-10-05T18:47:55-04:00 testsuite: Don't force run of llvm ways in T14251 This breaks if LLVM is not available. (cherry picked from commit d0d74842868ceb6716b7334eb6310f61f90023bf) - - - - - 73273be4 by Kavon Farvardin at 2018-10-05T18:48:16-04:00 Multiple fixes / improvements for LLVM backend - Fix for #13904 -- stop "trashing" callee-saved registers, since it is not actually doing anything useful. - Fix for #14251 -- fixes the calling convention for functions passing raw SSE-register values by adding padding as needed to get the values in the right registers. This problem cropped up when some args were unused an dropped from the live list. - Fixed a typo in 'readnone' attribute - Added 'lower-expect' pass to level 0 LLVM optimization passes to improve block layout in LLVM for stack checks, etc. Test Plan: `make test WAYS=optllvm` and `make test WAYS=llvm` Reviewers: bgamari, simonmar, angerman Reviewed By: angerman Subscribers: rwbarton, carter GHC Trac Issues: #13904, #14251 Differential Revision: https://phabricator.haskell.org/D5190 (cherry picked from commit adcb5fb47c0942671d409b940d8884daa9359ca4) - - - - - bf256ef2 by Ben Gamari at 2018-10-05T18:48:18-04:00 Bump array submodule - - - - - a2e3334c by Tamar Christina at 2018-10-05T18:48:18-04:00 Drop accidental write-attributes request Summary: The new filesystem code accidentally asks for write attributes permissions when doing read-only access. I believe this is what's causing the GHC 8.6.1 tarballs to fail when installed to a privileged location. I haven't been able to reproduce the issue yet, but this permission bit is wrong anyway. Test Plan: I'm still trying to workout how to test that this works, changing the permissions on the folder doesn't seem to reproduce the error on a tarball I made from before the change. Reviewers: bgamari, tdammers Reviewed By: bgamari Subscribers: tdammers, monoidal, rwbarton, carter GHC Trac Issues: #15667 Differential Revision: https://phabricator.haskell.org/D5177 (cherry picked from commit deceb21b7ec64ae60377addc2679692ca500b6ae) - - - - - 0af55c12 by Ryan Scott at 2018-10-05T18:48:18-04:00 Be mindful of GADT tyvar order when desugaring record updates After commit ef26182e2014b0a2a029ae466a4b121bf235e4e4, the type variable binders in GADT constructor type signatures are now quantified in toposorted order, instead of always having all the universals before all the existentials. Unfortunately, that commit forgot to update some code (which was assuming the latter scenario) in `DsExpr` which desugars record updates. This wound up being the cause of #15499. This patch makes up for lost time by desugaring record updates in a way such that the desugared expression applies type arguments to the right-hand side constructor in the correct order—that is, the order in which they were quantified by the user. Test Plan: make test TEST=T15499 Reviewers: simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15499 Differential Revision: https://phabricator.haskell.org/D5060 (cherry picked from commit 63b6a1d44849c479d2a7cb59211f5c64d133bc62) - - - - - facf7cce by Ben Gamari at 2018-10-07T11:54:13-04:00 users guide: Drop old release notes - - - - - 87266ea7 by Alec Theriault at 2018-10-12T23:30:38-04:00 Don't show constraint tuples in errors (#14907) Summary: This means that 'GHC.Classes.(%,%)' is no longer mentioned in error messages for things like class (a,b,c) -- outside of 'GHC.Classes' class (a,Bool) Test Plan: make TEST=T14907a && make TEST=T14907b Reviewers: RyanGlScott, bgamari Reviewed By: RyanGlScott Subscribers: rwbarton, carter GHC Trac Issues: #14907 Differential Revision: https://phabricator.haskell.org/D5172 (cherry picked from commit 9bfbc4e16d511678cffa9f7f76b369c8cfca7a66) - - - - - 377975e0 by Ben Gamari at 2018-10-12T23:31:00-04:00 testsuite: Add test for #15053 Reviewers: Phyx Reviewed By: Phyx Subscribers: Phyx, rwbarton, thomie, carter GHC Trac Issues: #15053 Differential Revision: https://phabricator.haskell.org/D4883 (cherry picked from commit f03f0d61bebe287e0df0254c175eb2f183d697aa) - - - - - 52304776 by roland at 2018-10-12T23:31:07-04:00 Compiler panic on invalid syntax (unterminated pragma) Summary: After a parse error in OPTIONS_GHC issue an error message instead of a compiler panic. Test Plan: make test TEST=T15053 Reviewers: Phyx, thomie, bgamari, monoidal, osa1 Reviewed By: Phyx, monoidal, osa1 Subscribers: tdammers, osa1, rwbarton, carter GHC Trac Issues: #15053 Differential Revision: https://phabricator.haskell.org/D5093 (cherry picked from commit df363a646b66f4dd13d63ec70f18e427cabc8878) - - - - - 10e3125d by Ömer Sinan Ağacan at 2018-10-12T23:32:22-04:00 Fix slop zeroing for AP_STACK eager blackholes in debug build As #15571 reports, eager blackholing breaks sanity checks as we can't zero the payload when eagerly blackholing (because we'll be using the payload after blackholing), but by the time we blackhole a previously eagerly blackholed object (in `threadPaused()`) we don't have the correct size information for the object (because the object's type becomes BLACKHOLE when we eagerly blackhole it) so can't properly zero the slop. This problem can be solved for AP_STACK eager blackholing (which unlike eager blackholing in general, is not optional) by zeroing the payload after entering the stack. This patch implements this idea. Fixes #15571. Test Plan: Previously concprog001 when compiled and run with sanity checks ghc-stage2 Mult.hs -debug -rtsopts ./Mult +RTS -DS was failing with Mult: internal error: checkClosure: stack frame (GHC version 8.7.20180821 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug thic patch fixes this panic. The test still panics, but it runs for a while before panicking (instead of directly panicking as before), and the new problem seems unrelated: Mult: internal error: ASSERTION FAILED: file rts/sm/Sanity.c, line 296 (GHC version 8.7.20180919 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug The new problem will be fixed in another diff. I also tried slow validate (which requires D5164): this does not introduce any new failures. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15571 Differential Revision: https://phabricator.haskell.org/D5165 (cherry picked from commit 66c17293648fd03a04aabfd807b3c8336e8f843a) - - - - - 4ab2f347 by Vladislav Zavialov at 2018-10-12T23:32:49-04:00 Add -Wstar-is-type to the User's Guide The -Wstar-is-type flag was added without documentation. Now it has documentation. Test Plan: Validate Reviewers: bgamari Reviewed By: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5203 (cherry picked from commit 07083fc44ebf3f0510ae1d71ae5c9c88c87ae1d8) - - - - - 51c44793 by Alec Theriault at 2018-10-13T00:03:37-04:00 GHCi should not filter instances involving cTuples Summary: See the new T12005 test case for an example of this. Test Plan: make TEST=T12005 Reviewers: bgamari, osa1 Reviewed By: osa1 Subscribers: osa1, rwbarton, carter GHC Trac Issues: #12005 Differential Revision: https://phabricator.haskell.org/D5182 (cherry picked from commit 21efbc7599e39ec93b8b13b7d7b84811226e6f6f) - - - - - a04ecd7b by Simon Marlow at 2018-10-13T13:26:18-04:00 Fix for recover with -fexternal-interpreter (#15418) Summary: When using -fexternal-interpreter, recover was not treating a Q compuation that simply registered an error with addErrTc as failing. Test Plan: New unit tests: * T15418 is the repro from in the ticket * TH_recover_warns is a new test to ensure that we're keeping warnings when the body of recover succeeds. Reviewers: bgamari, RyanGlScott, angerman, goldfire, erikd Subscribers: rwbarton, carter GHC Trac Issues: #15418 Differential Revision: https://phabricator.haskell.org/D5185 (cherry picked from commit d00c308633fe7d216d31a1087e00e63532d87d6d) - - - - - a22ee705 by Simon Peyton Jones at 2018-10-13T13:26:57-04:00 Do not mark CoVars as dead in the occur-anal For years we have been marking CoVars as dead, becuase we don't gather occurrence info from types. This is obviously wrong and caused Trac #15695. See Note [Do not mark CoVars as dead] in OccurAnal. (cherry picked from commit 02b303eed0170983921877801e57f55d012db301) - - - - - b11126fc by Ömer Sinan Ağacan at 2018-10-13T13:30:03-04:00 Fix dataToTag# argument evaluation See #15696 for more details. We now always enter dataToTag# argument (done in generated Cmm, in StgCmmExpr). Any high-level optimisations on dataToTag# applications are done by the simplifier. Looking at tag bits (instead of reading the info table) for small types is left to another diff. Incorrect test T14626 is removed. We no longer do this optimisation (see comment:44, comment:45, comment:60). Comments and notes about special cases around dataToTag# are removed. We no longer have any special cases around it in Core. Other changes related to evaluating primops (seq# and dataToTag#) will be pursued in follow-up diffs. Test Plan: Validates with three regression tests Reviewers: simonpj, simonmar, hvr, bgamari, dfeuer Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15696 Differential Revision: https://phabricator.haskell.org/D5201 (cherry picked from commit ac977688523e5d77eb6f041f043552410b0c21da) - - - - - f7b1ee96 by Ben Gamari at 2018-10-15T22:23:49-04:00 base: Fill in TBAs in changelog I've added a check in my release script to ensure that this doesn't happen in the future. (cherry picked from commit 2605458930f2d79738fab4437f10793448d4232c) - - - - - 3e050064 by Simon Peyton Jones at 2018-10-17T14:46:22-04:00 Fail fast on pattern synonyms We were recovering too eagerly from errors in pattern-synonym type inference, leading to a cascade of confusing follow up errors (Trac #15685, #15692). The underlying issue is that a pattern synonym should have a closed, fixed type, with no unification variables in it. But it wasn't! Fixing this made me change the interface to simplifyInfer slightly. Instead of /emitting/ a residual implication constraint, it now /returns/ it, so that the caller can decide what to do. (cherry picked from commit 9ebfa03d9e9cbf79f698b5d4bd39e799e4e9a02c) - - - - - 334be779 by Ben Gamari at 2018-10-17T14:46:22-04:00 Bump haddock submodule - - - - - ba5d0a48 by Richard Eisenberg at 2018-10-17T14:46:22-04:00 Fix #15761 by adding parens This was just a pretty-printer infelicity. Fixed now. Test case: printer/T15761 (cherry picked from commit 38c28c1a8bb129141e533866700e7318314f32c1) - - - - - 578012be by Ben Gamari at 2018-10-17T15:31:36-04:00 circleci: Build with in-tree GMP on Darwin Fixes #15404. - - - - - 6f590e9c by Ben Gamari at 2018-10-17T18:39:25-04:00 Bump version to 8.6.2 - - - - - 093bbff2 by Ben Gamari at 2018-10-24T14:14:18-04:00 Bump hsc2hs submodule - - - - - 2e23e1c7 by Kavon Farvardin at 2018-10-28T13:32:30-04:00 Fix for T14251 on ARM We now calculate the SSE register padding needed to fix the calling convention in LLVM in a robust way: grouping them by whether registers in that class overlap (with the same class overlapping itself). My prior patch assumed that no matter the platform, physical register Fx aliases with Dx, etc, for our calling convention. This is unfortunately not the case for any platform except x86-64. Test Plan: Only know how to test on x86-64, but it should be tested on ARM with: `make test WAYS=llvm && make test WAYS=optllvm` Reviewers: bgamari, angerman Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15780, #14251, #15747 Differential Revision: https://phabricator.haskell.org/D5254 (cherry picked from commit c36a2b596a6ba9d7a0a80df01b3c041720c727ca) - - - - - 38618f74 by Zejun Wu at 2018-10-28T13:32:38-04:00 Fix rare undefined asm temp end label error in x86 Summary: Encountered assembly error due to undefined label `.LcaDcU_info_end` for following code generated by `pprFrameProc`: ``` .Lsat_sa8fp{v}_info_fde_end: .long .Lblock{v caDcU}_info_fde_end-.Lblock{v caDcU}_info_fde .Lblock{v caDcU}_info_fde: .long _nbHlD-.Lsection_frame .quad block{v caDcU}_info-1 .quad .Lblock{v caDcU}_info_end-block{v caDcU}_info+1 .byte 1 ``` This diff fixed the error. Test Plan: ./validate Also the case where we used to have assembly error is now fixed. Unfortunately, I have limited insight here and cannot get a small enough repro or test case for this. Ben says: > I think I see: Previously we only produced end symbols for the info > tables of top-level procedures. However, blocks within a procedure may > also have info tables, we will dutifully generate debug information for > and consequently we get undefined symbols. Reviewers: simonmar, scpmw, last_g, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5246 (cherry picked from commit cf961dcf5ebc26cbd960196ba387736334088303) - - - - - b539a99c by Ben Gamari at 2018-10-28T13:32:47-04:00 includes: Allow headers to be built with C++11 compilers Summary: Fixes #14784. Note that C++11 is quite conservative; we could likely accept C++03 as well. Test Plan: ``` $ cat >hi.c <<EOF #include <Rts.h> EOF $ g++ -std=c++11 hi.c ``` Reviewers: simonmar, hvr Subscribers: rwbarton, carter GHC Trac Issues: #14784 Differential Revision: https://phabricator.haskell.org/D5244 (cherry picked from commit d3a1022fabb0ad337003fac774c6929f402ecb8b) - - - - - 804518f7 by Ningning Xie at 2018-10-28T13:33:14-04:00 Fix `:k` command: add validity checking Summary: This patch fixes #15806, where we found that the `:k` command in GHCi misses a validity checking for the type. Missing validity checking causes `:k` to accept types that are not validated. For example, `:k (Maybe (forall a. a -> a))` (incorrectly) returns `*`, while impredictivity of type instantiation shouldn't be allowed. Test Plan: ./validate Reviewers: simonpj, goldfire, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15806 Differential Revision: https://phabricator.haskell.org/D5265 (cherry picked from commit 12cb5cf50b8b35394e2e2d57e1ac693c76f90833) - - - - - 37d14601 by Fangyi Zhou at 2018-10-28T13:33:23-04:00 Fix integer overflow when encoding doubles (Trac #15271) Summary: Ticket #15271 reports a case where 1e1000000000 is incorrectly converted to 0.0. After some investigation, I discovered the number is converted to rational correctly, but converting the ratio into a double introduced an error. Tracking down to how the conversion is done, I found the rts float implementation uses `ldexp`, whose signature is `double ldexp (double x, int exp);` The callsite passes an `I_` to the second argument, which is platform-dependent. On machines where `I_` is 64 bits and `int` is 32 bits, we observe integer overflow behaviour. Here is a mapping from rational to exponent with observations 1e646457008 -> 2147483645 (result = infinity, positive in int32) 1e646457009 -> 2147483648 (result = 0.0, overflow to negative in int32) 1e1000000000 -> 3321928042 (result = infinity, overflow to positive in int32) 1e1555550000 -> 5167425196 (result = 0.0, overflow to negative in int32) We fix this issue by comparing STG_INT_MIN/MAX and INT_MIN/MAX and bound the value appropriately. Test Plan: New test cases Reviewers: bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15271 Differential Revision: https://phabricator.haskell.org/D5271 (cherry picked from commit 311a63979cfa2c1e81be54b82205e681f6ec4f14) - - - - - de9a8feb by Christiaan Baaij at 2018-10-28T13:33:30-04:00 Comment out CONSTANT_FOLDED in GHC.Natural Summary: Although these functions were marked as CONSTANT_FOLDED, they did not have a corresponding builtinRule in PrelRules. The idea was probably to add them eventually, but this hasn't manifested so far. The plan is to eventually add builtin rules for these functions over Natural, so as a reminder we simply comment out the CONSTANT_FOLDED annotation instead of removing it completely. Reviewers: hvr, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter Differential Revision: https://phabricator.haskell.org/D5267 (cherry picked from commit 3ec6fe8827956cc36b58cdf0bb1f5752eaa2a8ea) - - - - - d2cd150e by sheaf at 2018-10-28T13:34:03-04:00 plugins: search for .a files if necessary Summary: on windows, plugins are loaded via .a files, but those paths were not being searched when loading plugins Test Plan: ./validate Reviewers: Phyx, bgamari Reviewed By: Phyx Subscribers: RyanGlScott, rwbarton, carter GHC Trac Issues: #15700 Differential Revision: https://phabricator.haskell.org/D5253 (cherry picked from commit 70298db16c3f0ea4adb603ccb2b5e93eb9c7a556) - - - - - 9f802777 by Ben Gamari at 2018-10-28T17:44:11-04:00 users-guide: Add release notes for 8.6.2 - - - - - b391cae1 by Ningning Xie at 2018-10-28T19:02:33-04:00 Fix TcType.anyRewritableTyVar Summary: This patch fixes #15805, where we found that `TcType.anyRewritableTyVar` has one wrong case. Besides the fix, it also: - removed some unnecessary `ASSERT2(tcIsTcTyVar...)` in `TcType`, as now we have `tcIsTcTyVar = isTyVar`. - fixed some comments Test Plan: ./validate Reviewers: goldfire, simonpj, bgamari Reviewed By: simonpj Subscribers: rwbarton, carter GHC Trac Issues: #15805 Differential Revision: https://phabricator.haskell.org/D5263 (cherry picked from commit a7f64c6cbfc5562adff207945576d1c9db2a58d9) - - - - - a49f95c2 by Simon Peyton Jones at 2018-10-30T14:58:32-04:00 Report a Wanted error even if there are Given ones We suppress some Given errors; see Note [Given errors] in TcErrors. But we must be careful not to suppress Wanted errors because of the presence of these Given errors -- else we might allow compilation to bogusly proceed The rubber hits the road in TcRnTypes.insolubleCt, where we don't want to treat Givens as insoluble, nor (and this is the new bit) Deriveds that arise from Givens. See Note [Given insolubles] in TcRnTypes. This fixes #15767. (cherry picked from commit 6b1102e2cfcffb265fd33cf8a99ab5e6b3f14906) Ben notes: I have folded some test output changes in `TEST="T12529 T12921 mc13 mc14"` into this patch that were not in the original. - - - - - d67cbced by Ben Gamari at 2018-10-30T14:58:32-04:00 users-guide: Fix typo - - - - - 9c4314ec by Ben Gamari at 2018-10-30T14:58:32-04:00 Revert "Fix for T14251 on ARM" This reverts commit 2e23e1c7de01c92b038e55ce53d11bf9db993dd4. - - - - - 377fe398 by Ben Gamari at 2018-10-30T14:58:32-04:00 Revert "Multiple fixes / improvements for LLVM backend" This reverts commit 73273be476a8cc6c13368660b042b3b0614fd928. Unfortunately we were unable to come to a fix that didn't sacrifice the ability to bootstrap GHC using the LLVM backend. Reverting for 8.6.2. - - - - - 2567e8f3 by Ryan Scott at 2018-10-30T14:58:32-04:00 Fix #15815 by parenthesizing the arguments to infix ~ An unfortunate consequence of commit b9483981d128f55d8dae3f434f49fa6b5b30c779 (`Remove HsEqTy and XEqTy`) is infix uses of `~` in TH quotes now desugar differently than before. In particular, we have that: ```haskell a ~ (Int -> Int) ``` Now desugars to: ```haskell HsOpTy a (~) (HsOpTy Int (->) Int) ``` Which GHC interprets as being: ```haskell a ~ Int -> Int ``` Or, equivalently: ```haskell (a ~ Int) -> Int ``` Which is different than what was intended! This is the cause of #15815. All of this has revealed that we likely need to renovate the way we desugar infix type operators to be more consistent with the treatment for infix expressions (see https://ghc.haskell.org/trac/ghc/ticket/15815#comment:5 for more on this.) Doing so would constitute a breaking change, however, so we will likely want to wait until another major GHC release to do this. In the meantime, this patch offers a non-invasive change to the way that infix uses of `~` are desugared. This makes the program in #15815 compile again by inserting extra `HsParTy`s around the arguments to `~` if they are lacking them. Test Plan: make test TEST=T15815 Reviewers: int-index, goldfire, bgamari Reviewed By: int-index Subscribers: int-e, rwbarton, carter GHC Trac Issues: #15815 Differential Revision: https://phabricator.haskell.org/D5274 (cherry picked from commit b8a797ecc34a309bd78f5a290e3554642a3a478a) - - - - - a876edcb by Ben Gamari at 2018-10-30T14:58:32-04:00 users-guide: Note existence of #14251 - - - - - cfc3ad1f by Ben Gamari at 2018-10-31T12:23:39-04:00 users-guide: Fix version number - - - - - 7a439e7b by Richard Eisenberg at 2018-11-02T10:59:49-04:00 Fix #15787 by squashing a coercion hole. In type-incorrect code, we can sometimes let a coercion hole make it through the zonker. If this coercion hole then ends up in the environment (e.g., in the type of a data constructor), then it causes trouble later. This patch avoids trouble by substituting the coercion hole for its representative CoVar. Really, any coercion would do, but the CoVar was very handy. test case: polykinds/T15787 (cherry picked from commit 4427315a65b25db22e1754d41b43dd4b782b022f) - - - - - 41f0f6c2 by Richard Eisenberg at 2018-11-02T11:00:36-04:00 Don't lint erroneous programs. newFamInst lints its types. This is good. But it's not so good when there have been errors and thus recovery tycons are about. So we now don't. Fixes #15796. Test case: typecheck/should_fail/T15796 (cherry picked from commit 1f72a1c81368e34387aac38c0b1c59521cec58ec) - - - - - 9448fdce by Ben Gamari at 2018-11-02T11:48:05-04:00 integer-gmp: Fix TBA in changelog - - - - - 701c872f by Ben Gamari at 2018-11-05T11:47:11-05:00 Set RELEASE=NO - - - - - cbde2726 by Ben Gamari at 2018-11-06T10:33:01-05:00 libiserv: Generate cabal file with autoconf Previously the version number was set by hand. This seems like unnecessary busywork for what is mostly an internal library. - - - - - 130b91db by Ben Gamari at 2018-11-07T21:02:19-05:00 distrib/configure: Set RanlibCmd This fixes #15875. - - - - - 22cd729a by Ömer Sinan Ağacan at 2018-11-22T14:01:30-05:00 Fix heap corruption during stable name allocation See #15906 for the problem. To fix we simply call `allocate()` instead of `ALLOC_PRIM()`. `allocate()` does not trigger GC when the nursery is full, instead it extends it. Test Plan: This validates. memo001 now passes with `-debug` compile parameter. I'll add another test that runs memo001 with `-debug` once I figure out how to use stdout files for multiple tests. Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15906 Differential Revision: https://phabricator.haskell.org/D5342 (cherry picked from commit 691aa715cf43bf9d88ee32bca37e471bae35adfb) - - - - - 14ae4ab6 by Ben Gamari at 2018-11-22T14:01:30-05:00 users guide: We no longer build libraries with -split-objs We now generally use split-sections instead. (cherry picked from commit f5fbecc85967218fd8ba6512f10eea2daf2812ac) - - - - - c8b24dce by Ben Gamari at 2018-11-22T14:01:30-05:00 rts/M32Alloc: Abort if m32 linker mmap fails Previously we should just blinding dereference a NULL pointer. (cherry picked from commit 86f6890e3689f2f75ecca8172eda0338fe3e9769) - - - - - e67bebbf by Christiaan Baaij at 2018-11-22T14:01:35-05:00 Load plugins in interactive session Reviewers: bgamari, tdammers Reviewed By: tdammers Subscribers: monoidal, rwbarton, carter GHC Trac Issues: #15633 Differential Revision: https://phabricator.haskell.org/D5348 (cherry picked from commit 599eaada382d04722219bfc319bde94591be3fb1) - - - - - 4519d98d by Simon Marlow at 2018-11-22T14:48:15-05:00 Fix a bug in SRT generation (#15892) Summary: The logic in `Note [recursive SRTs]` was correct. However, my implementation of it wasn't: I got the associativity of `Set.difference` wrong, which led to an extremely subtle and difficult to find bug. Fortunately now we have a test case. I was able to cut down the code to something manageable, and I've added it to the test suite. Test Plan: Before (using my stage 1 compiler without the fix): ``` ====> T15892(normal) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output -O cd "T15892.run" && ./T15892 +RTS -G1 -A32k -RTS Wrong exit code for T15892(normal)(expected 0 , actual 134 ) Stderr ( T15892 ): T15892: internal error: evacuate: strange closure type 0 (GHC version 8.7.20181113 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) *** unexpected failure for T15892(normal) =====> T15892(g1) 1 of 1 [0, 1, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/bin/ghc-stage1" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output -O cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS Wrong exit code for T15892(g1)(expected 0 , actual 134 ) Stderr ( T15892 ): T15892: internal error: evacuate: strange closure type 0 (GHC version 8.7.20181113 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug Aborted (core dumped) ``` After (using my stage 2 compiler with the fix): ``` =====> T15892(normal) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/test spaces/ghc-stage2" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output cd "T15892.run" && ./T15892 +RTS -G1 -A32k -RTS =====> T15892(g1) 1 of 1 [0, 0, 0] cd "T15892.run" && "/home/smarlow/ghc/inplace/test spaces/ghc-stage2" -o T15892 T15892.hs -dcore-lint -dcmm-lint -no-user-package-db -rtsopts -fno-warn-missed-specialisations -fshow-warning-groups -fdiagnostics-color=never -fno-diagnostics-show-caret -Werror=compat -dno-debug-output cd "T15892.run" && ./T15892 +RTS -G1 -RTS +RTS -G1 -A32k -RTS ``` Reviewers: bgamari, osa1, erikd Reviewed By: osa1 Subscribers: rwbarton, carter GHC Trac Issues: #15892 Differential Revision: https://phabricator.haskell.org/D5334 - - - - - b6d2d837 by Dario Bertini at 2018-11-22T16:03:11-05:00 circleci: Actually build with in-tree GMP on Darwin Fixes #15404. (cherry picked from commit 3584bd4255eb59be043252c9b4ef16bcbd835c9b) - - - - - 65ced246 by Dario Bertini at 2018-11-22T16:06:09-05:00 rts/MachO: Add a bit more debugging output to getNames (cherry picked from commit 9e0a23b95c285c4019fd2d36102374ee582f1dcb) - - - - - b44caa05 by Dario Bertini at 2018-11-22T16:06:09-05:00 rts/MachO: A bit of refactoring in ocGetNames Eliminates a bit of repetition. (cherry picked from commit b2f6f896a0bae0e68ec629bd6817a2cb2533a12c) - - - - - 11fd7df5 by Dario Bertini at 2018-11-22T16:06:09-05:00 rts/MachO: Iterate through N (all) symbols, not M external symbols Fixes #15105 (cherry picked from commit 254890855ee04762cc0392da19e0c42fc039a718) - - - - - c2c6f498 by Ben Gamari at 2018-11-22T16:59:14-05:00 Revert "libiserv: Generate cabal file with autoconf" This reverts commit cbde2726f10b8f4c19483bbb755ad42356098c51. - - - - - 64a50445 by Ben Gamari at 2018-11-22T17:02:45-05:00 base: Mention openFile throwing does-not-exist-errors on FIFOs As discussed in #15715, the POSIX specification specifies that attempting to open a FIFO in write-only mode when the FIFO has no readers will fail with -ENOENT. [skip ci] Test Plan: Read it Reviewers: hvr Subscribers: rwbarton, carter GHC Trac Issues: #15715 Differential Revision: https://phabricator.haskell.org/D5295 (cherry picked from commit 4ba3fa31ddfa12b428bd67216a2d4118dc9e8311) - - - - - 2594ea25 by Richard Eisenberg at 2018-11-22T17:04:06-05:00 Fix #15859 by checking, not assuming, an ArgFlag We thought that visible dependent quantification was impossible in terms, but Iceland Jack discovered otherwise in #15859. This fixes an ASSERT failure that arose. test case: dependent/should_fail/T15859 (cherry picked from commit 72b82343b79365dc74ffafb345dd33499a7fd394) (cherry picked from commit 5693ddd071033516a1804420a903cb7e3677682b) - - - - - 6db7d11e by Alexander Vershilov at 2018-12-06T12:41:22-05:00 Remove explicit recursion in retainer profiling (fixes #14758) Retainer profiling contained a recursion that under certain circumstances could lead to the stack overflow in C code. The idea of the improvement is to keep an explicit stack for the object, more precise to reuse existing stack, but allow new type of objects to be stored there. There is no reliable reproducer that is not a big program but in some cases foldr (+) 0 [1..10000000] can work. Reviewers: bgamari, simonmar, erikd, osa1 Reviewed By: bgamari, osa1 Subscribers: osa1, rwbarton, carter GHC Trac Issues: #14758 Differential Revision: https://phabricator.haskell.org/D5351 (cherry picked from commit 5f1d949ab9e09b8d95319633854b7959df06eb58) - - - - - bf074e3e by Ben Gamari at 2018-12-06T12:43:34-05:00 Bump iserv versions This fixes #15866, the original fix for which didn't merge cleanly to the stable branch. - - - - - c64918c1 by Tamar Christina at 2018-12-06T12:49:25-05:00 linker: store entire link map and use it. Summary: This fixes a corner case in which we have seen the symbol multiple times in different static libraries, but due to a depencency we end up loading the symbol from a library other than the first one. Previously the runtime linker would only track symbols from the first library and did not store the full link map. In this case it was unable to find the address for the symbols in the second library during delay loading. This change stores the address of all symbols seen so a full link map is generated, such that when we make a different decision later than what was expected we're able to still correctly load the library. Test Plan: ./validate, new testcase T15894 Reviewers: angerman, bgamari, erikd, simonmar Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #15894 Differential Revision: https://phabricator.haskell.org/D5353 (cherry picked from commit a8b7cef4d45a5003bf7584e06912f0f632116c71) - - - - - ed86e3b5 by Ben Gamari at 2018-12-06T16:28:16-05:00 Windows: Use the "big" PE object format on amd64 Test Plan: Do full build on Windows. Reviewers: AndreasK, Phyx Reviewed By: AndreasK Subscribers: rwbarton, erikd, carter GHC Trac Issues: #15934 Differential Revision: https://phabricator.haskell.org/D5383 (cherry picked from commit 1ef90f990da90036d481c830d8832e21b8f1571b) - - - - - d59812ce by Ben Gamari at 2018-12-06T16:57:16-05:00 users guide: Add release notes for 8.6.3 - - - - - 31cd867e by Ben Gamari at 2018-12-06T16:58:34-05:00 Release 8.6.3 - - - - - ff9ee830 by Ben Gamari at 2018-12-15T15:08:07-05:00 utils/gen-dll: Bump containers upper bound Fixes #16023. (cherry picked from commit e709c8f8d45c699840f5bab7c9ff71373a53b8b0) - - - - - c6827011 by Ben Gamari at 2018-12-23T20:09:38-05:00 Revert "Windows: Use the "big" PE object format on amd64" This ended up breaking GHCi due to alignment issues. See #16071. This reverts commit ed86e3b531322f74d2c2d00d7ff8662b08fabde6. - - - - - b6237131 by Ben Gamari at 2018-12-27T01:11:20-05:00 Grab CI configuration from master This is awfully ugly but is nevertheless significantly less error-prone than cherry-picking all of the relevant commits manually. - - - - - 27019e9f by Ben Gamari at 2018-12-27T10:26:43-05:00 gitlab-ci: Skip performance tests These are just too fragile on ghc-8.6 which lacks #12758. - - - - - 8b043e88 by Ben Gamari at 2018-12-29T16:35:09-05:00 testsuite: Skip ffi018_ghci when unregisterised As noted in #16085 this test is fragile in unregisterised compilers. (cherry picked from commit 7bfc1e81377d1e37069cf52bd090530124dcd871) - - - - - b348b173 by Ben Gamari at 2018-12-29T17:40:01-05:00 gitlab-ci: Allow integer-simple and unregisterised builds to fail - - - - - 1acf0ceb by Ben Gamari at 2018-12-30T10:20:13-05:00 testsuite: Mark heapprof001 as broken in prof_hc_hb way on i386 As documented in #15382, this is known to fail in prof_hc_hb on i386. Concerningly, I have also seen this test non-deterministically fail in prof_hc_hb on amd64. We should really investigate this. (cherry picked from commit 8fd3f9a67f9c7b447a5bfcb3aefd8986794918ce) - - - - - ee6cf4b3 by Ben Gamari at 2018-12-30T10:20:13-05:00 testsuite: Mark objcpp-hi and T13366 as broken on Darwin due to #16083 (cherry picked from commit 1c0c5e844226f3d77af31d97b21ffb8b14b55740) - - - - - 08cfa615 by Simon Marlow at 2019-01-07T12:18:09-05:00 Fix recompilation bug with default class methods (#15970) If a module uses a class, then it can instantiate the class and thereby use its default methods, so we must include the default methods when calculating the fingerprint for the class. Test Plan: New unit test: driver/T15970 Before: ``` =====> T15970(normal) 1 of 1 [0, 0, 0] cd "T15970.run" && $MAKE -s --no-print-directory T15970 Wrong exit code for T15970()(expected 0 , actual 2 ) Stdout ( T15970 ): Makefile:13: recipe for target 'T15970' failed Stderr ( T15970 ): C.o:function Main_zdfTypeClassMyDataType1_info: error: undefined reference to 'A_toTypedData2_closure' C.o:function Main_main1_info: error: undefined reference to 'A_toTypedData2_closure' C.o(.data+0x298): error: undefined reference to 'A_toTypedData2_closure' C.o(.data+0x480): error: undefined reference to 'A_toTypedData2_closure' collect2: error: ld returned 1 exit status `gcc' failed in phase `Linker'. (Exit code: 1) ``` After: test passes. Reviewers: bgamari, simonpj, erikd, watashi, afarmer Subscribers: rwbarton, carter GHC Trac Issues: #15970 Differential Revision: https://phabricator.haskell.org/D5394 (cherry picked from commit 288f681e06accbae690c46eb8a6e997fa9e5f56a) - - - - - a7fdfd95 by Ben Gamari at 2019-01-10T23:58:53-05:00 Release notes for 8.6.4 - - - - - 3ad6c60e by Ben Gamari at 2019-01-15T23:21:39-05:00 gitlab: Collect artifacts on Windows - - - - - c25a9d8e by Peter Trommler at 2019-01-17T13:38:21-05:00 PPC NCG: Implement simple 64-Bit compare on 32-bit - - - - - ff47e60a by Simon Peyton Jones at 2019-01-28T18:07:36-05:00 Fix bogus worker for newtypes The "worker" for a newtype is actually a function with a small (compulsory) unfolding, namely a cast. But the construction of this function was plain wrong for newtype /instances/; it cast the arguemnt to the family type rather than the representation type. This never actually bit us because, in the case of a family instance, we immediately cast the result to the family type. So we get \x. (x |> co1) |> co2 where the compositio of co1 and co2 is ill-kinded. However the optimiser (even the simple optimiser) just collapsed those casts, ignoring the mis-match in the middle, so we never saw the problem. Trac #16191 is indeed a dup of #16141; but the resaon these tickets produce Lint errors is not the unnecessary forcing; it's because of the ill-typed casts. This patch fixes the ill-typed casts, properly. I can't see a way to trigger an actual failure prior to this patch, but it's still wrong wrong wrong to have ill-typed casts, so better to get rid of them. (cherry picked from commit a5373c1fe172dee31e07bcb7c7f6caff1035e6ba) - - - - - 7ec385f4 by Ben Gamari at 2019-01-28T18:07:38-05:00 itimer: Don't free condvar until we know ticker is stopped When we are shutting down the pthread ticker we signal the start_cond condition variable to ensure that the ticker thread wakes up and exits in a reasonable amount of time. Previously, when the ticker thread would shut down it was responsible for freeing the start_cond condition variable. However, this would lead to a race wherein the ticker would free start_cond, then the main thread would try to signal it in an effort to wake the ticker (#16150). Avoid this by moving the mutex destruction to the main thread. (cherry picked from commit 7b12b3f0240321ac1ee43f14eb9c07e015022eeb) - - - - - 4f180640 by Ben Gamari at 2019-01-28T18:07:38-05:00 rts: Use always-available locking operations in pthread Itimer implementation Previously we ACQUIRE_LOCK and RELEASE_LOCK but these compile to a noop in the non-threaded RTS, as noted in #16150. Use OS_ACQUIRE_LOCK and OS_RELEASE_LOCK instead. (cherry picked from commit ce11f6f25c1160262830d9670c4eaaebac37cbaf) - - - - - ee6e4fcc by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00 Fix a MSG_BLACKHOLE sanity check, add some comments Reviewers: simonmar, bgamari, erikd Reviewed By: simonmar Subscribers: rwbarton, carter GHC Trac Issues: #15508 Differential Revision: https://phabricator.haskell.org/D5178 (cherry picked from commit d90946cea1357d3e99805c27dab1e811785a4088) - - - - - 4f712fb3 by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00 Implement a sanity check for CCS fields in profiling builds This helped me debug one of the bugs in #15508. I'm not sure if this is a good idea, but it worked for me, so wanted to submit this as a MR. (cherry picked from commit 82d1a88dec216d761b17252ede760da5c566007f) - - - - - cf5b5a74 by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00 Fix raiseAsync() UNDERFLOW_FRAME handling in profiling runtime UNDERFLOW_FRAMEs don't have profiling headers so we have to use the AP_STACK's function's CCS as the new frame's CCS. Fixes one of the many bugs caught by concprog001 (#15508). (cherry picked from commit 74cd4ec5d2f9321aad5db3285cb60d78f2562996) - - - - - 14001294 by Ömer Sinan Ağacan at 2019-01-28T18:07:38-05:00 Fix checkPtrInArena (See comments) (cherry picked from commit 448f0e7dd78a8d9404f1aa5e8522cc284360c06d) - - - - - 1e4f0a9a by Ben Gamari at 2019-02-02T20:16:31-05:00 Bump process submodule to 1.6.4.0 See #16199 - - - - - 9fbcfb97 by Ben Gamari at 2019-02-02T20:16:31-05:00 Bump transformers to 0.5.6.2 See #16199. - - - - - 18e2de94 by Ben Gamari at 2019-02-09T10:41:41-05:00 testsuite: Mark ghci063 as broken on Darwin This is the last failing test on Darwin preventing us from disallowing CI failures. See #16201. (cherry picked from commit 0b705fadf936eaf48aaca26d2f7c8c9ae9158c66) - - - - - 8c2dbc16 by Ben Gamari at 2019-02-10T19:56:41-05:00 testsuite: Add test for #16104 - - - - - 5abfd982 by Ben Gamari at 2019-02-10T19:56:41-05:00 GhcPlugins: Fix lookup of TH names Previously `thNameToGhcName` was calling `lookupOrigNameCache` directly, which failed to handle the case that the name wasn't already in the name cache. This happens, for instance, when the name was in scope in a plugin being used during compilation but not in scope in the module being compiled. In this case we the interface file containing the name won't be loaded and `lookupOrigNameCache` fails. This was the cause of #16104. The solution is simple: use the nicely packaged `lookupOrigIO` instead. (cherry picked from commit 0d9f105ba423af4f2ca215a18d04d4c8e2c372a8) - - - - - 0f253b89 by Tamar Christina at 2019-02-10T19:56:41-05:00 Stack: fix name mangling. (cherry picked from commit fb031b9b046e48ffe0d2864ec76bee3bc8ff5625) - - - - - ba11d0aa by Ben Gamari at 2019-02-12T13:17:02-05:00 users-guide: Some more release notes for 8.6.4 - - - - - a481b199 by Ömer Sinan Ağacan at 2019-02-20T13:19:05-05:00 Fix two bugs in stg_ap_0_fast in profiling runtime This includes two bug fixes in profiling version of stg_ap_0_fast: - PAPs allocated by stg_ap_0_fast are now correctly tagged. This invariant is checked in Sanity.c:checkPAP. (This was originally implemented in 2693eb11f5, later reverted with ab55b4ddb7 because it revealed the bug below, but it wasn't clear at the time whether the bug was the one below or something in the commit) - The local variable `untaggedfun` is now marked as a pointer so it survives GC. With this we finally fix all known bugs caught in #15508. `concprog001` now works reliably with prof+threaded and prof runtimes (with and without -debug). (cherry picked from commit 908b4b8659713f0b7a1704ce33c7fa30e3e0ffc3) - - - - - bdc9680c by Herbert Valerio Riedel at 2019-02-20T14:46:47-05:00 Fix regression incorrectly advertising TH support `--supported-languages` must only advertise language extensions which are supported by the compiler in order for tooling such as Cabal relying on this signalling not to behave incorrectly. Fixes #16331 (cherry picked from commit db4372cda7f6c87e7ad26efe3fca4b3f7f527a48) - - - - - e1f52f38 by Ben Gamari at 2019-03-02T15:30:07-05:00 gitlab-ci: Pull docker images from ghc/ci-images registry (cherry picked from commit b90695cdaaa0995c1b7a26289c63be9f9e9cfe3e) - - - - - b09f057a by Ben Gamari at 2019-03-02T15:30:11-05:00 gitlab-ci: Produce DWARF-enabled binary distribution (cherry picked from commit d298cb9cf722126316c9697c20a8e0048498efb9) - - - - - b6f949ff by Ben Gamari at 2019-03-02T15:32:30-05:00 gitlab-ci: Drop CircleCI jobs - - - - - aac18e9a by Ben Gamari at 2019-03-04T15:48:49-05:00 Bump to 8.6.4 - - - - - 1d5b97c2 by Ben Gamari at 2019-03-05T16:02:06-05:00 Set RELEASE=NO - - - - - fd4637c8 by Ben Gamari at 2019-03-19T14:23:21-04:00 gitlab-ci: Don't build Windows in quick flavour This applies the fix from !516 to the 8.6 branch. - - - - - 2f196a5c by Ben Gamari at 2019-03-21T15:29:55-04:00 Introduce i386-windows job - - - - - 1dfc8864 by Matthew Pickering at 2019-03-29T17:03:56-04:00 Don't overwrite the set log_action when using --interactive -ddump-json didn't work with --interactive as --interactive overwrote the log_action in terms of defaultLogAction. Reviewers: bgamari Subscribers: rwbarton, thomie, carter GHC Trac Issues: #14078 Differential Revision: https://phabricator.haskell.org/D4533 (cherry picked from commit 10faf44d97095b2f8516b6d449d266f6889dcd70) - - - - - 97c1ef86 by Edward Z. Yang at 2019-03-29T17:34:49-04:00 Fix #16219: TemplateHaskell causes indefinite package build error It should work to write an indefinite package using TemplateHaskell, so long as all of the actual TH code lives outside of the package. However, cleverness we had to build TH code even when building with -fno-code meant that we attempted to build object code for modules in an indefinite package, even when the signatures were not instantiated. This patch disables said logic in the event that an indefinite package is being typechecked. Signed-off-by: Edward Z. Yang <ezyang at fb.com> Test Plan: validate Reviewers: simonpj, bgamari Reviewed By: bgamari Subscribers: rwbarton, carter GHC Trac Issues: #16219 Differential Revision: https://phabricator.haskell.org/D5475 (cherry picked from commit d6d735c1114082b9e9cc1ba7da87c49f52891320) - - - - - e04e3d81 by Ben Gamari at 2019-04-04T12:35:47-04:00 gitlab-ci: Build hyperlinked sources for releases Fixes #16445. (cherry picked from commit a32ac2f4d963b657c0a53359b492c593e82304b1) - - - - - 9cf1f91b by klebinger.andreas at gmx.at at 2019-04-04T12:35:47-04:00 Restore Xmm registers properly in StgCRun.c This fixes #16514: Xmm6-15 was restored based off rax instead of rsp. The code was introduced in the fix for #14619. (cherry picked from commit 9b131500371a07626e33edc56700c12322364560) - - - - - d2a284ab by Ben Gamari at 2019-04-04T12:35:47-04:00 configure: Always use AC_LINK_ELSEIF when testing against assembler This fixes #16440, where the build system incorrectly concluded that the `.subsections_via_symbols` assembler directive was supported on a Linux system. This was caused by the fact that gcc was invoked with `-flto`; when so-configured gcc does not call the assembler but rather simply serialises its AST for compilation during the final link. This is described in Note [autoconf assembler checks and -flto]. (cherry picked from commit 7b090b53fea065d2cfd967ea919426af9ba8d737) - - - - - 7d3040ac by Ben Gamari at 2019-04-06T12:32:53-04:00 Add release notes for 8.6.5 - - - - - f6cd3ae8 by Ben Gamari at 2019-04-06T12:35:41-04:00 users-guide: Add missing libraries to release notes library list - - - - - d6c93748 by Ben Gamari at 2019-04-07T15:35:51-04:00 users-guide: Fix version number reference - - - - - b9001408 by Ben Gamari at 2019-04-07T15:39:32-04:00 users-guide: Mention fix to #16514 - - - - - 4c7d3228 by Ben Gamari at 2019-04-08T13:47:04-04:00 Move 8.6.5-notes.rst to docs/users_guide - - - - - f0592c22 by Ben Gamari at 2019-04-19T09:45:03-04:00 Do not build i386 Windows with profiled libraries Due to #15934 - - - - - 71abf35a by Ben Gamari at 2019-04-19T09:47:48-04:00 gitlab-ci: Add centos7 release job - - - - - 1df8c217 by Takenobu Tani at 2019-04-19T10:22:27-04:00 gitlab-ci: Enable -haddock while building ghc library Fixing #16415. This is a variant of @takenobu-hs's !769. - - - - - e86d5a21 by Ben Gamari at 2019-04-19T17:04:47-04:00 gitlab-ci: Disable Sphinx PDF output on Debian 8 - - - - - bc75b94f by Ben Gamari at 2019-04-21T10:27:23-04:00 gitlab-ci: Fix YAML syntax - - - - - 92b6a023 by Ben Gamari at 2019-04-22T21:46:46-04:00 Release 8.6.5 - - - - - b1e4243a by Ben Gamari at 2020-11-10T11:23:40-05:00 gitlab-ci: Bump Docker images - - - - - 30 changed files: - .circleci/config.yml - + .circleci/images/aarch64-linux-deb9/Dockerfile - + .circleci/images/i386-linux-deb8/Dockerfile - + .circleci/images/i386-linux-deb9/Dockerfile - .circleci/images/i386-linux/Dockerfile - + .circleci/images/linters/Dockerfile - + .circleci/images/powerpc64le-linux-deb9-cross/Dockerfile - + .circleci/images/update-image - .circleci/images/x86_64-freebsd/Dockerfile - + .circleci/images/x86_64-linux-centos7/Dockerfile - + .circleci/images/x86_64-linux-deb8/Dockerfile - + .circleci/images/x86_64-linux-deb9/Dockerfile - .circleci/images/x86_64-linux-fedora/Dockerfile - + .circleci/images/x86_64-linux-fedora27/Dockerfile - .circleci/images/x86_64-linux/Dockerfile - .circleci/prepare-system.sh - + .circleci/push-test-metrics.sh - + .gitlab-ci.yml - + .gitlab/circle-ci-job.sh - + .gitlab/darwin-init.sh - + .gitlab/fix-submodules.py - + .gitlab/linters/check-cpp.py - + .gitlab/linters/check-makefiles.py - + .gitlab/linters/linter.py - + .gitlab/win32-init.sh - aclocal.m4 - compiler/basicTypes/BasicTypes.hs - compiler/basicTypes/DataCon.hs - compiler/basicTypes/Demand.hs - compiler/basicTypes/MkId.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4f35f54516e35f7a56b67244a15a9f094efae1a9...b1e4243ad3783b46e2f56be53f2303de2787ce3a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4f35f54516e35f7a56b67244a15a9f094efae1a9...b1e4243ad3783b46e2f56be53f2303de2787ce3a 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 Tue Nov 10 16:38:52 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 10 Nov 2020 11:38:52 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-debug-stack Message-ID: <5faac21c6c7f7_10ee3ffb941bdaa812290e1@gitlab.haskell.org.mail> Matthew Pickering pushed new branch wip/ghc-debug-stack at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-debug-stack 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 Tue Nov 10 17:22:28 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 10 Nov 2020 12:22:28 -0500 Subject: [Git][ghc/ghc][wip/con-info] Improve docs, a little Message-ID: <5faacc5458269_10ee3ffbafb9a4481236537@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: a6ef34bb by Matthew Pickering at 2020-11-09T11:13:19+00:00 Improve docs, a little - - - - - 1 changed file: - compiler/GHC/Driver/CodeOutput.hs Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -353,11 +353,12 @@ to a position in the source. The prime example is being able to map a THUNK to a specific place in the source program, the mapping is usually quite precise because a fresh info table is created for each distinct THUNK. -There are two parts to the implementation +There are three parts to the implementation -1. The SourceNote information is used in order to give a source location to +1. In CoreToStg, the SourceNote information is used in order to give a source location to some specific closures. -2. During code generation, a mapping from the info table to the statically +2. In StgToCmm, the actually used info tables are recorded. +3. During code generation, a mapping from the info table to the statically determined location is emitted which can then be queried at runtime by various tools. @@ -373,6 +374,9 @@ During the CoreToStg phase, this map is populated whenever something is turned i a StgRhsClosure or an StgConApp. The current source position is recorded depending on the location indicated by the surrounding SourceNote. +The functions which add information to the map are `recordStgIdPosition` and +`incDc`. + When the -fdistinct-constructor-tables` flag is turned on then every usage of a data constructor gets its own distinct info table. This is orchestrated in `coreToStgExpr` where an incrementing number is used to distinguish each @@ -382,10 +386,16 @@ occurrence of a data constructor. The info tables which are actually used in the generated program are recorded during the conversion from STG to Cmm. The used info tables are recorded in the `emitProc` function. +All the used info tables are recorded in the `cgs_used_info` field. This step +is necessary because when the information about names is collected in the previous +phase it's unpredictable about which names will end up needing info tables. If +you don't record which ones are actually used then you end up generating code +which references info tables which don't exist. -- Code Generation -After the mapping has been collected during compilation, a C stub is generated which +The output of these two phases is combined together during code generation. +A C stub is generated which creates the static map from info table pointer to the information about where that info table was created from. This is created by `ipInitCode` in the same manner as a C stub is generated for cost centres. @@ -406,4 +416,4 @@ can cause code generation to generate a distinct info table for each usage of a constructor. Then, when inspecting the heap you can see precisely which usage of a constructor was responsible for each allocation. --} \ No newline at end of file +-} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a6ef34bb20b9adda775954039a7c69a84535751e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a6ef34bb20b9adda775954039a7c69a84535751e 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 Tue Nov 10 17:36:21 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 10 Nov 2020 12:36:21 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] 3 commits: Introduce snapshotting of thread's own stack Message-ID: <5faacf957c0f3_10ee3ffbd5aa8fdc12383d4@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC Commits: 9e30aabe by Sven Tennie at 2020-11-10T17:26:36+00:00 Introduce snapshotting of thread's own stack Introduce `StackSnapshot#` type and the `cloneMyStack#` primop, allowing the user to reify the state of the calling thread's stack for later inspection. The stack snapshot is offline/cold, i.e. it isn't evaluated any further. For technical details, please see note [Stack Cloning]. Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 3874b577 by Sven Tennie at 2020-11-10T17:27:40+00:00 Introduce cloning of other threads' stacks Introduce `cloneThreadStack` function, allowing threads to request snapshots of other threads' stacks. For technical details, please see note [Stack Cloning]. Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 6b09e577 by Matthew Pickering at 2020-11-10T17:35:36+00:00 Add another test for stack cloning This test triggers at least one GC, which showed up the problem with the stale sp field. - - - - - 22 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/StgToCmm/Prim.hs - includes/rts/storage/Closures.h - includes/stg/MiscClosures.h - + libraries/base/GHC/Stack/CloneStack.hs - libraries/base/base.cabal - + rts/CloneStack.c - + rts/CloneStack.h - rts/Messages.c - rts/PrimOps.cmm - rts/RtsSymbols.c - rts/StgMiscClosures.cmm - rts/package.conf.in - rts/rts.cabal.in - testsuite/tests/rts/all.T - + testsuite/tests/rts/cloneMyStack.hs - + testsuite/tests/rts/cloneMyStack2.hs - + testsuite/tests/rts/cloneStackLib.c - + testsuite/tests/rts/cloneThreadStack.hs - utils/genprimopcode/Main.hs Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -1770,7 +1770,7 @@ statePrimTyConKey, stableNamePrimTyConKey, stableNameTyConKey, typeConKey, threadIdPrimTyConKey, bcoPrimTyConKey, ptrTyConKey, funPtrTyConKey, tVarPrimTyConKey, eqPrimTyConKey, eqReprPrimTyConKey, eqPhantPrimTyConKey, - compactPrimTyConKey :: Unique + compactPrimTyConKey, stackSnapshotPrimTyConKey :: Unique statePrimTyConKey = mkPreludeTyConUnique 50 stableNamePrimTyConKey = mkPreludeTyConUnique 51 stableNameTyConKey = mkPreludeTyConUnique 52 @@ -1801,6 +1801,7 @@ ptrTyConKey = mkPreludeTyConUnique 77 funPtrTyConKey = mkPreludeTyConUnique 78 tVarPrimTyConKey = mkPreludeTyConUnique 79 compactPrimTyConKey = mkPreludeTyConUnique 80 +stackSnapshotPrimTyConKey = mkPreludeTyConUnique 81 eitherTyConKey :: Unique eitherTyConKey = mkPreludeTyConUnique 84 ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -69,6 +69,7 @@ module GHC.Builtin.Types.Prim( bcoPrimTyCon, bcoPrimTy, weakPrimTyCon, mkWeakPrimTy, threadIdPrimTyCon, threadIdPrimTy, + stackSnapshotPrimTyCon, stackSnapshotPrimTy, int8PrimTyCon, int8PrimTy, int8PrimTyConName, word8PrimTyCon, word8PrimTy, word8PrimTyConName, @@ -189,6 +190,7 @@ exposedPrimTyCons , word16PrimTyCon , word32PrimTyCon , word64PrimTyCon + , stackSnapshotPrimTyCon , tYPETyCon , funTyCon @@ -211,7 +213,7 @@ mkBuiltInPrimTc fs unique tycon BuiltInSyntax -charPrimTyConName, intPrimTyConName, int8PrimTyConName, int16PrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word8PrimTyConName, word16PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, proxyPrimTyConName, realWorldTyConName, arrayPrimTyConName, arrayArrayPrimTyConName, smallArrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutableArrayArrayPrimTyConName, smallMutableArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, ioPortPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, compactPrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName, eqPrimTyConName, eqReprPrimTyConName, eqPhantPrimTyConName :: Name +charPrimTyConName, intPrimTyConName, int8PrimTyConName, int16PrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word8PrimTyConName, word16PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, proxyPrimTyConName, realWorldTyConName, arrayPrimTyConName, arrayArrayPrimTyConName, smallArrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutableArrayArrayPrimTyConName, smallMutableArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, ioPortPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, compactPrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName, eqPrimTyConName, eqReprPrimTyConName, eqPhantPrimTyConName, stackSnapshotPrimTyConName :: Name charPrimTyConName = mkPrimTc (fsLit "Char#") charPrimTyConKey charPrimTyCon intPrimTyConName = mkPrimTc (fsLit "Int#") intPrimTyConKey intPrimTyCon int8PrimTyConName = mkPrimTc (fsLit "Int8#") int8PrimTyConKey int8PrimTyCon @@ -247,6 +249,7 @@ tVarPrimTyConName = mkPrimTc (fsLit "TVar#") tVarPrimTyConKey tVarPr stablePtrPrimTyConName = mkPrimTc (fsLit "StablePtr#") stablePtrPrimTyConKey stablePtrPrimTyCon stableNamePrimTyConName = mkPrimTc (fsLit "StableName#") stableNamePrimTyConKey stableNamePrimTyCon compactPrimTyConName = mkPrimTc (fsLit "Compact#") compactPrimTyConKey compactPrimTyCon +stackSnapshotPrimTyConName = mkPrimTc (fsLit "StackSnapshot#") stackSnapshotPrimTyConKey stackSnapshotPrimTyCon bcoPrimTyConName = mkPrimTc (fsLit "BCO") bcoPrimTyConKey bcoPrimTyCon weakPrimTyConName = mkPrimTc (fsLit "Weak#") weakPrimTyConKey weakPrimTyCon threadIdPrimTyConName = mkPrimTc (fsLit "ThreadId#") threadIdPrimTyConKey threadIdPrimTyCon @@ -1087,6 +1090,21 @@ compactPrimTyCon = pcPrimTyCon0 compactPrimTyConName UnliftedRep compactPrimTy :: Type compactPrimTy = mkTyConTy compactPrimTyCon +{- +************************************************************************ +* * + The @StackSnapshot#@ type +* * +************************************************************************ +-} + +stackSnapshotPrimTyCon :: TyCon +stackSnapshotPrimTyCon = pcPrimTyCon0 stackSnapshotPrimTyConName UnliftedRep + +stackSnapshotPrimTy :: Type +stackSnapshotPrimTy = mkTyConTy stackSnapshotPrimTyCon + + {- ************************************************************************ * * ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3151,6 +3151,16 @@ primop SetThreadAllocationCounter "setThreadAllocationCounter#" GenPrimOp has_side_effects = True out_of_line = True +primtype StackSnapshot# + +primop CloneMyStack "cloneMyStack#" GenPrimOp + State# RealWorld -> (# State# RealWorld, StackSnapshot# #) + { Clones the stack of the current Haskell thread. } + with + has_side_effects = True + out_of_line = True + + ------------------------------------------------------------------------ section "Safe coercions" ------------------------------------------------------------------------ ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1521,6 +1521,7 @@ emitPrimOp dflags primop = case primop of TraceEventBinaryOp -> alwaysExternal TraceMarkerOp -> alwaysExternal SetThreadAllocationCounter -> alwaysExternal + CloneMyStack -> alwaysExternal where profile = targetProfile dflags ===================================== includes/rts/storage/Closures.h ===================================== @@ -431,6 +431,14 @@ typedef struct MessageBlackHole_ { StgClosure *bh; } MessageBlackHole; +typedef struct MessageCloneStack_ { + StgHeader header; + Message *link; + StgMVar *result; + StgTSO *tso; +} MessageCloneStack; + + /* ---------------------------------------------------------------------------- Compact Regions ------------------------------------------------------------------------- */ ===================================== includes/stg/MiscClosures.h ===================================== @@ -129,6 +129,7 @@ RTS_ENTRY(stg_STM_AWOKEN); RTS_ENTRY(stg_MSG_TRY_WAKEUP); RTS_ENTRY(stg_MSG_THROWTO); RTS_ENTRY(stg_MSG_BLACKHOLE); +RTS_ENTRY(stg_MSG_CLONE_STACK); RTS_ENTRY(stg_MSG_NULL); RTS_ENTRY(stg_MVAR_TSO_QUEUE); RTS_ENTRY(stg_catch); @@ -492,6 +493,7 @@ RTS_FUN_DECL(stg_traceBinaryEventzh); RTS_FUN_DECL(stg_traceMarkerzh); RTS_FUN_DECL(stg_getThreadAllocationCounterzh); RTS_FUN_DECL(stg_setThreadAllocationCounterzh); +RTS_FUN_DECL(stg_cloneMyStackzh); /* Other misc stuff */ ===================================== libraries/base/GHC/Stack/CloneStack.hs ===================================== @@ -0,0 +1,70 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE UnliftedFFITypes#-} + +-- | +-- This module exposes an interface for capturing the state of a thread's +-- execution stack for diagnostics purposes. +-- +-- @since 2.16.0.0 +module GHC.Stack.CloneStack ( + StackSnapshot(..), + cloneMyStack, + cloneThreadStack + ) where + +import GHC.Prim (StackSnapshot#, cloneMyStack#, ThreadId#) +import Control.Concurrent.MVar +import GHC.Conc.Sync +import GHC.Stable +import GHC.IO (IO(..)) + +-- | A frozen snapshot of the state of an execution stack. +-- +-- @since 2.16.0.0 +data StackSnapshot = StackSnapshot !StackSnapshot# + +{- +Note [Stack Cloning] +~~~~~~~~~~~~~~~~~~~~ +"Cloning" a stack means that it's StgStack closure is copied including the +stack memory (stack[]). The stack pointer (sp) of the clone is adjusted to be +valid. + +The clone is "offline"/"cold", i.e. it won't be evaluated any further. This is +useful for further analyses like stack unwinding or traversal. + +There are two different ways to clone a stack: +1. By the corresponding thread via a primop call (cloneMyStack#). +2. By sending a RTS message (Messages.c) with a MVar to the corresponding + thread and receiving the stack by taking it out of this MVar. + +A StackSnapshot# is really a pointer to an immutable StgStack closure with +the invariant that stack->sp points to a valid frame. +-} + +-- | Clone the stack of the executing thread +-- +-- @since 2.16.0.0 +cloneMyStack :: IO StackSnapshot +cloneMyStack = IO $ \s -> + case (cloneMyStack# s) of (# s1, stack #) -> (# s1, StackSnapshot stack #) + +foreign import ccall "sendCloneStackMessage" sendCloneStackMessage :: ThreadId# -> StablePtr PrimMVar -> IO () + +-- | Clone the stack of a thread identified by its 'ThreadId' +-- +-- @since 2.16.0.0 +cloneThreadStack :: ThreadId -> IO StackSnapshot +cloneThreadStack (ThreadId tid#) = do + resultVar <- newEmptyMVar @StackSnapshot + ptr <- newStablePtrPrimMVar resultVar + -- Use the RTS's "message" mechanism to request that + -- the thread captures its stack, saving the result + -- into resultVar. + sendCloneStackMessage tid# ptr + freeStablePtr ptr + takeMVar resultVar + ===================================== libraries/base/base.cabal ===================================== @@ -264,6 +264,7 @@ Library GHC.ResponseFile GHC.RTS.Flags GHC.ST + GHC.Stack.CloneStack GHC.StaticPtr GHC.STRef GHC.Show ===================================== rts/CloneStack.c ===================================== @@ -0,0 +1,104 @@ +/* --------------------------------------------------------------------------- + * + * (c) The GHC Team, 2001-2021 + * + * Stack snapshotting. + */ + +#include + +#include "Rts.h" +#include "rts/Messages.h" +#include "Messages.h" +#include "rts/storage/TSO.h" +#include "stg/Types.h" +#include "CloneStack.h" +#include "StablePtr.h" +#include "Threads.h" + +#if defined(DEBUG) +#include "sm/Sanity.h" +#endif + +static StgStack* cloneStackChunk(Capability* capability, const StgStack* stack) +{ + StgWord spOffset = stack->sp - stack->stack; + StgWord closureSizeBytes = sizeof(StgStack) + (stack->stack_size * sizeof(StgWord)); + + StgStack* newStackClosure = (StgStack*) allocate(capability, ROUNDUP_BYTES_TO_WDS(closureSizeBytes)); + + memcpy(newStackClosure, stack, closureSizeBytes); + + newStackClosure->sp = newStackClosure->stack + spOffset; + // The new stack is not on the mutable list; clear the dirty flag such that + // we don't claim that it is. + newStackClosure->dirty = 0; + +#if defined(DEBUG) + checkClosure((StgClosure*) newStackClosure); +#endif + + return newStackClosure; +} + +StgStack* cloneStack(Capability* capability, const StgStack* stack) +{ + StgStack *top_stack = cloneStackChunk(capability, stack); + StgStack *last_stack = top_stack; + while (true) { + // check whether the stack ends in an underflow frame + StgPtr top = last_stack->stack + last_stack->stack_size; + StgUnderflowFrame *underFlowFrame = ((StgUnderflowFrame *) top); + StgUnderflowFrame *frame = underFlowFrame--; + if (frame->info == &stg_stack_underflow_frame_info) { + StgStack *s = cloneStackChunk(capability, frame->next_chunk); + frame->next_chunk = s; + last_stack = s; + } else { + break; + } + } + return top_stack; +} + +#if defined(THREADED_RTS) + +// ThreadId# in Haskell is a StgTSO* in RTS. +void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar) { + Capability *srcCapability = rts_unsafeGetMyCapability(); + + MessageCloneStack *msg; + msg = (MessageCloneStack *)allocate(srcCapability, sizeofW(MessageCloneStack)); + msg->tso = tso; + msg->result = (StgMVar*)deRefStablePtr(mvar); + freeStablePtr(mvar); + SET_HDR(msg, &stg_MSG_CLONE_STACK_info, CCS_SYSTEM); + // Ensure that writes constructing Message are committed before sending. + write_barrier(); + + sendMessage(srcCapability, tso->cap, (Message *)msg); +} + +void handleCloneStackMessage(MessageCloneStack *msg){ + StgStack* newStackClosure = cloneStack(msg->tso->cap, msg->tso->stackobj); + + // Lift StackSnapshot# to StackSnapshot by applying it's constructor. + // This is necessary because performTryPutMVar() puts the closure onto the + // stack for evaluation and stacks can not be evaluated (entered). + HaskellObj result = rts_apply(msg->tso->cap, StackSnapshot_constructor_closure, (HaskellObj) newStackClosure); + + bool putMVarWasSuccessful = performTryPutMVar(msg->tso->cap, msg->result, result); + + if(!putMVarWasSuccessful) { + barf("Can't put stack cloning result into MVar."); + } +} + +#else // !defined(THREADED_RTS) + +GNU_ATTRIBUTE(__noreturn__) +void sendCloneStackMessage(StgTSO *tso STG_UNUSED, HsStablePtr mvar STG_UNUSED) { + barf("Sending CloneStackMessages is only available in threaded RTS!"); +} + +#endif // end !defined(THREADED_RTS) ===================================== rts/CloneStack.h ===================================== @@ -0,0 +1,23 @@ +/* --------------------------------------------------------------------------- + * + * (c) The GHC Team, 2001-2021 + * + * Stack snapshotting. + */ + +#pragma once + +extern StgClosure DLL_IMPORT_DATA_VARNAME(base_GHCziStackziCloneStack_StackSnapshot_closure); +#define StackSnapshot_constructor_closure DLL_IMPORT_DATA_REF(base_GHCziStackziCloneStack_StackSnapshot_closure) + +StgStack* cloneStack(Capability* capability, const StgStack* stack); + +void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar); + +#include "BeginPrivate.h" + +#if defined(THREADED_RTS) +void handleCloneStackMessage(MessageCloneStack *msg); +#endif + +#include "EndPrivate.h" ===================================== rts/Messages.c ===================================== @@ -14,6 +14,7 @@ #include "Threads.h" #include "RaiseAsync.h" #include "sm/Storage.h" +#include "CloneStack.h" /* ---------------------------------------------------------------------------- Send a message to another Capability @@ -32,7 +33,8 @@ void sendMessage(Capability *from_cap, Capability *to_cap, Message *msg) i != &stg_MSG_BLACKHOLE_info && i != &stg_MSG_TRY_WAKEUP_info && i != &stg_IND_info && // can happen if a MSG_BLACKHOLE is revoked - i != &stg_WHITEHOLE_info) { + i != &stg_WHITEHOLE_info && + i != &stg_MSG_CLONE_STACK_info) { barf("sendMessage: %p", i); } } @@ -131,6 +133,10 @@ loop: #endif goto loop; } + else if(i == &stg_MSG_CLONE_STACK_info){ + MessageCloneStack *cloneStackMessage = (MessageCloneStack*) m; + handleCloneStackMessage(cloneStackMessage); + } else { barf("executeMessage: %p", i); ===================================== rts/PrimOps.cmm ===================================== @@ -2840,3 +2840,14 @@ stg_setThreadAllocationCounterzh ( I64 counter ) StgTSO_alloc_limit(CurrentTSO) = counter + TO_I64(offset); return (); } + +stg_cloneMyStackzh () { + W_ stgStack; + W_ clonedStack; + stgStack = StgTSO_stackobj(CurrentTSO); + StgStack_sp(stgStack) = Sp; + + ("ptr" clonedStack) = ccall cloneStack(MyCapability() "ptr", stgStack "ptr"); + + return (clonedStack); +} ===================================== rts/RtsSymbols.c ===================================== @@ -12,6 +12,7 @@ #include "Rts.h" #include "TopHandler.h" #include "HsFFI.h" +#include "CloneStack.h" #include "sm/Storage.h" #include "sm/NonMovingMark.h" @@ -979,6 +980,7 @@ SymI_HasProto(stg_traceBinaryEventzh) \ SymI_HasProto(stg_getThreadAllocationCounterzh) \ SymI_HasProto(stg_setThreadAllocationCounterzh) \ + SymI_HasProto(stg_cloneMyStackzh) \ SymI_HasProto(getMonotonicNSec) \ SymI_HasProto(lockFile) \ SymI_HasProto(unlockFile) \ @@ -998,6 +1000,7 @@ SymI_HasProto(cas) \ SymI_HasProto(_assertFail) \ SymI_HasProto(keepCAFs) \ + SymI_HasProto(sendCloneStackMessage) \ RTS_USER_SIGNALS_SYMBOLS \ RTS_INTCHAR_SYMBOLS ===================================== rts/StgMiscClosures.cmm ===================================== @@ -573,6 +573,9 @@ INFO_TABLE_CONSTR(stg_MSG_BLACKHOLE,3,0,0,PRIM,"MSG_BLACKHOLE","MSG_BLACKHOLE") INFO_TABLE_CONSTR(stg_MSG_NULL,1,0,0,PRIM,"MSG_NULL","MSG_NULL") { foreign "C" barf("MSG_NULL object (%p) entered!", R1) never returns; } +INFO_TABLE_CONSTR(stg_MSG_CLONE_STACK,3,0,0,PRIM,"MSG_CLONE_STACK","MSG_CLONE_STACK") +{ foreign "C" barf("stg_MSG_CLONE_STACK object (%p) entered!", R1) never returns; } + /* ---------------------------------------------------------------------------- END_TSO_QUEUE ===================================== rts/package.conf.in ===================================== @@ -194,6 +194,7 @@ ld-options: * so we need to force it to be included in the binary. */ , "-Wl,-u,_findPtr" #endif + , "-Wl,-u,_base_GHCziStackziCloneStack_StackSnapshot_closure" #else "-Wl,-u,base_GHCziTopHandler_runIO_closure" , "-Wl,-u,base_GHCziTopHandler_runNonIO_closure" @@ -308,6 +309,7 @@ ld-options: * so we need to force it to be included in the binary. */ , "-Wl,-u,findPtr" #endif + , "-Wl,-u,base_GHCziStackziCloneStack_StackSnapshot_closure" #endif /* Pick up static libraries in preference over dynamic if in earlier search ===================================== rts/rts.cabal.in ===================================== @@ -286,6 +286,7 @@ library "-Wl,-u,_hs_atomicwrite8" "-Wl,-u,_hs_atomicwrite16" "-Wl,-u,_hs_atomicwrite32" + "-Wl,-u,_base_GHCziStackziCloneStack_StackSnapshot_closure" if flag(find-ptr) -- This symbol is useful in gdb, but not referred to anywhere, @@ -367,6 +368,7 @@ library "-Wl,-u,hs_atomicwrite8" "-Wl,-u,hs_atomicwrite16" "-Wl,-u,hs_atomicwrite32" + "-Wl,-u,base_GHCziStackziCloneStack_StackSnapshot_closure" if flag(find-ptr) -- This symbol is useful in gdb, but not referred to anywhere, @@ -410,6 +412,7 @@ library Arena.c Capability.c CheckUnload.c + CloneStack.c ClosureFlags.c Disassembler.c FileLock.c ===================================== testsuite/tests/rts/all.T ===================================== @@ -418,3 +418,8 @@ test('T17088', compile_and_run, ['-rtsopts -O2']) test('T15427', normal, compile_and_run, ['']) + +test('cloneMyStack', [extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c']) +test('cloneMyStack2', ignore_stdout, compile_and_run, ['']) + +test('cloneThreadStack', [only_ways(['threaded1']), extra_ways(['threaded1']), extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c -threaded']) ===================================== testsuite/tests/rts/cloneMyStack.hs ===================================== @@ -0,0 +1,20 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnliftedFFITypes #-} + +import GHC.Prim (StackSnapshot#) +import GHC.Stack.CloneStack +import Foreign +import Foreign.C.Types (CUInt) + +foreign import ccall "expectClosureTypes" expectClosureTypes:: StackSnapshot# -> Ptr CUInt -> Int -> IO () + +main :: IO () +main = do + stackSnapshot <- cloneMyStack + + let (StackSnapshot stack) = stackSnapshot + let expectedClosureTypes = [34 -- CATCH_FRAME + ,36 -- STOP_FRAME + ] + withArray expectedClosureTypes (\ptr -> expectClosureTypes stack ptr (length expectedClosureTypes)) ===================================== testsuite/tests/rts/cloneMyStack2.hs ===================================== @@ -0,0 +1,15 @@ +{-# LANGUAGE BangPatterns #-} +module Main where + +import GHC.Stack.CloneStack + +main = foo 100 + +{-# NOINLINE foo #-} +foo 0 = () <$ getStack +foo n = print "x" >> foo (n - 1) >> print "x" + +-- This shouldn't segfault +getStack = do + !s <- cloneMyStack + return () ===================================== testsuite/tests/rts/cloneStackLib.c ===================================== @@ -0,0 +1,55 @@ +#include "Rts.h" +#include "RtsAPI.h" +#include "rts/Messages.h" + + +void expectStacksToBeEqual(StgStack *clonedStack, StgTSO *tso) { + StgStack *liveStack = tso->stackobj; + + if(liveStack->header.info != clonedStack->header.info){ + barf("info table pointer not equal! Expected same pointer address, but got %p and %p", liveStack->header.info, clonedStack->header.info); + } + + StgInfoTable *info = INFO_PTR_TO_STRUCT(liveStack->header.info); + + if (info->type != STACK) { + barf("Expected a closure of type STACK!"); + } + + if(liveStack->stack_size != clonedStack->stack_size){ + barf("Expected same stack_size!"); + } + + if(liveStack->marking != clonedStack->marking){ + barf("Expected same marking flags!"); + } + + for(StgWord i = liveStack->stack_size - 1; (liveStack->stack + i) >= liveStack->sp; i--){ + if(liveStack->stack[i] != clonedStack->stack[i]){ + barf("Expected stack word %lu to be equal on both stacks.", i); + } + } +} + +void expectStackToBeNotDirty(StgStack *stack) { + if(stack->dirty != 0) { + barf("Expected stack to be not dirty. But dirty flag was set to %u", stack->dirty); + } +} + +void expectClosureTypes(StgStack *stack, unsigned int types[], size_t typesSize){ + StgPtr sp = stack->sp; + StgPtr spBottom = stack->stack + stack->stack_size; + + for (StgWord i = 0; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp), i++) { + const StgInfoTable *info = get_itbl((StgClosure *)sp); + + if(i >= typesSize) { + barf("Stack size exceeds expectation!"); + } + + if(info->type != types[i]) { + barf("Wrong closure type on stack! Expected %u but got %u", types[i], info->type); + } + } +} ===================================== testsuite/tests/rts/cloneThreadStack.hs ===================================== @@ -0,0 +1,49 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnliftedFFITypes #-} + +import GHC.Prim (StackSnapshot#, ThreadId#) +import GHC.Conc.Sync (ThreadId(..)) +import GHC.Stack.CloneStack +import Control.Concurrent +import GHC.Conc + +foreign import ccall "expectStacksToBeEqual" expectStacksToBeEqual:: StackSnapshot# -> ThreadId# -> IO () + +foreign import ccall "expectStackToBeNotDirty" expectStackToBeNotDirty:: StackSnapshot# -> IO () + +main :: IO () +main = do + mVarToBeBlockedOn <- newEmptyMVar + threadId <- forkIO $ immediatelyBlocking mVarToBeBlockedOn + + waitUntilBlocked threadId + + stackSnapshot <- cloneThreadStack threadId + + let (StackSnapshot stack) = stackSnapshot + let (ThreadId tid#) = threadId + expectStacksToBeEqual stack tid# + expectStackToBeNotDirty stack + +immediatelyBlocking :: MVar Int -> IO () +immediatelyBlocking mVarToBeBlockedOn = do + takeMVar mVarToBeBlockedOn + return () + +waitUntilBlocked :: ThreadId -> IO () +waitUntilBlocked tid = do + blocked <- isBlocked tid + if blocked then + return () + else + do + threadDelay 100000 + waitUntilBlocked tid + +isBlocked:: ThreadId -> IO Bool +isBlocked = fmap isThreadStatusBlocked . threadStatus + +isThreadStatusBlocked :: ThreadStatus -> Bool +isThreadStatusBlocked (ThreadBlocked _) = True +isThreadStatusBlocked _ = False ===================================== utils/genprimopcode/Main.hs ===================================== @@ -878,6 +878,7 @@ ppType (TyApp (TyCon "ThreadId#") []) = "threadIdPrimTy" ppType (TyApp (TyCon "ForeignObj#") []) = "foreignObjPrimTy" ppType (TyApp (TyCon "BCO") []) = "bcoPrimTy" ppType (TyApp (TyCon "Compact#") []) = "compactPrimTy" +ppType (TyApp (TyCon "StackSnapshot#") []) = "stackSnapshotPrimTy" ppType (TyApp (TyCon "()") []) = "unitTy" -- unitTy is GHC.Builtin.Types's name for () ppType (TyVar "a") = "alphaTy" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bcc93393857b1014bb0127f5ab9743211ed82678...6b09e577cf7afb73a423db02a62a3eff150f8dde -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bcc93393857b1014bb0127f5ab9743211ed82678...6b09e577cf7afb73a423db02a62a3eff150f8dde 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 Tue Nov 10 17:57:11 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 10 Nov 2020 12:57:11 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Improve performance Message-ID: <5faad477e342c_10ee107f6970124638@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 1c2aa0e3 by Richard Eisenberg at 2020-11-10T17:56:29+00:00 Improve performance - - - - - 2 changed files: - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Tc/Solver/Flatten.hs ===================================== @@ -364,18 +364,17 @@ faster. This doesn't seem quite worth it, yet. Note [flatten_exact_fam_app_fully performance] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The refactor of GRefl seems to cause performance trouble for T9872x: -the allocation of flatten_exact_fam_app_fully_performance -increased. See note [Generalized reflexive coercion] in -GHC.Core.TyCo.Rep for more information about GRefl and #15192 for the -current state. - -The explicit pattern match in homogenise_result helps with T9872a, b, c. - -Still, it increases the expected allocation of T9872d by ~2%. - -TODO: a step-by-step replay of the refactor to analyze the performance. - +Once we've got a flat rhs, we extend the flat-cache to record +the result. Doing so can save lots of work when the same redex shows up more +than once. Note that we record the link from the redex all the way to its +*final* value, not just the single step reduction. Interestingly, adding to the +flat-cache for the first reduction *doubles* the allocations +for the T9872a test. However, using the flat-cache in +the later reduction is a similar gain. I (Richard E) don't currently +(Dec '14 nor Nov '20) have any knowledge as to *why* these facts are true. +Perhaps the first use of the flat-cache doesn't add much, because we didn't +need to reduce in the arguments (and instance lookup is similar to cache +lookup). -} {-# INLINE flatten_args_tc #-} @@ -766,7 +765,7 @@ flatten_fam_app tc tys -- Can be over-saturated ; flatten_app_ty_args xi1 co1 tys_rest } -- the [TcType] exactly saturate the TyCon --- See note [flatten_exact_fam_app_fully performance] +-- See Note [flatten_exact_fam_app_fully performance] flatten_exact_fam_app_fully :: TyCon -> [TcType] -> FlatM (Xi, Coercion) flatten_exact_fam_app_fully tc tys = do { checkStackDepth (mkTyConApp tc tys) @@ -774,14 +773,15 @@ flatten_exact_fam_app_fully tc tys -- Step 1. Try to reduce without reducing arguments first. ; result1 <- try_to_reduce tc tys ; case result1 of - { Just (co, xi) -> finish (xi, co) + { Just (co, xi) -> do { (xi2, co2) <- bumpDepth $ flatten_one xi + ; return (xi2, co2 `mkTcTransCo` co) } ; Nothing -> -- That didn't work. So reduce the arguments. do { (xis, cos, kind_co) <- flatten_args_tc tc (repeat Nominal) tys -- kind_co :: tcTypeKind(F xis) ~N tcTypeKind(F tys) - ; eq_rel <- getEqRel + ; eq_rel <- getEqRel ; let role = eqRelRole eq_rel args_co = mkTyConAppCo role tc cos -- args_co :: F xis ~r F tys @@ -791,14 +791,7 @@ flatten_exact_fam_app_fully tc tys -- assume co :: xi ~r F xis, co is homogeneous -- then xi' :: tcTypeKind(F tys) -- and co' :: xi' ~r F tys, which is homogeneous - homogenise xi co = (casted_xi, final_co) - where - casted_xi = xi `mkCastTy` kind_co - -- casted_xi :: tcTypeKind(F tys) - homo_co = mkTcGReflLeftCo role xi kind_co - -- homo_co :: casted_xi ~r xi - - final_co = homo_co `mkTcTransCo` co `mkTcTransCo` args_co + homogenise xi co = homogenise_result xi (co `mkTcTransCo` args_co) role kind_co ; result2 <- liftTcS $ lookupFamAppInert tc xis ; flavour <- getFlavour @@ -807,7 +800,8 @@ flatten_exact_fam_app_fully tc tys -- co :: F xis ~ir xi | fr `eqCanRewriteFR` (flavour, eq_rel) -> - do { traceFlat "flatten/flat-cache hit" (ppr tc <+> ppr xis $$ ppr xi) + do { traceFlat "rewrite family application with inert" + (ppr tc <+> ppr xis $$ ppr xi) ; finish (homogenise xi downgraded_co) } where inert_role = eqRelRole inert_eq_rel @@ -832,7 +826,10 @@ flatten_exact_fam_app_fully tc tys ; let final_co = fully_co `mkTcTransCo` co ; eq_rel <- getEqRel ; flavour <- getFlavour - ; when (eq_rel == NomEq && flavour /= Derived) $ -- the cache only wants Nominal eqs + ; when (eq_rel == NomEq && flavour /= Derived) $ + -- the cache only wants Nominal eqs + -- and Wanteds can rewrite Deriveds; the cache + -- has only Givens liftTcS $ extendFamAppCache tc tys (final_co, fully) ; return (fully, final_co) } @@ -846,210 +843,19 @@ try_to_reduce tc tys where downgrade :: Maybe (TcCoercionN, TcType) -> FlatM (Maybe (TcCoercion, TcType)) downgrade Nothing = return Nothing - downgrade (Just (co, xi)) + downgrade result@(Just (co, xi)) = do { traceFlat "Eager T.F. reduction success" $ vcat [ ppr tc, ppr tys, ppr xi , ppr co <+> dcolon <+> ppr (coercionKind co) ] - ; role <- getRole - ; return (Just (tcDowngradeRole role Nominal co, xi)) } - -{- "RAE" - -- See Note [Reduce type family applications eagerly] - -- the following tcTypeKind should never be evaluated, as it's just used in - -- casting, and casts by refl are dropped - = do { mOut <- try_to_reduce_nocache tc tys - ; case mOut of - Just out -> pure out - Nothing -> do - { -- First, flatten the arguments - ; (xis, cos, kind_co) - <- setEqRel NomEq $ -- just do this once, instead of for - -- each arg - flatten_args_tc tc (repeat Nominal) tys - -- kind_co :: tcTypeKind(F xis) ~N tcTypeKind(F tys) - ; eq_rel <- getEqRel - ; cur_fr <- getFlavourRole - ; let role = eqRelRole eq_rel - ret_co = mkTyConAppCo role tc cos - -- ret_co :: F xis ~ F tys; might be heterogeneous - - -- Now, look in the inerts and the cache - ; mb_ct <- liftTcS $ lookupFamApp tc xis - ; dflags <- getDynFlags - ; loc <- getLoc - ; case mb_ct of - Just (co, rhs_ty, inert_fr@(_, inert_eq_rel)) -- co :: F xis ~ rhs_ty - | inert_fr `eqCanRewriteFR` cur_fr - -- See Note [Runaway Derived rewriting] - , let reduction_ok | (Derived, _) <- cur_fr - = not (subGoalDepthExceeded dflags - (bumpSubGoalDepth (ctLocDepth loc))) - | otherwise - = True - , reduction_ok - -> -- Usable hit in the flat-cache - do { traceFlat "flatten/flat-cache hit" $ - (ppr tc <+> ppr xis $$ ppr rhs_ty) - ; (rhs_xi, rhs_co) <- flatten_one rhs_ty - -- There may be more work to do on the rhs: - -- flatten it - -- rhs_co :: rhs_xi ~ rhs_ty - ; let xi = rhs_xi `mkCastTy` kind_co - co' = mkTcCoherenceLeftCo role rhs_xi kind_co rhs_co - `mkTransCo` - tcDowngradeRole role (eqRelRole inert_eq_rel) - (mkTcSymCo co) - `mkTransCo` ret_co - ; return (xi, co') - } - - - -- Try to reduce the family application right now - -- See Note [Reduce type family applications eagerly] - _ -> do { mOut <- try_to_reduce tc - xis - kind_co - (`mkTransCo` ret_co) - ; case mOut of - Just out -> pure out - Nothing -> do - { traceFlat "flatten/flat-cache miss" $ - ppr tc <+> ppr xis - ; let uncasted_ty = mkTyConApp tc xis - casted_ty = uncasted_ty `mkCastTy` kind_co - final_co = mkTcCoherenceLeftCo role uncasted_ty - kind_co ret_co - ; return ( casted_ty, final_co ) - } - } - } - } - - where - - -- try_to_reduce and try_to_reduce_nocache (below) could be unified into - -- a more general definition, but it was observed that separating them - -- gives better performance (lower allocation numbers in T9872x). - - try_to_reduce :: TyCon -- F, family tycon - -> [Type] -- args, not necessarily flattened - -> CoercionN -- kind_co :: tcTypeKind(F args) ~N - -- tcTypeKind(F orig_args) - -- where - -- orig_args is what was passed to the outer - -- function - -> ( Coercion -- :: (xi |> kind_co) ~ F args - -> Coercion ) -- what to return from outer function - -> FlatM (Maybe (Xi, Coercion)) - try_to_reduce tc tys kind_co update_co - = do { checkStackDepth (mkTyConApp tc tys) - ; mb_match <- liftTcS $ matchFam tc tys - ; case mb_match of - -- NB: norm_co will always be homogeneous. All type families - -- are homogeneous. - Just (norm_co, norm_ty) - -> do { traceFlat "Eager T.F. reduction success" $ - vcat [ ppr tc, ppr tys, ppr norm_ty - , ppr norm_co <+> dcolon - <+> ppr (coercionKind norm_co) - ] - ; (xi, final_co) <- bumpDepth $ flatten_one norm_ty - ; eq_rel <- getEqRel - ; let co = maybeTcSubCo eq_rel norm_co - `mkTransCo` mkSymCo final_co - -- NB: only extend cache with nominal equalities - ; when (eq_rel == NomEq) $ - liftTcS $ extendFamAppCache tc tys (co, xi) - ; let role = eqRelRole eq_rel - xi' = xi `mkCastTy` kind_co - co' = update_co $ - mkTcCoherenceLeftCo role xi kind_co (mkSymCo co) - ; return $ Just (xi', co') } - Nothing -> pure Nothing } - - try_to_reduce_nocache :: TyCon -- F, family tycon - -> [Type] -- args, not necessarily flattened - -> FlatM (Maybe (Xi, Coercion)) - try_to_reduce_nocache tc tys - = do { checkStackDepth (mkTyConApp tc tys) - ; mb_match <- liftTcS $ matchFam tc tys - ; case mb_match of - -- NB: norm_co will always be homogeneous. All type families - -- are homogeneous. - Just (norm_co, norm_ty) - -> do { (xi, final_co) <- bumpDepth $ flatten_one norm_ty - ; eq_rel <- getEqRel - ; let co = mkSymCo (maybeTcSubCo eq_rel norm_co - `mkTransCo` mkSymCo final_co) - ; return $ Just (xi, co) } - Nothing -> pure Nothing } --} - -{- Note [Reduce type family applications eagerly] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": Update Note. - -If we come across a type-family application like (Append (Cons x Nil) t), -then, rather than flattening to a skolem etc, we may as well just reduce -it on the spot to (Cons x t). This saves a lot of intermediate steps. -Examples that are helped are tests T9872, and T5321Fun. - -Performance testing indicates that it's best to try this *twice*, once -before flattening arguments and once after flattening arguments. -Adding the extra reduction attempt before flattening arguments cut -the allocation amounts for the T9872{a,b,c} tests by half. - -An example of where the early reduction appears helpful: - - type family Last x where - Last '[x] = x - Last (h ': t) = Last t - - workitem: (x ~ Last '[1,2,3,4,5,6]) - -Flattening the argument never gets us anywhere, but trying to flatten -it at every step is quadratic in the length of the list. Reducing more -eagerly makes simplifying the right-hand type linear in its length. - -Testing also indicated that the early reduction should *not* use the -flat-cache, but that the later reduction *should*. (Although the -effect was not large.) Hence the Bool argument to try_to_reduce. To -me (SLPJ) this seems odd; I get that eager reduction usually succeeds; -and if don't use the cache for eager reduction, we will miss most of -the opportunities for using it at all. More exploration would be good -here. - -At the end, once we've got a flat rhs, we extend the flatten-cache to record -the result. Doing so can save lots of work when the same redex shows up more -than once. Note that we record the link from the redex all the way to its -*final* value, not just the single step reduction. Interestingly, using the -flat-cache for the first reduction resulted in an increase in allocations -of about 3% for the four T9872x tests. However, using the flat-cache in -the later reduction is a similar gain. I (Richard E) don't currently (Dec '14) -have any knowledge as to *why* these facts are true. - -Note [Runaway Derived rewriting] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -"RAE": Remove. We do occurs-checking now. - -Suppose we have - [WD] F a ~ T (F a) -We *don't* want to fall into a hole using that to rewrite a Derived - [D] F a ~ Int -because that produces an unhelpful error about a reduction stack overflow. -Instead, when we've reached the reduction stack limit on a Derived, just stop. -Either the program will be accepted if all the Wanteds are solved (good), -or a Wanted will not be solved, and will be reported (also good). - -There is a tiny chance that continuing to try to reduce the Derived would -yield fruit, and there is no way for the user to know this is the case -(or to increase the reduction stack limit). But I see no easy way of -communicating this. Since Deriveds are likely going to be short-lived -at this point, it's not worth thinking about further. - -This arose in typecheck/should_fail/T13320. + ; eq_rel <- getEqRel + -- manually doing it this way avoids allocation in the vastly + -- common NomEq case + ; case eq_rel of + NomEq -> return result + ReprEq -> return (Just (mkSubCo co, xi)) } +{- ************************************************************************ * * Flattening a type variable ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -406,6 +406,9 @@ data InertSet , inert_famapp_cache :: FunEqMap (TcCoercion, TcType) -- If F tys :-> (co, rhs, flav), -- then co :: rhs ~ F tys + -- all evidence is from instances or Givens + -- (We have no way of "kicking out" from the cache, so putting + -- wanteds here means we can end up solving a Wanted with itself. Bad) -- -- Some entries in the cache might have arisen from Wanteds, and -- so this should be used only for rewriting Wanteds. @@ -2385,11 +2388,15 @@ lookupFamAppInert fam_tc tys | otherwise = Nothing lookupFamAppCache :: CtFlavour -> TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType)) -lookupFamAppCache Given _ _ = return Nothing - -- the famapp_cache contains some wanteds. Not appropriate to rewrite a Given. lookupFamAppCache _ fam_tc tys = do { IS { inert_famapp_cache = famapp_cache } <- getTcSInerts - ; return (findFunEq famapp_cache fam_tc tys) } + ; case findFunEq famapp_cache fam_tc tys of + result@(Just (co, ty)) -> + do { traceTcS "famapp_cache hit" (vcat [ ppr (mkTyConApp fam_tc tys) + , ppr ty + , ppr co ]) + ; return result } + Nothing -> return Nothing } lookupInInerts :: CtLoc -> TcPredType -> TcS (Maybe CtEvidence) -- Is this exact predicate type cached in the solved or canonicals of the InertSet? View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c2aa0e32e96f23caf12e6f19108401c5a6afc8f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c2aa0e32e96f23caf12e6f19108401c5a6afc8f 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 Tue Nov 10 18:45:16 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 10 Nov 2020 13:45:16 -0500 Subject: [Git][ghc/ghc][wip/T18870] 145 commits: Parser regression tests, close #12862 #12446 Message-ID: <5faadfbc85823_10ee3ffb94199d9c1256259@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/T18870 at Glasgow Haskell Compiler / GHC Commits: e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - ac85229e by Sebastian Graf at 2020-11-10T19:44:08+01:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Axiom.hs - − compiler/GHC/Core/ConLike.hs-boot The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/81453d69fbb6acf2b8d126ab16abd45c919d9e15...ac85229e2cba3571f6a205881beea304c270f483 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/81453d69fbb6acf2b8d126ab16abd45c919d9e15...ac85229e2cba3571f6a205881beea304c270f483 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 Tue Nov 10 18:54:17 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 10 Nov 2020 13:54:17 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Don't fail eagerly on runaway Derived instances Message-ID: <5faae1d983d9d_10ee3ffbc0535ab01259585@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 6cf1819f by Richard Eisenberg at 2020-11-10T13:53:59-05:00 Don't fail eagerly on runaway Derived instances - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Interact.hs Changes: ===================================== compiler/GHC/Tc/Solver/Interact.hs ===================================== @@ -1071,6 +1071,8 @@ shortCutSolver dflags ev_w ev_i ; lift $ traceTcS "shortCutSolver: found instance" (ppr preds) ; loc' <- lift $ checkInstanceOK loc what pred + ; lift $ checkReductionDepth loc' pred + ; evc_vs <- mapM (new_wanted_cached loc' solved_dicts') preds -- Emit work for subgoals but use our local cache @@ -1939,47 +1941,48 @@ chooseInstance work_item , cir_mk_ev = mk_ev }) = do { traceTcS "doTopReact/found instance for" $ ppr ev ; deeper_loc <- checkInstanceOK loc what pred - ; if isDerived ev then finish_derived deeper_loc theta - else finish_wanted deeper_loc theta mk_ev } + ; if isDerived ev + then -- Use type-class instances for Deriveds, in the hope + -- of generating some improvements + -- C.f. Example 3 of Note [The improvement story] + -- It's easy because no evidence is involved + do { dflags <- getDynFlags + ; unless (subGoalDepthExceeded dflags (ctLocDepth deeper_loc)) $ + emitNewDeriveds deeper_loc theta + -- If we have a runaway Derived, let's not issue a + -- "reduction stack overflow" error, which is not particularly + -- friendly. Instead, just drop the Derived. + ; traceTcS "finish_derived" (ppr (ctl_depth deeper_loc)) + ; stopWith ev "Dict/Top (solved derived)" } + + else -- wanted + do { checkReductionDepth deeper_loc pred + ; evb <- getTcEvBindsVar + ; if isCoEvBindsVar evb + then continueWith work_item + -- See Note [Instances in no-evidence implications] + + else + do { evc_vars <- mapM (newWanted deeper_loc) theta + ; setEvBindIfWanted ev (mk_ev (map getEvExpr evc_vars)) + ; emitWorkNC (freshGoals evc_vars) + ; stopWith ev "Dict/Top (solved wanted)" }}} where ev = ctEvidence work_item pred = ctEvPred ev loc = ctEvLoc ev - finish_wanted :: CtLoc -> [TcPredType] - -> ([EvExpr] -> EvTerm) -> TcS (StopOrContinue Ct) - -- Precondition: evidence term matches the predicate workItem - finish_wanted loc theta mk_ev - = do { evb <- getTcEvBindsVar - ; if isCoEvBindsVar evb - then -- See Note [Instances in no-evidence implications] - continueWith work_item - else - do { evc_vars <- mapM (newWanted loc) theta - ; setEvBindIfWanted ev (mk_ev (map getEvExpr evc_vars)) - ; emitWorkNC (freshGoals evc_vars) - ; stopWith ev "Dict/Top (solved wanted)" } } - - finish_derived loc theta - = -- Use type-class instances for Deriveds, in the hope - -- of generating some improvements - -- C.f. Example 3 of Note [The improvement story] - -- It's easy because no evidence is involved - do { emitNewDeriveds loc theta - ; traceTcS "finish_derived" (ppr (ctl_depth loc)) - ; stopWith ev "Dict/Top (solved derived)" } - chooseInstance work_item lookup_res = pprPanic "chooseInstance" (ppr work_item $$ ppr lookup_res) checkInstanceOK :: CtLoc -> InstanceWhat -> TcPredType -> TcS CtLoc -- Check that it's OK to use this insstance: -- (a) the use is well staged in the Template Haskell sense --- (b) we have not recursed too deep -- Returns the CtLoc to used for sub-goals +-- Probably also want to call checkReductionDepth, but this function +-- does not do so to enable special handling for Deriveds in chooseInstance checkInstanceOK loc what pred = do { checkWellStagedDFun loc what pred - ; checkReductionDepth deeper_loc pred ; return deeper_loc } where deeper_loc = zap_origin (bumpCtLocDepth loc) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6cf1819f586e5abae39ca19430ad9d0f1fcb94d4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6cf1819f586e5abae39ca19430ad9d0f1fcb94d4 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 Tue Nov 10 19:23:20 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 14:23:20 -0500 Subject: [Git][ghc/ghc][wip/bump-ci] gitlab-ci: Try cleaning up hadrian directory Message-ID: <5faae8a81cdd5_10ee3ffbae4edad81263194@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-ci at Glasgow Haskell Compiler / GHC Commits: cc4c79dc by Ben Gamari at 2020-11-10T14:22:58-05:00 gitlab-ci: Try cleaning up hadrian directory - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -53,6 +53,7 @@ ghc-linters: .validate-hadrian: allow_failure: true script: + - rm -Rf hadrian; git checkout . - git clean -xdf && git submodule foreach git clean -xdf - bash .circleci/prepare-system.sh - if [[ -d ./cabal-cache ]]; then cp -R ./.cabal-cache ~/.cabal-cache; fi @@ -86,6 +87,7 @@ validate-x86_64-linux-deb8-hadrian: variables: TEST_TYPE: test before_script: + - rm -Rf hadrian; git checkout . - git clean -xdf && git submodule foreach git clean -xdf script: - ./boot @@ -120,6 +122,7 @@ validate-x86_64-darwin: ac_cv_func_clock_gettime: "no" LANG: "en_US.UTF-8" before_script: + - rm -Rf hadrian; git checkout . - git clean -xdf && git submodule foreach git clean -xdf - python .gitlab/fix-submodules.py - git submodule sync --recursive @@ -148,6 +151,7 @@ validate-x86_64-darwin: tags: - x86_64-linux before_script: + - rm -Rf hadrian; git checkout . - git clean -xdf && git submodule foreach git clean -xdf - python3 .gitlab/fix-submodules.py - git submodule sync --recursive @@ -372,6 +376,7 @@ validate-x86_64-linux-fedora27: .validate-windows: before_script: + - rm -Rf hadrian; git checkout . - git clean -xdf - git submodule foreach git clean -xdf View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc4c79dc896c630f0693dcdf2c78685041117daa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc4c79dc896c630f0693dcdf2c78685041117daa 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 Tue Nov 10 19:25:08 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 14:25:08 -0500 Subject: [Git][ghc/ghc][wip/T17609] 7 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5faae914a0196_10ee3ffbd5a8609012633d8@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - 811ed43f by Ben Gamari at 2020-11-10T14:24:59-05:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - 541815b6 by Ben Gamari at 2020-11-10T14:25:00-05:00 Add Note cross-reference for unique tag allocations - - - - - 14 changed files: - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Types/Unique.hs - includes/rts/storage/Closures.h - includes/rts/storage/Heap.h - includes/rts/storage/TSO.h - libraries/base/GHC/Exts.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/Heap.c - rts/linker/PEi386.c - + testsuite/tests/typecheck/should_compile/T17186.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Builtin/Uniques.hs ===================================== @@ -296,6 +296,9 @@ getTupleDataConName boxity n = * * ************************************************************************ +Note [Unique tag allocation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + Allocation of unique supply characters: v,t,u : for renumbering value-, type- and usage- vars. B: builtin ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -12,6 +12,7 @@ import GHC.Cmm.DebugBlock import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Platform +import GHC.Types.SrcLoc import GHC.Types.Unique import GHC.Types.Unique.Supply @@ -46,11 +47,12 @@ dwarfGen config modLoc us blocks = do compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + producer = dwarfStringFromString $ cProjectName ++ " " ++ cProjectVersion dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) - , dwName = fromMaybe "" (ml_hs_file modLoc) - , dwCompDir = addTrailingPathSeparator compPath - , dwProducer = cProjectName ++ " " ++ cProjectVersion + , dwName = dwarfStringFromString $ fromMaybe "" (ml_hs_file modLoc) + , dwCompDir = dwarfStringFromString $ addTrailingPathSeparator compPath + , dwProducer = producer , dwLowLabel = lowLabel , dwHighLabel = highLabel , dwLineLabel = dwarfLineLabel @@ -76,6 +78,9 @@ dwarfGen config modLoc us blocks = do , compileUnitFooter platform unitU ] + -- .debug_str section: Strings + let stringsSct = dwarfStringsSection platform (dwarfInfoStrings dwarfUnit) + -- .debug_line section: Generated mainly by the assembler, but we -- need to label it let lineSct = dwarfLineSection platform $$ @@ -92,7 +97,7 @@ dwarfGen config modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection platform $$ pprDwarfARanges platform aranges' unitU - return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') + return (infoSct $$ stringsSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. -- With split sections, each proc needs its own entry, since they may get @@ -177,7 +182,7 @@ parent, B. procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) - , dwName = case dblSourceTick prc of + , dwName = dwarfStringFromString $ case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) , dwLabel = dblCLabel prc @@ -208,7 +213,13 @@ blockToDwarf blk | otherwise = Nothing -- block was optimized out tickToDwarf :: Tickish () -> [DwarfInfo] -tickToDwarf (SourceNote ss _) = [DwarfSrcNote ss] +tickToDwarf (SourceNote ss _) = + [DwarfSrcNote { dwSpanFile = dwarfStringFromFastString (srcSpanFile ss) + , dwSpanStartLine = srcSpanStartLine ss + , dwSpanStartCol = srcSpanStartCol ss + , dwSpanEndLine = srcSpanEndLine ss + , dwSpanEndCol = srcSpanEndCol ss + }] tickToDwarf _ = [] -- | Generates the data for the debug frame section, which encodes the ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -86,12 +86,14 @@ dW_CHILDREN_no, dW_CHILDREN_yes :: Word8 dW_CHILDREN_no = 0 dW_CHILDREN_yes = 1 -dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, dW_FORM_string, dW_FORM_flag, +dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, + dW_FORM_strp,dW_FORM_string, dW_FORM_flag, dW_FORM_block1, dW_FORM_ref4, dW_FORM_ref_addr, dW_FORM_flag_present :: Word dW_FORM_addr = 0x01 dW_FORM_data2 = 0x05 dW_FORM_data4 = 0x06 dW_FORM_string = 0x08 +dW_FORM_strp = 0x0e dW_FORM_flag = 0x0c dW_FORM_block1 = 0x0a dW_FORM_ref_addr = 0x10 @@ -145,11 +147,13 @@ dW_OP_call_frame_cfa = 0x9c -- * Dwarf section declarations dwarfInfoSection, dwarfAbbrevSection, dwarfLineSection, - dwarfFrameSection, dwarfGhcSection, dwarfARangesSection :: Platform -> SDoc + dwarfFrameSection, dwarfStringSection, + dwarfGhcSection, dwarfARangesSection :: Platform -> SDoc dwarfInfoSection platform = dwarfSection platform "info" dwarfAbbrevSection platform = dwarfSection platform "abbrev" dwarfLineSection platform = dwarfSection platform "line" dwarfFrameSection platform = dwarfSection platform "frame" +dwarfStringSection platform = dwarfSection platform "str" dwarfGhcSection platform = dwarfSection platform "ghc" dwarfARangesSection platform = dwarfSection platform "aranges" @@ -165,11 +169,13 @@ dwarfSection platform name = -> text "\t.section .debug_" <> text name <> text ",\"dr\"" -- * Dwarf section labels -dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel :: PtrString +dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel, + dwarfStringLabel :: PtrString dwarfInfoLabel = sLit ".Lsection_info" dwarfAbbrevLabel = sLit ".Lsection_abbrev" dwarfLineLabel = sLit ".Lsection_line" dwarfFrameLabel = sLit ".Lsection_frame" +dwarfStringLabel = sLit ".Lsection_str" -- | Mapping of registers to DWARF register numbers dwarfRegNo :: Platform -> Reg -> Word8 ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -2,12 +2,19 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RecordWildCards #-} module GHC.CmmToAsm.Dwarf.Types ( -- * Dwarf information DwarfInfo(..) , pprDwarfInfo , pprAbbrevDecls + , dwarfInfoStrings + -- * Dwarf Strings section + , DwarfString + , dwarfStringsSection + , dwarfStringFromString + , dwarfStringFromFastString -- * Dwarf address range table , DwarfARange(..) , pprDwarfARanges @@ -32,18 +39,15 @@ import GHC.Prelude import GHC.Cmm.DebugBlock import GHC.Cmm.CLabel import GHC.Cmm.Expr ( GlobalReg(..) ) -import GHC.Utils.Encoding import GHC.Data.FastString import GHC.Utils.Outputable import GHC.Platform import GHC.Types.Unique +import GHC.Types.Unique.Set import GHC.Platform.Reg -import GHC.Types.SrcLoc -import GHC.Utils.Misc import GHC.CmmToAsm.Dwarf.Constants -import qualified Data.ByteString as BS import qualified Control.Monad.Trans.State.Strict as S import Control.Monad (zipWithM, join) import Data.Bits @@ -53,18 +57,49 @@ import Data.Char import GHC.Platform.Regs +-- | A string in the DWARF @.debug_str@ section. +newtype DwarfString = DwarfString FastString + +instance Uniquable DwarfString where + getUnique (DwarfString fs) = getUnique fs + +dwarfStringFromString :: String -> DwarfString +dwarfStringFromString = dwarfStringFromFastString . fsLit + +dwarfStringFromFastString :: FastString -> DwarfString +dwarfStringFromFastString = DwarfString + +dwarfStringSymbol :: DwarfString -> CLabel +dwarfStringSymbol (DwarfString fs) = + mkAsmTempDerivedLabel (mkAsmTempLabel fs) (fsLit "_fstr") + +pprDwarfString :: Platform -> DwarfString -> SDoc +pprDwarfString plat s = + sectionOffset plat (pdoc plat $ dwarfStringSymbol s) (ptext dwarfStringLabel) + +dwarfStringsSection :: Platform -> UniqSet DwarfString -> SDoc +dwarfStringsSection platform xs = vcat + [ ptext dwarfStringLabel <> colon + , dwarfStringSection platform + , vcat (map string $ nonDetEltsUniqSet xs) + ] + where + string :: DwarfString -> SDoc + string dstr@(DwarfString fstr) = + pdoc platform (dwarfStringSymbol dstr) <> colon $$ pprFastString fstr + -- | Individual dwarf records. Each one will be encoded as an entry in -- the @.debug_info@ section. data DwarfInfo = DwarfCompileUnit { dwChildren :: [DwarfInfo] - , dwName :: String - , dwProducer :: String - , dwCompDir :: String + , dwName :: DwarfString + , dwProducer :: DwarfString + , dwCompDir :: DwarfString , dwLowLabel :: CLabel , dwHighLabel :: CLabel , dwLineLabel :: PtrString } | DwarfSubprogram { dwChildren :: [DwarfInfo] - , dwName :: String + , dwName :: DwarfString , dwLabel :: CLabel , dwParent :: Maybe CLabel -- ^ label of DIE belonging to the parent tick @@ -73,9 +108,23 @@ data DwarfInfo , dwLabel :: CLabel , dwMarker :: Maybe CLabel } - | DwarfSrcNote { dwSrcSpan :: RealSrcSpan + | DwarfSrcNote { dwSpanFile :: !DwarfString + , dwSpanStartLine :: !Int + , dwSpanStartCol :: !Int + , dwSpanEndLine :: !Int + , dwSpanEndCol :: !Int } +-- | 'DwarfStrings' mentioned by the given 'DwarfInfo'. +dwarfInfoStrings :: DwarfInfo -> UniqSet DwarfString +dwarfInfoStrings dwinfo = + case dwinfo of + DwarfCompileUnit {..} -> mkUniqSet [dwName, dwProducer, dwCompDir] `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfSubprogram {..} -> unitUniqSet dwName `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfBlock {..} -> foldMap dwarfInfoStrings dwChildren + DwarfSrcNote {..} -> unitUniqSet dwSpanFile + + -- | Abbreviation codes used for encoding above records in the -- @.debug_info@ section. data DwarfAbbrev @@ -104,7 +153,7 @@ pprAbbrevDecls platform haveDebugLine = -- These are shared between DwAbbrSubprogram and -- DwAbbrSubprogramWithParent subprogramAttrs = - [ (dW_AT_name, dW_FORM_string) + [ (dW_AT_name, dW_FORM_strp) , (dW_AT_MIPS_linkage_name, dW_FORM_string) , (dW_AT_external, dW_FORM_flag) , (dW_AT_low_pc, dW_FORM_addr) @@ -114,10 +163,10 @@ pprAbbrevDecls platform haveDebugLine = in dwarfAbbrevSection platform $$ ptext dwarfAbbrevLabel <> colon $$ mkAbbrev DwAbbrCompileUnit dW_TAG_compile_unit dW_CHILDREN_yes - ([(dW_AT_name, dW_FORM_string) - , (dW_AT_producer, dW_FORM_string) + ([(dW_AT_name, dW_FORM_strp) + , (dW_AT_producer, dW_FORM_strp) , (dW_AT_language, dW_FORM_data4) - , (dW_AT_comp_dir, dW_FORM_string) + , (dW_AT_comp_dir, dW_FORM_strp) , (dW_AT_use_UTF8, dW_FORM_flag_present) -- not represented in body , (dW_AT_low_pc, dW_FORM_addr) , (dW_AT_high_pc, dW_FORM_addr) @@ -138,7 +187,7 @@ pprAbbrevDecls platform haveDebugLine = , (dW_AT_high_pc, dW_FORM_addr) ] $$ mkAbbrev DwAbbrGhcSrcNote dW_TAG_ghc_src_note dW_CHILDREN_no - [ (dW_AT_ghc_span_file, dW_FORM_string) + [ (dW_AT_ghc_span_file, dW_FORM_strp) , (dW_AT_ghc_span_start_line, dW_FORM_data4) , (dW_AT_ghc_span_start_col, dW_FORM_data2) , (dW_AT_ghc_span_end_line, dW_FORM_data4) @@ -174,10 +223,10 @@ pprDwarfInfoOpen :: Platform -> Bool -> DwarfInfo -> SDoc pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowLabel highLabel lineLbl) = pprAbbrev DwAbbrCompileUnit - $$ pprString name - $$ pprString producer + $$ pprDwarfString platform name + $$ pprDwarfString platform producer $$ pprData4 dW_LANG_Haskell - $$ pprString compDir + $$ pprDwarfString platform compDir $$ pprWord platform (pdoc platform lowLabel) $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc @@ -186,7 +235,7 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = pdoc platform (mkAsmTempDieLabel label) <> colon $$ pprAbbrev abbrev - $$ pprString name + $$ pprDwarfString platform name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) @@ -209,13 +258,13 @@ pprDwarfInfoOpen platform _ (DwarfBlock _ label (Just marker)) = $$ pprLabelString platform label $$ pprWord platform (pdoc platform marker) $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel marker) -pprDwarfInfoOpen _ _ (DwarfSrcNote ss) = +pprDwarfInfoOpen platform _ (DwarfSrcNote {..}) = pprAbbrev DwAbbrGhcSrcNote - $$ pprString' (ftext $ srcSpanFile ss) - $$ pprData4 (fromIntegral $ srcSpanStartLine ss) - $$ pprHalf (fromIntegral $ srcSpanStartCol ss) - $$ pprData4 (fromIntegral $ srcSpanEndLine ss) - $$ pprHalf (fromIntegral $ srcSpanEndCol ss) + $$ pprDwarfString platform dwSpanFile + $$ pprData4 (fromIntegral dwSpanStartLine) + $$ pprHalf (fromIntegral dwSpanStartCol) + $$ pprData4 (fromIntegral dwSpanEndLine) + $$ pprHalf (fromIntegral dwSpanEndCol) -- | Close a DWARF info record with children pprDwarfInfoClose :: SDoc @@ -584,12 +633,8 @@ pprString' :: SDoc -> SDoc pprString' str = text "\t.asciz \"" <> str <> char '"' -- | Generate a string constant. We take care to escape the string. -pprString :: String -> SDoc -pprString str - = pprString' $ hcat $ map escapeChar $ - if str `lengthIs` utf8EncodedLength str - then str - else map (chr . fromIntegral) $ BS.unpack $ bytesFS $ mkFastString str +pprFastString :: FastString -> SDoc +pprFastString = pprString' . hcat . map escapeChar . unpackFS -- | Escape a single non-unicode character escapeChar :: Char -> SDoc ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -68,8 +68,11 @@ import Data.Bits * * ************************************************************************ -The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . -Fast comparison is everything on @Uniques@: +The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . The +allocation of these is documented in Note [Unique tag allocation] in +GHC.Builtin.Uniques. + +Fast comparison is everything on @Uniques at . -} -- | Unique identifier. ===================================== includes/rts/storage/Closures.h ===================================== @@ -63,6 +63,11 @@ typedef struct { -------------------------------------------------------------------------- */ typedef struct { + // If TABLES_NEXT_TO_CODE is defined, then `info` is offset by + // `sizeof(StgInfoTable)` and so points to the `code` field of the + // StgInfoTable! You may want to use `get_itbl` to get the pointer to the + // start of the info table. See + // https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/rts/storage/heap-objects#tables_next_to_code. const StgInfoTable* info; #if defined(PROFILING) StgProfHeader prof; ===================================== includes/rts/storage/Heap.h ===================================== @@ -16,3 +16,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs , StgClosure *fun, StgClosure **payload, StgWord size); StgWord heap_view_closureSize(StgClosure *closure); + +/* + * Collect the pointers of a closure into the given array. `size` should be + * large enough to hold all collected pointers e.g. + * `heap_view_closureSize(closure)`. Returns the number of pointers collected. + * The caller must ensure that `closure` is not modified (or moved by the GC) + * for the duration of the call to `collect_pointers`. + */ +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[]); ===================================== includes/rts/storage/TSO.h ===================================== @@ -242,10 +242,22 @@ typedef struct StgTSO_ { typedef struct StgStack_ { StgHeader header; - StgWord32 stack_size; // stack size in *words* + + /* Size of the `stack` field in *words*. This is not affected by how much of + * the stack space is used, nor if more stack space is linked to by an + * UNDERFLOW_FRAME. + */ + StgWord32 stack_size; + StgWord8 dirty; // non-zero => dirty StgWord8 marking; // non-zero => someone is currently marking the stack - StgPtr sp; // current stack pointer + + /* Pointer to the "top" of the stack i.e. the most recently written address. + * The stack is filled downwards, so the "top" of the stack starts with `sp + * = stack + stack_size` and is decremented as the stack fills with data. + * See comment on "Invariants" below. + */ + StgPtr sp; StgWord stack[]; } StgStack; ===================================== libraries/base/GHC/Exts.hs ===================================== @@ -72,7 +72,7 @@ module GHC.Exts breakpoint, breakpointCond, -- * Ids with special behaviour - inline, noinline, lazy, oneShot, + inline, noinline, lazy, oneShot, SPEC (..), -- * Running 'RealWorld' state thread runRW#, ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -7,6 +7,9 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE UnliftedFFITypes #-} {-| Module : GHC.Exts.Heap @@ -25,6 +28,7 @@ module GHC.Exts.Heap ( , ClosureType(..) , PrimType(..) , HasHeapRep(getClosureData) + , getClosureDataFromHeapRep -- * Info Table types , StgInfoTable(..) @@ -58,7 +62,7 @@ import GHC.Exts.Heap.Utils import Control.Monad import Data.Bits -import GHC.Arr +import Foreign import GHC.Exts import GHC.Int import GHC.Word @@ -66,13 +70,19 @@ import GHC.Word #include "ghcconfig.h" class HasHeapRep (a :: TYPE rep) where - getClosureData :: a -> IO Closure + + -- | Decode a closure to it's heap representation ('GenClosure'). + getClosureData + :: a + -- ^ Closure to decode. + -> IO Closure + -- ^ Heap representation of the closure. instance HasHeapRep (a :: TYPE 'LiftedRep) where - getClosureData = getClosure + getClosureData = getClosureDataFromHeapObject instance HasHeapRep (a :: TYPE 'UnliftedRep) where - getClosureData x = getClosure (unsafeCoerce# x) + getClosureData x = getClosureDataFromHeapObject (unsafeCoerce# x) instance Int# ~ a => HasHeapRep (a :: TYPE 'IntRep) where getClosureData x = return $ @@ -102,49 +112,84 @@ instance Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) where getClosureData x = return $ DoubleClosure { ptipe = PDouble, doubleVal = D# x } --- | This returns the raw representation of the given argument. The second --- component of the triple is the raw words of the closure on the heap, and the --- third component is those words that are actually pointers. Once back in the --- Haskell world, the raw words that hold pointers may be outdated after a --- garbage collector run, but the corresponding values in 'Box's will still --- point to the correct value. -getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box]) -getClosureRaw x = do +-- | Get the heap representation of a closure _at this moment_, even if it is +-- unevaluated or an indirection or other exotic stuff. Beware when passing +-- something to this function, the same caveats as for +-- 'GHC.Exts.Heap.Closures.asBox' apply. +-- +-- For most use cases 'getClosureData' is an easier to use alternative. +-- +-- Currently TSO and STACK objects will return `UnsupportedClosure`. This is +-- because it is not memory safe to extract TSO and STACK objects (done via +-- `unpackClosure#`). Other threads may be mutating those objects and interleave +-- with reads in `unpackClosure#`. This is particularly problematic with STACKs +-- where pointer values may be overwritten by non-pointer values as the +-- corresponding haskell thread runs. +getClosureDataFromHeapObject + :: a + -- ^ Heap object to decode. + -> IO Closure + -- ^ Heap representation of the closure. +getClosureDataFromHeapObject x = do case unpackClosure# x of --- This is a hack to cover the bootstrap compiler using the old version of --- 'unpackClosure'. The new 'unpackClosure' return values are not merely --- a reordering, so using the old version would not work. - (# iptr, dat, pointers #) -> do - let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE - end = fromIntegral nelems - 1 - rawWds = [W# (indexWordArray# dat i) | I# i <- [0.. end] ] - pelems = I# (sizeofArray# pointers) - ptrList = amap' Box $ Array 0 (pelems - 1) pelems pointers - pure (Ptr iptr, rawWds, ptrList) - --- From GHC.Runtime.Heap.Inspect -amap' :: (t -> b) -> Array Int t -> [b] -amap' f (Array i0 i _ arr#) = map g [0 .. i - i0] - where g (I# i#) = case indexArray# arr# i# of - (# e #) -> f e - --- | This function returns a parsed heap representation of the argument _at --- this moment_, even if it is unevaluated or an indirection or other exotic --- stuff. Beware when passing something to this function, the same caveats as --- for 'asBox' apply. -getClosure :: a -> IO Closure -getClosure x = do - (iptr, wds, pts) <- getClosureRaw x - itbl <- peekItbl iptr - -- The remaining words after the header - let rawWds = drop (closureTypeHeaderSize (tipe itbl)) wds - -- For data args in a pointers then non-pointers closure - -- This is incorrect in non pointers-first setups - -- not sure if that happens - npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) wds +#if MIN_VERSION_ghc_prim(0,5,3) + (# infoTableAddr, heapRep, pointersArray #) -> do +#else + -- This is a hack to cover the bootstrap compiler using the old version + -- of 'unpackClosure'. The new 'unpackClosure' return values are not + -- merely a reordering, so using the old version would not work. + (# infoTableAddr, pointersArray, heapRep #) -> do +#endif + let infoTablePtr = Ptr infoTableAddr + ptrList = [case indexArray# pointersArray i of + (# ptr #) -> Box ptr + | I# i <- [0..(I# (sizeofArray# pointersArray)) - 1] + ] + + infoTable <- peekItbl infoTablePtr + case tipe infoTable of + TSO -> pure $ UnsupportedClosure infoTable + STACK -> pure $ UnsupportedClosure infoTable + _ -> getClosureDataFromHeapRep heapRep infoTablePtr ptrList + +-- | Convert an unpacked heap object, to a `GenClosure b`. The inputs to this +-- function can be generated from a heap object using `unpackClosure#`. +getClosureDataFromHeapRep + :: ByteArray# + -- ^ Heap representation of the closure as returned by `unpackClosure#`. + -- This includes all of the object including the header, info table + -- pointer, pointer data, and non-pointer data. The ByteArray# may be + -- pinned or unpinned. + -> Ptr StgInfoTable + -- ^ Pointer to the `StgInfoTable` of the closure, extracted from the heap + -- representation. The info table must not be movable by GC i.e. must be in + -- pinned or off-heap memory. + -> [b] + -- ^ Pointers in the payload of the closure, extracted from the heap + -- representation as returned by `collect_pointers()` in `Heap.c`. The type + -- `b` is some representation of a pointer e.g. `Any` or `Ptr Any`. + -> IO (GenClosure b) + -- ^ Heap representation of the closure. +getClosureDataFromHeapRep heapRep infoTablePtr pts = do + itbl <- peekItbl infoTablePtr + let -- heapRep as a list of words. + rawHeapWords :: [Word] + rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ] + where + nelems = (I# (sizeofByteArray# heapRep)) `div` wORD_SIZE + end = fromIntegral nelems - 1 + + -- Just the payload of rawHeapWords (no header). + payloadWords :: [Word] + payloadWords = drop (closureTypeHeaderSize (tipe itbl)) rawHeapWords + + -- The non-pointer words in the payload. Only valid for closures with a + -- "pointers first" layout. Not valid for bit field layout. + npts :: [Word] + npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) rawHeapWords case tipe itbl of t | t >= CONSTR && t <= CONSTR_NOCAF -> do - (p, m, n) <- dataConNames iptr + (p, m, n) <- dataConNames infoTablePtr if m == "GHC.ByteCode.Instr" && n == "BreakInfo" then pure $ UnsupportedClosure itbl else pure $ ConstrClosure itbl pts npts p m n @@ -164,9 +209,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to AP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 raw words to AP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ APClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -181,9 +226,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to PAP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail "Expected at least 2 raw words to PAP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ PAPClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -218,10 +263,10 @@ getClosure x = do unless (length pts >= 3) $ fail $ "Expected at least 3 ptr argument to BCO, found " ++ show (length pts) - unless (length rawWds >= 4) $ + unless (length payloadWords >= 4) $ fail $ "Expected at least 4 words to BCO, found " - ++ show (length rawWds) - let splitWord = rawWds !! 3 + ++ show (length payloadWords) + let splitWord = payloadWords !! 3 pure $ BCOClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -230,27 +275,30 @@ getClosure x = do (fromIntegral splitWord) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) #endif - (drop 4 rawWds) + (drop 4 payloadWords) ARR_WORDS -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 words to ARR_WORDS, found " - ++ show (length rawWds) - pure $ ArrWordsClosure itbl (head rawWds) (tail rawWds) + ++ show (length payloadWords) + pure $ ArrWordsClosure itbl (head payloadWords) (tail payloadWords) t | t >= MUT_ARR_PTRS_CLEAN && t <= MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 words to MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ MutArrClosure itbl (rawWds !! 0) (rawWds !! 1) pts + ++ "found " ++ show (length payloadWords) + pure $ MutArrClosure itbl (payloadWords !! 0) (payloadWords !! 1) pts t | t >= SMALL_MUT_ARR_PTRS_CLEAN && t <= SMALL_MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 word to SMALL_MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ SmallMutArrClosure itbl (rawWds !! 0) pts + ++ "found " ++ show (length payloadWords) + pure $ SmallMutArrClosure itbl (payloadWords !! 0) pts - t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> + t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> do + unless (length pts >= 1) $ + fail $ "Expected at least 1 words to MUT_VAR, found " + ++ show (length pts) pure $ MutVarClosure itbl (head pts) t | t == MVAR_CLEAN || t == MVAR_DIRTY -> do @@ -260,13 +308,12 @@ getClosure x = do pure $ MVarClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) BLOCKING_QUEUE -> - pure $ OtherClosure itbl pts wds + pure $ OtherClosure itbl pts rawHeapWords -- pure $ BlockingQueueClosure itbl -- (pts !! 0) (pts !! 1) (pts !! 2) (pts !! 3) - -- pure $ OtherClosure itbl pts wds + -- pure $ OtherClosure itbl pts rawHeapWords -- - WEAK -> pure $ WeakClosure { info = itbl ===================================== rts/Heap.c ===================================== @@ -76,23 +76,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs } } -StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { - ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); - - StgWord size = heap_view_closureSize(closure); - StgWord nptrs = 0; - StgWord i; - - // First collect all pointers here, with the comfortable memory bound - // of the whole closure. Afterwards we know how many pointers are in - // the closure and then we can allocate space on the heap and copy them - // there - StgClosure *ptrs[size]; - +// See Heap.h +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[size]) { StgClosure **end; - StgClosure **ptr; - const StgInfoTable *info = get_itbl(closure); + StgWord nptrs = 0; + StgWord i; switch (info->type) { case INVALID_OBJECT: @@ -101,6 +90,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { // No pointers case ARR_WORDS: + case STACK: break; // Default layout @@ -123,7 +113,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case FUN_0_2: case FUN_STATIC: end = closure->payload + info->layout.payload.ptrs; - for (ptr = closure->payload; ptr < end; ptr++) { + for (StgClosure **ptr = closure->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -136,7 +126,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case THUNK_0_2: case THUNK_STATIC: end = ((StgThunk *)closure)->payload + info->layout.payload.ptrs; - for (ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { + for (StgClosure **ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -228,6 +218,21 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { break; } + return nptrs; +} + +StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); + + StgWord size = heap_view_closureSize(closure); + + // First collect all pointers here, with the comfortable memory bound + // of the whole closure. Afterwards we know how many pointers are in + // the closure and then we can allocate space on the heap and copy them + // there + StgClosure *ptrs[size]; + StgWord nptrs = collect_pointers(closure, size, ptrs); + size = nptrs + mutArrPtrsCardTableSize(nptrs); StgMutArrPtrs *arr = (StgMutArrPtrs *)allocate(cap, sizeofW(StgMutArrPtrs) + size); @@ -236,7 +241,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { arr->ptrs = nptrs; arr->size = size; - for (i = 0; ipayload[i] = ptrs[i]; } ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } ===================================== testsuite/tests/typecheck/should_compile/T17186.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE TypeOperators, AllowAmbiguousTypes #-} + +module T17186 where + +-- This test is significantly abbreviated from what was posted; see +-- #16512 for more context. + +type family Dim v + +type family v `OfDim` (n :: Dim v) = r | r -> n + +(!*^) :: Dim m `OfDim` j -> Dim m `OfDim` i +(!*^) = undefined ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,4 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) - +test('T17186', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ab96a4ad5eec76235d1512d8e64ee5a013862a6a...541815b6393f15ecad603d608eb888dffb30bf8f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ab96a4ad5eec76235d1512d8e64ee5a013862a6a...541815b6393f15ecad603d608eb888dffb30bf8f 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 Tue Nov 10 21:08:10 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 16:08:10 -0500 Subject: [Git][ghc/ghc][wip/T17609] 3 commits: Unique: Ensure that we don't overflow tag Message-ID: <5fab013a3b387_10ee108441c01275488@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17609 at Glasgow Haskell Compiler / GHC Commits: 8e2d0e71 by Ben Gamari at 2020-11-10T16:07:33-05:00 Unique: Ensure that we don't overflow tag Add DEBUG assertions to ensure that mkUnique, incrUnique, and stepUnique don't overflow the tag. - - - - - 4b7dc83d by Ben Gamari at 2020-11-10T16:07:33-05:00 nativeGen: Deduplicate DWARF strings As noted in #17609, we previously made no attempt to deduplicate strings. This resulted in unnecessarily long compile times and large object files. Fix this. Fixes #17609. - - - - - cc2b9065 by Ben Gamari at 2020-11-10T16:07:33-05:00 Add Note cross-reference for unique tag allocations - - - - - 5 changed files: - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Builtin/Uniques.hs ===================================== @@ -296,6 +296,9 @@ getTupleDataConName boxity n = * * ************************************************************************ +Note [Unique tag allocation] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + Allocation of unique supply characters: v,t,u : for renumbering value-, type- and usage- vars. B: builtin ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -12,6 +12,7 @@ import GHC.Cmm.DebugBlock import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Platform +import GHC.Types.SrcLoc import GHC.Types.Unique import GHC.Types.Unique.Supply @@ -46,11 +47,12 @@ dwarfGen config modLoc us blocks = do compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + producer = dwarfStringFromString $ cProjectName ++ " " ++ cProjectVersion dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) - , dwName = fromMaybe "" (ml_hs_file modLoc) - , dwCompDir = addTrailingPathSeparator compPath - , dwProducer = cProjectName ++ " " ++ cProjectVersion + , dwName = dwarfStringFromString $ fromMaybe "" (ml_hs_file modLoc) + , dwCompDir = dwarfStringFromString $ addTrailingPathSeparator compPath + , dwProducer = producer , dwLowLabel = lowLabel , dwHighLabel = highLabel , dwLineLabel = dwarfLineLabel @@ -76,6 +78,9 @@ dwarfGen config modLoc us blocks = do , compileUnitFooter platform unitU ] + -- .debug_str section: Strings + let stringsSct = dwarfStringsSection platform (dwarfInfoStrings dwarfUnit) + -- .debug_line section: Generated mainly by the assembler, but we -- need to label it let lineSct = dwarfLineSection platform $$ @@ -92,7 +97,7 @@ dwarfGen config modLoc us blocks = do | otherwise = [DwarfARange lowLabel highLabel] let aranges = dwarfARangesSection platform $$ pprDwarfARanges platform aranges' unitU - return (infoSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') + return (infoSct $$ stringsSct $$ abbrevSct $$ lineSct $$ frameSct $$ aranges, us'') -- | Build an address range entry for one proc. -- With split sections, each proc needs its own entry, since they may get @@ -177,7 +182,7 @@ parent, B. procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) - , dwName = case dblSourceTick prc of + , dwName = dwarfStringFromString $ case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) , dwLabel = dblCLabel prc @@ -208,7 +213,13 @@ blockToDwarf blk | otherwise = Nothing -- block was optimized out tickToDwarf :: Tickish () -> [DwarfInfo] -tickToDwarf (SourceNote ss _) = [DwarfSrcNote ss] +tickToDwarf (SourceNote ss _) = + [DwarfSrcNote { dwSpanFile = dwarfStringFromFastString (srcSpanFile ss) + , dwSpanStartLine = srcSpanStartLine ss + , dwSpanStartCol = srcSpanStartCol ss + , dwSpanEndLine = srcSpanEndLine ss + , dwSpanEndCol = srcSpanEndCol ss + }] tickToDwarf _ = [] -- | Generates the data for the debug frame section, which encodes the ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -86,12 +86,14 @@ dW_CHILDREN_no, dW_CHILDREN_yes :: Word8 dW_CHILDREN_no = 0 dW_CHILDREN_yes = 1 -dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, dW_FORM_string, dW_FORM_flag, +dW_FORM_addr, dW_FORM_data2, dW_FORM_data4, + dW_FORM_strp,dW_FORM_string, dW_FORM_flag, dW_FORM_block1, dW_FORM_ref4, dW_FORM_ref_addr, dW_FORM_flag_present :: Word dW_FORM_addr = 0x01 dW_FORM_data2 = 0x05 dW_FORM_data4 = 0x06 dW_FORM_string = 0x08 +dW_FORM_strp = 0x0e dW_FORM_flag = 0x0c dW_FORM_block1 = 0x0a dW_FORM_ref_addr = 0x10 @@ -145,11 +147,13 @@ dW_OP_call_frame_cfa = 0x9c -- * Dwarf section declarations dwarfInfoSection, dwarfAbbrevSection, dwarfLineSection, - dwarfFrameSection, dwarfGhcSection, dwarfARangesSection :: Platform -> SDoc + dwarfFrameSection, dwarfStringSection, + dwarfGhcSection, dwarfARangesSection :: Platform -> SDoc dwarfInfoSection platform = dwarfSection platform "info" dwarfAbbrevSection platform = dwarfSection platform "abbrev" dwarfLineSection platform = dwarfSection platform "line" dwarfFrameSection platform = dwarfSection platform "frame" +dwarfStringSection platform = dwarfSection platform "str" dwarfGhcSection platform = dwarfSection platform "ghc" dwarfARangesSection platform = dwarfSection platform "aranges" @@ -165,11 +169,13 @@ dwarfSection platform name = -> text "\t.section .debug_" <> text name <> text ",\"dr\"" -- * Dwarf section labels -dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel :: PtrString +dwarfInfoLabel, dwarfAbbrevLabel, dwarfLineLabel, dwarfFrameLabel, + dwarfStringLabel :: PtrString dwarfInfoLabel = sLit ".Lsection_info" dwarfAbbrevLabel = sLit ".Lsection_abbrev" dwarfLineLabel = sLit ".Lsection_line" dwarfFrameLabel = sLit ".Lsection_frame" +dwarfStringLabel = sLit ".Lsection_str" -- | Mapping of registers to DWARF register numbers dwarfRegNo :: Platform -> Reg -> Word8 ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -2,12 +2,19 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE RecordWildCards #-} module GHC.CmmToAsm.Dwarf.Types ( -- * Dwarf information DwarfInfo(..) , pprDwarfInfo , pprAbbrevDecls + , dwarfInfoStrings + -- * Dwarf Strings section + , DwarfString + , dwarfStringsSection + , dwarfStringFromString + , dwarfStringFromFastString -- * Dwarf address range table , DwarfARange(..) , pprDwarfARanges @@ -32,18 +39,15 @@ import GHC.Prelude import GHC.Cmm.DebugBlock import GHC.Cmm.CLabel import GHC.Cmm.Expr ( GlobalReg(..) ) -import GHC.Utils.Encoding import GHC.Data.FastString import GHC.Utils.Outputable import GHC.Platform import GHC.Types.Unique +import GHC.Types.Unique.Set import GHC.Platform.Reg -import GHC.Types.SrcLoc -import GHC.Utils.Misc import GHC.CmmToAsm.Dwarf.Constants -import qualified Data.ByteString as BS import qualified Control.Monad.Trans.State.Strict as S import Control.Monad (zipWithM, join) import Data.Bits @@ -53,18 +57,55 @@ import Data.Char import GHC.Platform.Regs +-- | A string in the DWARF @.debug_str@ section. +newtype DwarfString = DwarfString FastString + +instance Uniquable DwarfString where + getUnique (DwarfString fs) = getUnique fs + +dwarfStringFromString :: String -> DwarfString +dwarfStringFromString = dwarfStringFromFastString . fsLit + +dwarfStringFromFastString :: FastString -> DwarfString +dwarfStringFromFastString = DwarfString + +dwarfStringSymbol :: DwarfString -> CLabel +dwarfStringSymbol (DwarfString fs) = + mkAsmTempDerivedLabel (mkAsmTempLabel u) (fsLit "_fstr") + where + -- N.B. FastStrings have a tag character of '\x00', which would produce + -- an invalid symbol name. Instead of handling this rare case in + -- pprUniqueAlways, incurring significant overhead in hot paths, we rather + -- override the unique tag here. + u = newTagUnique (getUnique fs) 'S' + +pprDwarfString :: Platform -> DwarfString -> SDoc +pprDwarfString plat s = + sectionOffset plat (pdoc plat $ dwarfStringSymbol s) (ptext dwarfStringLabel) + +dwarfStringsSection :: Platform -> UniqSet DwarfString -> SDoc +dwarfStringsSection platform xs = vcat + [ ptext dwarfStringLabel <> colon + , dwarfStringSection platform + , vcat (map string $ nonDetEltsUniqSet xs) + ] + where + string :: DwarfString -> SDoc + string dstr@(DwarfString fstr) = + pdoc platform (dwarfStringSymbol dstr) <> colon $$ pprFastString fstr + -- | Individual dwarf records. Each one will be encoded as an entry in -- the @.debug_info@ section. data DwarfInfo = DwarfCompileUnit { dwChildren :: [DwarfInfo] - , dwName :: String - , dwProducer :: String - , dwCompDir :: String + , dwName :: DwarfString + , dwProducer :: DwarfString + , dwCompDir :: DwarfString , dwLowLabel :: CLabel , dwHighLabel :: CLabel , dwLineLabel :: PtrString } | DwarfSubprogram { dwChildren :: [DwarfInfo] - , dwName :: String + , dwName :: DwarfString , dwLabel :: CLabel , dwParent :: Maybe CLabel -- ^ label of DIE belonging to the parent tick @@ -73,9 +114,23 @@ data DwarfInfo , dwLabel :: CLabel , dwMarker :: Maybe CLabel } - | DwarfSrcNote { dwSrcSpan :: RealSrcSpan + | DwarfSrcNote { dwSpanFile :: !DwarfString + , dwSpanStartLine :: !Int + , dwSpanStartCol :: !Int + , dwSpanEndLine :: !Int + , dwSpanEndCol :: !Int } +-- | 'DwarfStrings' mentioned by the given 'DwarfInfo'. +dwarfInfoStrings :: DwarfInfo -> UniqSet DwarfString +dwarfInfoStrings dwinfo = + case dwinfo of + DwarfCompileUnit {..} -> mkUniqSet [dwName, dwProducer, dwCompDir] `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfSubprogram {..} -> unitUniqSet dwName `unionUniqSets` foldMap dwarfInfoStrings dwChildren + DwarfBlock {..} -> foldMap dwarfInfoStrings dwChildren + DwarfSrcNote {..} -> unitUniqSet dwSpanFile + + -- | Abbreviation codes used for encoding above records in the -- @.debug_info@ section. data DwarfAbbrev @@ -104,7 +159,7 @@ pprAbbrevDecls platform haveDebugLine = -- These are shared between DwAbbrSubprogram and -- DwAbbrSubprogramWithParent subprogramAttrs = - [ (dW_AT_name, dW_FORM_string) + [ (dW_AT_name, dW_FORM_strp) , (dW_AT_MIPS_linkage_name, dW_FORM_string) , (dW_AT_external, dW_FORM_flag) , (dW_AT_low_pc, dW_FORM_addr) @@ -114,10 +169,10 @@ pprAbbrevDecls platform haveDebugLine = in dwarfAbbrevSection platform $$ ptext dwarfAbbrevLabel <> colon $$ mkAbbrev DwAbbrCompileUnit dW_TAG_compile_unit dW_CHILDREN_yes - ([(dW_AT_name, dW_FORM_string) - , (dW_AT_producer, dW_FORM_string) + ([(dW_AT_name, dW_FORM_strp) + , (dW_AT_producer, dW_FORM_strp) , (dW_AT_language, dW_FORM_data4) - , (dW_AT_comp_dir, dW_FORM_string) + , (dW_AT_comp_dir, dW_FORM_strp) , (dW_AT_use_UTF8, dW_FORM_flag_present) -- not represented in body , (dW_AT_low_pc, dW_FORM_addr) , (dW_AT_high_pc, dW_FORM_addr) @@ -138,7 +193,7 @@ pprAbbrevDecls platform haveDebugLine = , (dW_AT_high_pc, dW_FORM_addr) ] $$ mkAbbrev DwAbbrGhcSrcNote dW_TAG_ghc_src_note dW_CHILDREN_no - [ (dW_AT_ghc_span_file, dW_FORM_string) + [ (dW_AT_ghc_span_file, dW_FORM_strp) , (dW_AT_ghc_span_start_line, dW_FORM_data4) , (dW_AT_ghc_span_start_col, dW_FORM_data2) , (dW_AT_ghc_span_end_line, dW_FORM_data4) @@ -174,10 +229,10 @@ pprDwarfInfoOpen :: Platform -> Bool -> DwarfInfo -> SDoc pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowLabel highLabel lineLbl) = pprAbbrev DwAbbrCompileUnit - $$ pprString name - $$ pprString producer + $$ pprDwarfString platform name + $$ pprDwarfString platform producer $$ pprData4 dW_LANG_Haskell - $$ pprString compDir + $$ pprDwarfString platform compDir $$ pprWord platform (pdoc platform lowLabel) $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc @@ -186,7 +241,7 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = pdoc platform (mkAsmTempDieLabel label) <> colon $$ pprAbbrev abbrev - $$ pprString name + $$ pprDwarfString platform name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) @@ -209,13 +264,13 @@ pprDwarfInfoOpen platform _ (DwarfBlock _ label (Just marker)) = $$ pprLabelString platform label $$ pprWord platform (pdoc platform marker) $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel marker) -pprDwarfInfoOpen _ _ (DwarfSrcNote ss) = +pprDwarfInfoOpen platform _ (DwarfSrcNote {..}) = pprAbbrev DwAbbrGhcSrcNote - $$ pprString' (ftext $ srcSpanFile ss) - $$ pprData4 (fromIntegral $ srcSpanStartLine ss) - $$ pprHalf (fromIntegral $ srcSpanStartCol ss) - $$ pprData4 (fromIntegral $ srcSpanEndLine ss) - $$ pprHalf (fromIntegral $ srcSpanEndCol ss) + $$ pprDwarfString platform dwSpanFile + $$ pprData4 (fromIntegral dwSpanStartLine) + $$ pprHalf (fromIntegral dwSpanStartCol) + $$ pprData4 (fromIntegral dwSpanEndLine) + $$ pprHalf (fromIntegral dwSpanEndCol) -- | Close a DWARF info record with children pprDwarfInfoClose :: SDoc @@ -584,12 +639,8 @@ pprString' :: SDoc -> SDoc pprString' str = text "\t.asciz \"" <> str <> char '"' -- | Generate a string constant. We take care to escape the string. -pprString :: String -> SDoc -pprString str - = pprString' $ hcat $ map escapeChar $ - if str `lengthIs` utf8EncodedLength str - then str - else map (chr . fromIntegral) $ BS.unpack $ bytesFS $ mkFastString str +pprFastString :: FastString -> SDoc +pprFastString = pprString' . hcat . map escapeChar . unpackFS -- | Escape a single non-unicode character escapeChar :: Char -> SDoc ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -61,6 +61,13 @@ import GHC.Exts (indexCharOffAddr#, Char(..), Int(..)) import Data.Char ( chr, ord ) import Data.Bits +-- | Should we enable overflow checks for construction functions? +-- We do this in 32-bit compilers (since the Unique space is quite small on +-- such platforms) and DEBUG compilers (just in case). +tagOverflowChecks :: Bool +tagOverflowChecks = is32Bit || debugIsOn + where is32Bit = finiteBitSize (0 :: Int) < 64 + {- ************************************************************************ * * @@ -68,8 +75,11 @@ import Data.Bits * * ************************************************************************ -The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . -Fast comparison is everything on @Uniques@: +The @Chars@ are ``tag letters'' that identify the @UniqueSupply at . The +allocation of these is documented in Note [Unique tag allocation] in +GHC.Builtin.Uniques. + +Fast comparison is everything on @Uniques at . -} -- | Unique identifier. @@ -104,8 +114,15 @@ mkUniqueGrimily = MkUnique {-# INLINE getKey #-} getKey (MkUnique x) = x -incrUnique (MkUnique i) = MkUnique (i + 1) -stepUnique (MkUnique i) n = MkUnique (i + n) +incrUnique (MkUnique i) + | tagOverflowChecks + , i .&. uniqueMask /= uniqueMask = panic "incrUnique: Unique overflow" + | otherwise = MkUnique (i + 1) + +stepUnique (MkUnique i) n + | tagOverflowChecks + , i .&. uniqueMask /= uniqueMask = panic "stepUnique: Unique overflow" + | otherwise = MkUnique (i + n) mkLocalUnique :: Int -> Unique mkLocalUnique i = mkUnique 'X' i @@ -133,10 +150,12 @@ uniqueMask = (1 `shiftL` uNIQUE_BITS) - 1 mkUnique :: Char -> Int -> Unique -- Builds a unique from pieces -- EXPORTED and used only in GHC.Builtin.Uniques mkUnique c i - = MkUnique (tag .|. bits) + | tagOverflowChecks + , bits /= i = panic "mkUnique: Unique overflow" + | otherwise = MkUnique (tag .|. bits) where - tag = ord c `shiftL` uNIQUE_BITS - bits = i .&. uniqueMask + !tag = ord c `shiftL` uNIQUE_BITS + !bits = i .&. uniqueMask unpkUnique (MkUnique u) = let View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/541815b6393f15ecad603d608eb888dffb30bf8f...cc2b9065d9614d42f474ab3a405bffc2d29a04f6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/541815b6393f15ecad603d608eb888dffb30bf8f...cc2b9065d9614d42f474ab3a405bffc2d29a04f6 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 Tue Nov 10 21:36:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 16:36:12 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] 1032 commits: rts: Teach getNumProcessors to return available processors Message-ID: <5fab07cc3f9ad_10ee3ffbd50e2c7812799b3@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 4413828b by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Teach getNumProcessors to return available processors Previously we would report the number of physical processors, which can be quite wrong in a containerized setting. Now we rather return how many processors are in our affinity mask when possible. I also refactored the code to prefer platform-specific since this will report logical CPUs instead of physical (using `machdep.cpu.thread_count` on Darwin and `cpuset_getaffinity` on FreeBSD). Fixes #14781. - - - - - 1449435c by Ben Gamari at 2020-05-30T06:07:31-04:00 users-guide: Note change in getNumProcessors in users guide - - - - - 3d960169 by Ben Gamari at 2020-05-30T06:07:31-04:00 rts: Drop compatibility shims for Windows Vista We can now assume that the thread and processor group interfaces are available. - - - - - 7f8f948c by Peter Trommler at 2020-05-30T06:08:07-04:00 PPC NCG: Fix .size directive on powerpc64 ELF v1 Thanks to Sergei Trofimovich for pointing out the issue. Fixes #18237 - - - - - 7c555b05 by Andreas Klebinger at 2020-05-30T06:08:43-04:00 Optimize GHC.Utils.Monad. Many functions in this module are recursive and as such are marked loop breakers. Which means they are unlikely to get an unfolding. This is *bad*. We always want to specialize them to specific Monads. Which requires a visible unfolding at the use site. I rewrote the recursive ones from: foo f x = ... foo x' ... to foo f x = go x where go x = ... As well as giving some pragmas to make all of them available for specialization. The end result is a reduction of allocations of about -1.4% for nofib/spectral/simple/Main.hs when compiled with `-O`. ------------------------- Metric Decrease: T12425 T14683 T5631 T9233 T9675 T9961 WWRec ------------------------- - - - - - 8b1cb5df by Ben Gamari at 2020-05-30T06:09:20-04:00 Windows: Bump Windows toolchain to 0.2 - - - - - 6947231a by Zubin Duggal at 2020-05-30T06:10:02-04:00 Simplify contexts in GHC.Iface.Ext.Ast - - - - - 2ee4f36c by Daniel Gröber at 2020-06-01T06:32:56-04:00 Cleanup OVERWRITING_CLOSURE logic The code is just more confusing than it needs to be. We don't need to mix the threaded check with the ldv profiling check since ldv's init already checks for this. Hence they can be two separate checks. Taking the sanity checking into account is also cleaner via DebugFlags.sanity. No need for checking the DEBUG define. The ZERO_SLOP_FOR_LDV_PROF and ZERO_SLOP_FOR_SANITY_CHECK definitions the old code had also make things a lot more opaque IMO so I removed those. - - - - - 6159559b by Daniel Gröber at 2020-06-01T06:32:56-04:00 Fix OVERWRITING_CLOSURE assuming closures are not inherently used The new ASSERT in LDV_recordDead() was being tripped up by MVars when removeFromMVarBlockedQueue() calls OVERWRITING_CLOSURE() via OVERWRITE_INFO(). - - - - - 38992085 by Daniel Gröber at 2020-06-01T06:32:56-04:00 Always zero shrunk mutable array slop when profiling When shrinking arrays in the profiling way we currently don't always zero the leftover slop. This means we can't traverse such closures in the heap profiler. The old Note [zeroing slop] and #8402 have some rationale for why this is so but I belive the reasoning doesn't apply to mutable closures. There users already have to ensure multiple threads don't step on each other's toes so zeroing should be safe. - - - - - b0c1f2a6 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for #18151 - - - - - 9a99a178 by Ben Gamari at 2020-06-01T06:33:37-04:00 testsuite: Add test for desugaring of PostfixOperators - - - - - 2b89ca5b by Ben Gamari at 2020-06-01T06:33:37-04:00 HsToCore: Eta expand left sections Strangely, the comment next to this code already alluded to the fact that even simply eta-expanding will sacrifice laziness. It's quite unclear how we regressed so far. See #18151. - - - - - d412d7a3 by Kirill Elagin at 2020-06-01T06:34:21-04:00 Winferred-safe-imports: Do not exit with error Currently, when -Winferred-safe-imports is enabled, even when it is not turned into an error, the compiler will still exit with exit code 1 if this warning was emitted. Make sure it is really treated as a warning. - - - - - f945eea5 by Ben Gamari at 2020-06-01T06:34:58-04:00 nonmoving: Optimise log2_ceil - - - - - aab606e4 by Bodigrim at 2020-06-01T06:35:36-04:00 Clarify description of fromListN - - - - - 7e5220e2 by Bodigrim at 2020-06-01T06:35:36-04:00 Apply suggestion to libraries/base/GHC/Exts.hs - - - - - f3fb1ce9 by fendor at 2020-06-01T06:36:18-04:00 Add `isInScope` check to `lintCoercion` Mirrors the behaviour of `lintType`. - - - - - 5ac4d946 by fendor at 2020-06-01T06:36:18-04:00 Lint rhs of IfaceRule - - - - - 1cef6126 by Jeremy Schlatter at 2020-06-01T06:37:00-04:00 Fix wording in documentation The duplicate "orphan instance" phrase here doesn't make sense, and was probably an accident. - - - - - 5aaf08f2 by Takenobu Tani at 2020-06-01T06:37:43-04:00 configure: Modify aclocal.m4 according to new module hierarchy This patch updates file paths according to new module hierarchy [1]: * Rename: * compiler/GHC/Parser.hs <= compiler/parser/Parser.hs * compiler/GHC/Parser/Lexer.hs <= compiler/Parser/Lexer.hs * Add: * compiler/GHC/Cmm/Lexer.hs [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular - - - - - 15857ad8 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Don't fail if we can't unlink __symlink_test Afterall, it's possible we were unable to create it due to lack of symlink permission. - - - - - 4a7229ef by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Refactor ghostscript detection Tamar reported that he saw crashes due to unhandled exceptions. - - - - - 2ab37eaf by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/perf_notes: Fix ill-typed assignments - - - - - e45d5b66 by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite/testutil: Fix bytes/str mismatch - - - - - 7002d0cb by Ben Gamari at 2020-06-01T06:38:26-04:00 testsuite: Work around spurious mypy failure - - - - - 11390e3a by Takenobu Tani at 2020-06-01T06:39:05-04:00 Clean up file paths for new module hierarchy This updates comments only. This patch replaces file references according to new module hierarchy. See also: * https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular * https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 8f2e5732 by Takenobu Tani at 2020-06-01T06:39:05-04:00 Modify file paths to module paths for new module hierarchy This updates comments only. This patch replaces module references according to new module hierarchy [1][2]. For files under the `compiler/` directory, I replace them as module paths instead of file paths. For instance, `GHC.Unit.State` instead of `compiler/GHC/Unit/State.hs` [3]. For current and future haddock's markup, this patch encloses the module name with "" [4]. [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 [3]: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3375#note_276613 [4]: https://haskell-haddock.readthedocs.io/en/latest/markup.html#linking-to-modules - - - - - 68b71c4a by Tom Ellis at 2020-06-01T06:39:55-04:00 Rename the singleton tuple GHC.Tuple.Unit to GHC.Tuple.Solo - - - - - 95da76c2 by Sylvain Henry at 2020-06-01T06:40:41-04:00 Hadrian: fix binary-dist target for cross-compilation - - - - - 730fcd54 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for the @-operator Since GHC diverges from the Haskell Report by allowing the user to define (@) as an infix operator, we better give a good error message when the user does so unintentionally. In general, this is rather hard to do, as some failures will be discovered only in the renamer or the type checker: x :: (Integer, Integer) x @ (a, b) = (1, 2) This patch does *not* address this general case. However, it gives much better error messages when the binding is not syntactically valid: pairs xs @ (_:xs') = zip xs xs' Before this patch, the error message was rather puzzling: <interactive>:1:1: error: Parse error in pattern: pairs After this patch, the error message includes a hint: <interactive>:1:1: error: Parse error in pattern: pairs In a function binding for the ‘@’ operator. Perhaps you meant an as-pattern, which must not be surrounded by whitespace - - - - - 0fde5377 by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TypeApplications With this patch, we always parse f @t as a type application, thereby producing better error messages. This steals two syntactic forms: * Prefix form of the @-operator in expressions. Since the @-operator is a divergence from the Haskell Report anyway, this is not a major loss. * Prefix form of @-patterns. Since we are stealing loose infix form anyway, might as well sacrifice the prefix form for the sake of much better error messages. - - - - - c68e7e1e by Vladislav Zavialov at 2020-06-01T06:41:18-04:00 Improve parser error messages for TemplateHaskellQuotes While [e| |], [t| |], [d| |], and so on, steal syntax from list comprehensions, [| |] and [|| ||] do not steal any syntax. Thus we can improve error messages by always accepting them in the lexer. Turns out the renamer already performs necessary validation. - - - - - 120aedbd by Ben Gamari at 2020-06-01T16:07:02-04:00 gitlab-ci: Disable use of ld.lld on ARMv7 It turns out that lld non-deterministically fails on ARMv7. I suspect this may be due to the a kernel regression as this only started happening when we upgraded to 5.4. Nevertheless, easily avoided by simply sticking with gold. Works around #18280. - - - - - d6279ff0 by Ben Gamari at 2020-06-02T13:03:30-04:00 gitlab-ci: Ensure that workaround for #18280 applies to bindisttest We need to ensure that the `configure` flags working around #18280 are propagated to the bindisttest `configure` as well. - - - - - cb5c31b5 by Ben Gamari at 2020-06-03T17:55:04-04:00 gitlab-ci: Allow ARMv7 job to fail Due to #18298. - - - - - 32a4ae90 by John Ericson at 2020-06-04T04:34:42-04:00 Clean up boot vs non-boot disambiguating types We often have (ModuleName, Bool) or (Module, Bool) pairs for "extended" module names (without or with a unit id) disambiguating boot and normal modules. We think this is important enough across the compiler that it deserves a new nominal product type. We do this with synnoyms and a functor named with a `Gen` prefix, matching other newly created definitions. It was also requested that we keep custom `IsBoot` / `NotBoot` sum type. So we have it too. This means changing many the many bools to use that instead. Updates `haddock` submodule. - - - - - c05756cd by Niklas Hambüchen at 2020-06-04T04:35:24-04:00 docs: Add more details on InterruptibleFFI. Details from https://gitlab.haskell.org/ghc/ghc/issues/8684 and https://github.com/takano-akio/filelock/pull/7#discussion_r280332430 - - - - - 1b975aed by Andrew Martin at 2020-06-04T04:36:03-04:00 Allow finalizeForeignPtr to be called on FinalPtr/PlainPtr. MR 2165 (commit 49301ad6226d9a83d110bee8c419615dd94f5ded) regressed finalizeForeignPtr by throwing exceptions when PlainPtr was encounterd. This regression did not make it into a release of GHC. Here, the original behavior is restored, and FinalPtr is given the same treatment as PlainPtr. - - - - - 2bd3929a by Luke Lau at 2020-06-04T04:36:41-04:00 Fix documentation on type families not being extracted It looks like the location of the Names used for CoAxioms on type families are now located at their type constructors. Previously, Docs.hs thought the Names were located in the RHS, so the RealSrcSpan in the instanceMap and getInstLoc didn't match up. Fixes #18241 - - - - - 6735b9d9 by Ben Gamari at 2020-06-04T04:37:21-04:00 GHC.Hs.Instances: Compile with -O0 This module contains exclusively Data instances, which are going to be slow no matter what we do. Furthermore, they are incredibly slow to compile with optimisation (see #9557). Consequently we compile this with -O0. See #18254. - - - - - c330331a by nineonine at 2020-06-04T04:37:59-04:00 Add test for #17669 - - - - - cab684f0 by Ben Gamari at 2020-06-04T04:38:36-04:00 rts: Add Windows-specific implementation of rtsSleep Previously we would use the POSIX path, which uses `nanosleep`. However, it turns out that `nanosleep` is provided by `libpthread` on Windows. In general we don't want to incur such a dependency. Avoid this by simply using `Sleep` on Windows. Fixes #18272. - - - - - ad44b504 by Ben Gamari at 2020-06-04T04:38:36-04:00 compiler: Disable use of process jobs with process < 1.6.9 Due to #17926. - - - - - 6a4098a4 by Moritz Angermann at 2020-06-04T04:55:51-04:00 [linker] Adds void printLoadedObjects(void); This allows us to dump in-memory object code locations for debugging. Fixup printLoadedObjects prototype - - - - - af5e3a88 by Artem Pelenitsyn at 2020-06-05T03:18:49-04:00 base: fix sign confusion in log1mexp implementation (fix #17125) author: claude (https://gitlab.haskell.org/trac-claude) The correct threshold for log1mexp is -(log 2) with the current specification of log1mexp. This change improves accuracy for large negative inputs. To avoid code duplication, a small helper function is added; it isn't the default implementation in Floating because it needs Ord. This patch does nothing to address that the Haskell specification is different from that in common use in other languages. - - - - - 2b792fac by Simon Peyton Jones at 2020-06-05T09:27:50-04:00 Simple subsumption This patch simplifies GHC to use simple subsumption. Ticket #17775 Implements GHC proposal #287 https://github.com/ghc-proposals/ghc-proposals/blob/master/ proposals/0287-simplify-subsumption.rst All the motivation is described there; I will not repeat it here. The implementation payload: * tcSubType and friends become noticably simpler, because it no longer uses eta-expansion when checking subsumption. * No deeplyInstantiate or deeplySkolemise That in turn means that some tests fail, by design; they can all be fixed by eta expansion. There is a list of such changes below. Implementing the patch led me into a variety of sticky corners, so the patch includes several othe changes, some quite significant: * I made String wired-in, so that "foo" :: String rather than "foo" :: [Char] This improves error messages, and fixes #15679 * The pattern match checker relies on knowing about in-scope equality constraints, andd adds them to the desugarer's environment using addTyCsDs. But the co_fn in a FunBind was missed, and for some reason simple-subsumption ends up with dictionaries there. So I added a call to addTyCsDs. This is really part of #18049. * I moved the ic_telescope field out of Implication and into ForAllSkol instead. This is a nice win; just expresses the code much better. * There was a bug in GHC.Tc.TyCl.Instance.tcDataFamInstHeader. We called checkDataKindSig inside tc_kind_sig, /before/ solveEqualities and zonking. Obviously wrong, easily fixed. * solveLocalEqualitiesX: there was a whole mess in here, around failing fast enough. I discovered a bad latent bug where we could successfully kind-check a type signature, and use it, but have unsolved constraints that could fill in coercion holes in that signature -- aargh. It's all explained in Note [Failure in local type signatures] in GHC.Tc.Solver. Much better now. * I fixed a serious bug in anonymous type holes. IN f :: Int -> (forall a. a -> _) -> Int that "_" should be a unification variable at the /outer/ level; it cannot be instantiated to 'a'. This was plain wrong. New fields mode_lvl and mode_holes in TcTyMode, and auxiliary data type GHC.Tc.Gen.HsType.HoleMode. This fixes #16292, but makes no progress towards the more ambitious #16082 * I got sucked into an enormous refactoring of the reporting of equality errors in GHC.Tc.Errors, especially in mkEqErr1 mkTyVarEqErr misMatchMsg misMatchMsgOrCND In particular, the very tricky mkExpectedActualMsg function is gone. It took me a full day. But the result is far easier to understand. (Still not easy!) This led to various minor improvements in error output, and an enormous number of test-case error wibbles. One particular point: for occurs-check errors I now just say Can't match 'a' against '[a]' rather than using the intimidating language of "occurs check". * Pretty-printing AbsBinds Tests review * Eta expansions T11305: one eta expansion T12082: one eta expansion (undefined) T13585a: one eta expansion T3102: one eta expansion T3692: two eta expansions (tricky) T2239: two eta expansions T16473: one eta determ004: two eta expansions (undefined) annfail06: two eta (undefined) T17923: four eta expansions (a strange program indeed!) tcrun035: one eta expansion * Ambiguity check at higher rank. Now that we have simple subsumption, a type like f :: (forall a. Eq a => Int) -> Int is no longer ambiguous, because we could write g :: (forall a. Eq a => Int) -> Int g = f and it'd typecheck just fine. But f's type is a bit suspicious, and we might want to consider making the ambiguity check do a check on each sub-term. Meanwhile, these tests are accepted, whereas they were previously rejected as ambiguous: T7220a T15438 T10503 T9222 * Some more interesting error message wibbles T13381: Fine: one error (Int ~ Exp Int) rather than two (Int ~ Exp Int, Exp Int ~ Int) T9834: Small change in error (improvement) T10619: Improved T2414: Small change, due to order of unification, fine T2534: A very simple case in which a change of unification order means we get tow unsolved constraints instead of one tc211: bizarre impredicative tests; just accept this for now Updates Cabal and haddock submodules. Metric Increase: T12150 T12234 T5837 haddock.base Metric Decrease: haddock.compiler haddock.Cabal haddock.base Merge note: This appears to break the `UnliftedNewtypesDifficultUnification` test. It has been marked as broken in the interest of merging. (cherry picked from commit 66b7b195cb3dce93ed5078b80bf568efae904cc5) - - - - - 2dff8141 by Ryan Scott at 2020-06-05T14:21:24-04:00 Simplify bindLHsTyVarBndrs and bindHsQTyVars Both `bindLHsTyVarBndrs` and `bindHsQTyVars` take two separate `Maybe` arguments, which I find terribly confusing. Thankfully, it's possible to remove one `Maybe` argument from each of these functions, which this patch accomplishes: * `bindHsQTyVars` takes a `Maybe SDoc` argument, which is `Just` if GHC should warn about any of the quantified type variables going unused. However, every call site uses `Nothing` in practice. This makes sense, since it doesn't really make sense to warn about unused type variables bound by an `LHsQTyVars`. For instance, you wouldn't warn about the `a` in `data Proxy a = Proxy` going unused. As a result, I simply remove this `Maybe SDoc` argument altogether. * `bindLHsTyVarBndrs` also takes a `Maybe SDoc` argument for the same reasons that `bindHsQTyVars` took one. To make things more confusing, however, `bindLHsTyVarBndrs` also takes a separate `HsDocContext` argument, which is pretty-printed (to an `SDoc`) in warnings and error messages. In practice, the `Maybe SDoc` and the `HsDocContext` often contain the same text. See the call sites for `bindLHsTyVarBndrs` in `rnFamInstEqn` and `rnConDecl`, for instance. There are only a handful of call sites where the text differs between the `Maybe SDoc` and `HsDocContext` arguments: * In `rnHsRuleDecl`, where the `Maybe SDoc` says "`In the rule`" and the `HsDocContext` says "`In the transformation rule`". * In `rnHsTyKi`/`rn_ty`, where the `Maybe SDoc` says "`In the type`" but the `HsDocContext` is inhereted from the surrounding context (e.g., if `rnHsTyKi` were called on a top-level type signature, the `HsDocContext` would be "`In the type signature`" instead) In both cases, warnings/error messages arguably _improve_ by unifying making the `Maybe SDoc`'s text match that of the `HsDocContext`. As a result, I decided to remove the `Maybe SDoc` argument to `bindLHsTyVarBndrs` entirely and simply reuse the text from the `HsDocContext`. (I decided to change the phrase "transformation rule" to "rewrite rule" while I was in the area.) The `Maybe SDoc` argument has one other purpose: signaling when to emit "`Unused quantified type variable`" warnings. To recover this functionality, I replaced the `Maybe SDoc` argument with a boolean-like `WarnUnusedForalls` argument. The only `bindLHsTyVarBndrs` call site that chooses _not_ to emit these warnings in `bindHsQTyVars`. - - - - - e372331b by Ben Gamari at 2020-06-07T08:46:41-04:00 hadrian: Add missing deriveConstants dependency on ghcplatform.h deriveConstants wants to compile C sources which #include PosixSource.h, which itself #includes ghcplatform.h. Make sure that Hadrian knows about this dependency. Fixes #18290. - - - - - b022051a by Moritz Angermann at 2020-06-07T08:46:42-04:00 ghc-prim needs to depend on libc and libm libm is just an empty shell on musl, and all the math functions are contained in libc. - - - - - 6dae6548 by Moritz Angermann at 2020-06-07T08:46:42-04:00 Disable DLL loading if without system linker Some platforms (musl, aarch64) do not have a working dynamic linker implemented in the libc, even though we might see dlopen. It will ultimately just return that this is not supported. Hence we'll add a flag to the compiler to flat our disable loading dlls. This is needed as we will otherwise try to load the shared library even if this will subsequently fail. At that point we have given up looking for static options though. - - - - - 4a158ffc by Moritz Angermann at 2020-06-07T08:46:43-04:00 Range is actually +/-2^32, not +/-2^31 See also: https://static.docs.arm.com/ihi0056/g/aaelf64.pdf - - - - - f1bfb806 by Ben Gamari at 2020-06-07T10:49:30-04:00 OccurAnal: Avoid exponential behavior due to where clauses Previously the `Var` case of `occAnalApp` could in some cases (namely in the case of `runRW#` applications) call `occAnalRhs` two. In the case of nested `runRW#`s this results in exponential complexity. In some cases the compilation time that resulted would be very long indeed (see #18296). Fixes #18296. Metric Decrease: T9961 T12150 T12234 - - - - - 9b607671 by Takenobu Tani at 2020-06-09T08:05:46-04:00 Add link to GHC's wiki in the GHC API header This adds a URL to point to GHC's wiki in the GHC API header. Newcomers could easily find more information from the GHC API's web like [1]. [1]: Current version, https://ghc.gitlab.haskell.org/ghc/doc/libraries/ghc-8.11.0.20200604/index.html [skip ci] - - - - - 72c7fe9a by Ryan Scott at 2020-06-09T08:06:24-04:00 Make GADT constructors adhere to the forall-or-nothing rule properly Issue #18191 revealed that the types of GADT constructors don't quite adhere to the `forall`-or-nothing rule. This patch serves to clean up this sad state of affairs somewhat. The main change is not in the code itself, but in the documentation, as this patch introduces two sections to the GHC User's Guide: * A "Formal syntax for GADTs" section that presents a BNF-style grammar for what is and isn't allowed in GADT constructor types. This mostly exists to codify GHC's existing behavior, but it also imposes a new restriction that addresses #18191: the outermost `forall` and/or context in a GADT constructor is not allowed to be surrounded by parentheses. Doing so would make these `forall`s/contexts nested, and GADTs do not support nested `forall`s/contexts at present. * A "`forall`-or-nothing rule" section that describes exactly what the `forall`-or-nothing rule is all about. Surprisingly, there was no mention of this anywhere in the User's Guide up until now! To adhere the new specification in the "Formal syntax for GADTs" section of the User's Guide, the following code changes were made: * A new function, `GHC.Hs.Type.splitLHsGADTPrefixTy`, was introduced. This is very much like `splitLHsSigmaTy`, except that it avoids splitting apart any parentheses, which can be syntactically significant for GADT types. See `Note [No nested foralls or contexts in GADT constructors]` in `GHC.Hs.Type`. * `ConDeclGADTPrefixPs`, an extension constructor for `XConDecl`, was introduced so that `GHC.Parser.PostProcess.mkGadtDecl` can return it when given a prefix GADT constructor. Unlike `ConDeclGADT`, `ConDeclGADTPrefixPs` does not split the GADT type into its argument and result types, as this cannot be done until after the type is renamed (see `Note [GADT abstract syntax]` in `GHC.Hs.Decls` for why this is the case). * `GHC.Renamer.Module.rnConDecl` now has an additional case for `ConDeclGADTPrefixPs` that (1) splits apart the full `LHsType` into its `forall`s, context, argument types, and result type, and (2) checks for nested `forall`s/contexts. Step (2) used to be performed the typechecker (in `GHC.Tc.TyCl.badDataConTyCon`) rather than the renamer, but now the relevant code from the typechecker can simply be deleted. One nice side effect of this change is that we are able to give a more accurate error message for GADT constructors that use visible dependent quantification (e.g., `MkFoo :: forall a -> a -> Foo a`), which improves the stderr in the `T16326_Fail6` test case. Fixes #18191. Bumps the Haddock submodule. - - - - - a47e6442 by Ryan Scott at 2020-06-10T03:39:12-04:00 Always use rnImplicitBndrs to bring implicit tyvars into scope This implements a first step towards #16762 by changing the renamer to always use `rnImplicitBndrs` to bring implicitly bound type variables into scope. The main change is in `rnFamInstEqn` and `bindHsQTyVars`, which previously used _ad hoc_ methods of binding their implicit tyvars. There are a number of knock-on consequences: * One of the reasons that `rnFamInstEqn` used an _ad hoc_ binding mechanism was to give more precise source locations in `-Wunused-type-patterns` warnings. (See https://gitlab.haskell.org/ghc/ghc/issues/16762#note_273343 for an example of this.) However, these warnings are actually a little _too_ precise, since implicitly bound type variables don't have exact binding sites like explicitly bound type variables do. A similar problem existed for "`Different names for the same type variable`" errors involving implicit tyvars bound by `bindHsQTyVars`. Therefore, we simply accept the less precise (but more accurate) source locations from `rnImplicitBndrs` in `rnFamInstEqn` and `bindHsQTyVars`. See `Note [Source locations for implicitly bound type variables]` in `GHC.Rename.HsType` for the full story. * In order for `rnImplicitBndrs` to work in `rnFamInstEqn`, it needs to be able to look up names from the parent class (in the event that we are renaming an associated type family instance). As a result, `rnImplicitBndrs` now takes an argument of type `Maybe assoc`, which is `Just` in the event that a type family instance is associated with a class. * Previously, GHC kept track of three type synonyms for free type variables in the renamer: `FreeKiTyVars`, `FreeKiTyVarsDups` (which are allowed to contain duplicates), and `FreeKiTyVarsNoDups` (which contain no duplicates). However, making is a distinction between `-Dups` and `-NoDups` is now pointless, as all code that returns `FreeKiTyVars{,Dups,NoDups}` will eventually end up being passed to `rnImplicitBndrs`, which removes duplicates. As a result, I decided to just get rid of `FreeKiTyVarsDups` and `FreeKiTyVarsNoDups`, leaving only `FreeKiTyVars`. * The `bindLRdrNames` and `deleteBys` functions are now dead code, so I took the liberty of removing them. - - - - - 24879129 by Takenobu Tani at 2020-06-10T03:39:59-04:00 Clarify leaf module names for new module hierarchy This updates comments only. This patch replaces leaf module names according to new module hierarchy [1][2] as followings: * Expand leaf names to easily find the module path: for instance, `Id.hs` to `GHC.Types.Id`. * Modify leaf names according to new module hierarchy: for instance, `Convert.hs` to `GHC.ThToHs`. * Fix typo: for instance, `GHC.Core.TyCo.Rep.hs` to `GHC.Core.TyCo.Rep` See also !3375 [1]: https://gitlab.haskell.org/ghc/ghc/-/wikis/Make-GHC-codebase-more-modular [2]: https://gitlab.haskell.org/ghc/ghc/issues/13009 - - - - - 92de9e25 by Ömer Sinan Ağacan at 2020-06-10T03:41:07-04:00 rts: Remove unused GET_ENTRY closure macro This macro is not used and got broken in the meantime, as ENTRY_CODE was deleted. - - - - - 87102928 by Ömer Sinan Ağacan at 2020-06-10T03:41:50-04:00 Fix -fkeep-cafs flag name in users guide - - - - - ccd6843d by Shayne Fletcher at 2020-06-10T04:14:57-04:00 Expose impliedGFlags, impledOffGFlags, impliedXFlags - - - - - 7a737e89 by Ömer Sinan Ağacan at 2020-06-10T04:14:58-04:00 Cross-module LambdaFormInfo passing - Store LambdaFormInfos of exported Ids in interface files - Use them in importing modules This is for optimization purposes: if we know LambdaFormInfo of imported Ids we can generate more efficient calling code, see `getCallMethod`. Exporting (putting them in interface files or in ModDetails) and importing (reading them from interface files) are both optional. We don't assume known LambdaFormInfos anywhere and do not change how we call Ids with unknown LambdaFormInfos. Runtime, allocation, and residency numbers when building Cabal-the-library (commit 0d4ee7ba3): (Log and .hp files are in the MR: !2842) | | GHC HEAD | This patch | Diff | |-----|----------|------------|----------------| | -O0 | 0:35.89 | 0:34.10 | -1.78s, -4.98% | | -O1 | 2:24.01 | 2:23.62 | -0.39s, -0.27% | | -O2 | 2:52.23 | 2:51.35 | -0.88s, -0.51% | | | GHC HEAD | This patch | Diff | |-----|-----------------|-----------------|----------------------------| | -O0 | 54,843,608,416 | 54,878,769,544 | +35,161,128 bytes, +0.06% | | -O1 | 227,136,076,400 | 227,569,045,168 | +432,968,768 bytes, +0.19% | | -O2 | 266,147,063,296 | 266,749,643,440 | +602,580,144 bytes, +0.22% | NOTE: Residency is measured with extra runtime args: `-i0 -h` which effectively turn all GCs into major GCs, and do GC more often. | | GHC HEAD | This patch | Diff | |-----|----------------------------|------------------------------|----------------------------| | -O0 | 410,284,000 (910 samples) | 411,745,008 (906 samples) | +1,461,008 bytes, +0.35% | | -O1 | 928,580,856 (2109 samples) | 943,506,552 (2103 samples) | +14,925,696 bytes, +1.60% | | -O2 | 993,951,352 (2549 samples) | 1,010,156,328 (2545 samples) | +16,204,9760 bytes, +1.63% | NoFib results: -------------------------------------------------------------------------------- Program Size Allocs Instrs Reads Writes -------------------------------------------------------------------------------- CS 0.0% 0.0% +0.0% +0.0% +0.0% CSD 0.0% 0.0% 0.0% +0.0% +0.0% FS 0.0% 0.0% +0.0% +0.0% +0.0% S 0.0% 0.0% +0.0% +0.0% +0.0% VS 0.0% 0.0% +0.0% +0.0% +0.0% VSD 0.0% 0.0% +0.0% +0.0% +0.1% VSM 0.0% 0.0% +0.0% +0.0% +0.0% anna 0.0% 0.0% -0.3% -0.8% -0.0% ansi 0.0% 0.0% -0.0% -0.0% 0.0% atom 0.0% 0.0% -0.0% -0.0% 0.0% awards 0.0% 0.0% -0.1% -0.3% 0.0% banner 0.0% 0.0% -0.0% -0.0% -0.0% bernouilli 0.0% 0.0% -0.0% -0.0% -0.0% binary-trees 0.0% 0.0% -0.0% -0.0% +0.0% boyer 0.0% 0.0% -0.0% -0.0% 0.0% boyer2 0.0% 0.0% -0.0% -0.0% 0.0% bspt 0.0% 0.0% -0.0% -0.2% 0.0% cacheprof 0.0% 0.0% -0.1% -0.4% +0.0% calendar 0.0% 0.0% -0.0% -0.0% 0.0% cichelli 0.0% 0.0% -0.9% -2.4% 0.0% circsim 0.0% 0.0% -0.0% -0.0% 0.0% clausify 0.0% 0.0% -0.1% -0.3% 0.0% comp_lab_zift 0.0% 0.0% -0.0% -0.0% +0.0% compress 0.0% 0.0% -0.0% -0.0% -0.0% compress2 0.0% 0.0% -0.0% -0.0% 0.0% constraints 0.0% 0.0% -0.1% -0.2% -0.0% cryptarithm1 0.0% 0.0% -0.0% -0.0% 0.0% cryptarithm2 0.0% 0.0% -1.4% -4.1% -0.0% cse 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e1 0.0% 0.0% -0.0% -0.0% -0.0% digits-of-e2 0.0% 0.0% -0.0% -0.0% -0.0% dom-lt 0.0% 0.0% -0.1% -0.2% 0.0% eliza 0.0% 0.0% -0.5% -1.5% 0.0% event 0.0% 0.0% -0.0% -0.0% -0.0% exact-reals 0.0% 0.0% -0.1% -0.3% +0.0% exp3_8 0.0% 0.0% -0.0% -0.0% -0.0% expert 0.0% 0.0% -0.3% -1.0% -0.0% fannkuch-redux 0.0% 0.0% +0.0% +0.0% +0.0% fasta 0.0% 0.0% -0.0% -0.0% +0.0% fem 0.0% 0.0% -0.0% -0.0% 0.0% fft 0.0% 0.0% -0.0% -0.0% 0.0% fft2 0.0% 0.0% -0.0% -0.0% 0.0% fibheaps 0.0% 0.0% -0.0% -0.0% +0.0% fish 0.0% 0.0% 0.0% -0.0% +0.0% fluid 0.0% 0.0% -0.4% -1.2% +0.0% fulsom 0.0% 0.0% -0.0% -0.0% 0.0% gamteb 0.0% 0.0% -0.1% -0.3% 0.0% gcd 0.0% 0.0% -0.0% -0.0% 0.0% gen_regexps 0.0% 0.0% -0.0% -0.0% -0.0% genfft 0.0% 0.0% -0.0% -0.0% 0.0% gg 0.0% 0.0% -0.0% -0.0% +0.0% grep 0.0% 0.0% -0.0% -0.0% -0.0% hidden 0.0% 0.0% -0.1% -0.4% -0.0% hpg 0.0% 0.0% -0.2% -0.5% +0.0% ida 0.0% 0.0% -0.0% -0.0% +0.0% infer 0.0% 0.0% -0.3% -0.8% -0.0% integer 0.0% 0.0% -0.0% -0.0% +0.0% integrate 0.0% 0.0% -0.0% -0.0% 0.0% k-nucleotide 0.0% 0.0% -0.0% -0.0% +0.0% kahan 0.0% 0.0% -0.0% -0.0% +0.0% knights 0.0% 0.0% -2.2% -5.4% 0.0% lambda 0.0% 0.0% -0.6% -1.8% 0.0% last-piece 0.0% 0.0% -0.0% -0.0% 0.0% lcss 0.0% 0.0% -0.0% -0.1% 0.0% life 0.0% 0.0% -0.0% -0.1% 0.0% lift 0.0% 0.0% -0.2% -0.6% +0.0% linear 0.0% 0.0% -0.0% -0.0% -0.0% listcompr 0.0% 0.0% -0.0% -0.0% 0.0% listcopy 0.0% 0.0% -0.0% -0.0% 0.0% maillist 0.0% 0.0% -0.1% -0.3% +0.0% mandel 0.0% 0.0% -0.0% -0.0% 0.0% mandel2 0.0% 0.0% -0.0% -0.0% -0.0% mate +0.0% 0.0% -0.0% -0.0% -0.0% minimax 0.0% 0.0% -0.2% -1.0% 0.0% mkhprog 0.0% 0.0% -0.1% -0.2% -0.0% multiplier 0.0% 0.0% -0.0% -0.0% -0.0% n-body 0.0% 0.0% -0.0% -0.0% +0.0% nucleic2 0.0% 0.0% -0.1% -0.2% 0.0% para 0.0% 0.0% -0.0% -0.0% -0.0% paraffins 0.0% 0.0% -0.0% -0.0% 0.0% parser 0.0% 0.0% -0.2% -0.7% 0.0% parstof 0.0% 0.0% -0.0% -0.0% +0.0% pic 0.0% 0.0% -0.0% -0.0% 0.0% pidigits 0.0% 0.0% +0.0% +0.0% +0.0% power 0.0% 0.0% -0.2% -0.6% +0.0% pretty 0.0% 0.0% -0.0% -0.0% -0.0% primes 0.0% 0.0% -0.0% -0.0% 0.0% primetest 0.0% 0.0% -0.0% -0.0% -0.0% prolog 0.0% 0.0% -0.3% -1.1% 0.0% puzzle 0.0% 0.0% -0.0% -0.0% 0.0% queens 0.0% 0.0% -0.0% -0.0% +0.0% reptile 0.0% 0.0% -0.0% -0.0% 0.0% reverse-complem 0.0% 0.0% -0.0% -0.0% +0.0% rewrite 0.0% 0.0% -0.7% -2.5% -0.0% rfib 0.0% 0.0% -0.0% -0.0% 0.0% rsa 0.0% 0.0% -0.0% -0.0% 0.0% scc 0.0% 0.0% -0.1% -0.2% -0.0% sched 0.0% 0.0% -0.0% -0.0% -0.0% scs 0.0% 0.0% -1.0% -2.6% +0.0% simple 0.0% 0.0% +0.0% -0.0% +0.0% solid 0.0% 0.0% -0.0% -0.0% 0.0% sorting 0.0% 0.0% -0.6% -1.6% 0.0% spectral-norm 0.0% 0.0% +0.0% 0.0% +0.0% sphere 0.0% 0.0% -0.0% -0.0% -0.0% symalg 0.0% 0.0% -0.0% -0.0% +0.0% tak 0.0% 0.0% -0.0% -0.0% 0.0% transform 0.0% 0.0% -0.0% -0.0% 0.0% treejoin 0.0% 0.0% -0.0% -0.0% 0.0% typecheck 0.0% 0.0% -0.0% -0.0% +0.0% veritas +0.0% 0.0% -0.2% -0.4% +0.0% wang 0.0% 0.0% -0.0% -0.0% 0.0% wave4main 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve1 0.0% 0.0% -0.0% -0.0% -0.0% wheel-sieve2 0.0% 0.0% -0.0% -0.0% +0.0% x2n1 0.0% 0.0% -0.0% -0.0% -0.0% -------------------------------------------------------------------------------- Min 0.0% 0.0% -2.2% -5.4% -0.0% Max +0.0% 0.0% +0.0% +0.0% +0.1% Geometric Mean -0.0% -0.0% -0.1% -0.3% +0.0% Metric increases micro benchmarks tracked in #17686: Metric Increase: T12150 T12234 T12425 T13035 T5837 T6048 T9233 Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 3b22b14a by Shayne Fletcher at 2020-06-10T04:15:01-04:00 Give Language a Bounded instance - - - - - 9454511b by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Optimisation in Unique.Supply This patch switches on -fno-state-hack in GHC.Types.Unique.Supply. It turned out that my fixes for #18078 (coercion floating) changed the optimisation pathway for mkSplitUniqSupply in such a way that we had an extra allocation inside the inner loop. Adding -fno-state-hack fixed that -- and indeed the loop in mkSplitUniqSupply is a classic example of the way in which -fno-state-hack can be bad; see #18238. Moreover, the new code is better than the old. They allocate the same, but the old code ends up with a partial application. The net effect is that the test perf/should_run/UniqLoop runs 20% faster! From 2.5s down to 2.0s. The allocation numbers are the same -- but elapsed time falls. Good! The bad thing about this is that it's terribly delicate. But at least it's a good example of such delicacy in action. There is a long Note [Optimising the unique supply] which now explains all this. - - - - - 6d49d5be by Simon Peyton Jones at 2020-06-10T04:17:06-04:00 Implement cast worker/wrapper properly The cast worker/wrapper transformation transforms x = e |> co into y = e x = y |> co This is done by the simplifier, but we were being careless about transferring IdInfo from x to y, and about what to do if x is a NOINLNE function. This resulted in a series of bugs: #17673, #18093, #18078. This patch fixes all that: * Main change is in GHC.Core.Opt.Simplify, and the new prepareBinding function, which does this cast worker/wrapper transform. See Note [Cast worker/wrappers]. * There is quite a bit of refactoring around prepareRhs, makeTrivial etc. It's nicer now. * Some wrappers from strictness and cast w/w, notably those for a function with a NOINLINE, should inline very late. There wasn't really a mechanism for that, which was an existing bug really; so I invented a new finalPhase = Phase (-1). It's used for all simplifier runs after the user-visible phase 2,1,0 have run. (No new runs of the simplifier are introduced thereby.) See new Note [Compiler phases] in GHC.Types.Basic; the main changes are in GHC.Core.Opt.Driver * Doing this made me trip over two places where the AnonArgFlag on a FunTy was being lost so we could end up with (Num a -> ty) rather than (Num a => ty) - In coercionLKind/coercionRKind - In contHoleType in the Simplifier I fixed the former by defining mkFunctionType and using it in coercionLKind/RKind. I could have done the same for the latter, but the information is almost to hand. So I fixed the latter by - adding sc_hole_ty to ApplyToVal (like ApplyToTy), - adding as_hole_ty to ValArg (like TyArg) - adding sc_fun_ty to StrictArg Turned out I could then remove ai_type from ArgInfo. This is just moving the deck chairs around, but it worked out nicely. See the new Note [AnonArgFlag] in GHC.Types.Var * When looking at the 'arity decrease' thing (#18093) I discovered that stable unfoldings had a much lower arity than the actual optimised function. That's what led to the arity-decrease message. Simple solution: eta-expand. It's described in Note [Eta-expand stable unfoldings] in GHC.Core.Opt.Simplify * I also discovered that unsafeCoerce wasn't being inlined if the context was boring. So (\x. f (unsafeCoerce x)) would create a thunk -- yikes! I fixed that by making inlineBoringOK a bit cleverer: see Note [Inline unsafeCoerce] in GHC.Core.Unfold. I also found that unsafeCoerceName was unused, so I removed it. I made a test case for #18078, and a very similar one for #17673. The net effect of all this on nofib is very modest, but positive: -------------------------------------------------------------------------------- Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- anna -0.4% -0.1% -3.1% -3.1% 0.0% fannkuch-redux -0.4% -0.3% -0.1% -0.1% 0.0% maillist -0.4% -0.1% -7.8% -1.0% -14.3% primetest -0.4% -15.6% -7.1% -6.6% 0.0% -------------------------------------------------------------------------------- Min -0.9% -15.6% -13.3% -14.2% -14.3% Max -0.3% 0.0% +12.1% +12.4% 0.0% Geometric Mean -0.4% -0.2% -2.3% -2.2% -0.1% All following metric decreases are compile-time allocation decreases between -1% and -3%: Metric Decrease: T5631 T13701 T14697 T15164 - - - - - 32fd37f5 by Luke Lau at 2020-06-10T04:17:22-04:00 Fix lookupGlobalOccRn_maybe sometimes reporting an error In some cases it was possible for lookupGlobalOccRn_maybe to return an error, when it should be returning a Nothing. If it called lookupExactOcc_either when there were no matching GlobalRdrElts in the otherwise case, it would return an error message. This could be caused when lookupThName_maybe in Template Haskell was looking in different namespaces (thRdrNameGuesses), guessing different namespaces that the name wasn't guaranteed to be found in. However, by addressing this some more accurate errors were being lost in the conversion to Maybes. So some of the lookup* functions have been shuffled about so that errors should always be ignored in lookup*_maybes, and propagated otherwise. This fixes #18263 - - - - - 9b283e1b by Roland Senn at 2020-06-10T04:17:34-04:00 Initialize the allocation counter in GHCi to 0 (Fixes #16012) According to the documentation for the function `getAllocationCounter` in [System.Mem](http://hackage.haskell.org/package/base-4.14.0.0/docs/System-Mem.html) initialize the allocationCounter also in GHCi to 0. - - - - - 8d07c48c by Sylvain Henry at 2020-06-10T04:17:36-04:00 test: fix conc038 We had spurious failures of conc038 test on CI with stdout: ``` newThread started -mainThread -Haskell: 2 newThread back again +mainThread 1 sec later shutting down +Haskell: 2 ``` - - - - - 4c7e9689 by Sebastian Graf at 2020-06-11T10:37:38+02:00 Release Notes: Add news from the pattern-match checker [skip ci] - - - - - 3445b965 by Sylvain Henry at 2020-06-13T02:13:01-04:00 Only test T16190 with the NCG T16190 is meant to test a NCG feature. It has already caused spurious failures in other MRs (e.g. !2165) when LLVM is used. - - - - - 2517a51c by Sylvain Henry at 2020-06-13T02:13:01-04:00 DynFlags refactoring VIII (#17957) * Remove several uses of `sdocWithDynFlags`, especially in GHC.Llvm.* * Add LlvmOpts datatype to store Llvm backend options * Remove Outputable instances (for LlvmVar, LlvmLit, LlvmStatic and Llvm.MetaExpr) which require LlvmOpts. * Rename ppMetaExpr into ppMetaAnnotExpr (pprMetaExpr is now used in place of `ppr :: MetaExpr -> SDoc`) - - - - - 7a02599a by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove unused code - - - - - 72d08610 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor homeUnit * rename thisPackage into homeUnit * document and refactor several Backpack things - - - - - 8dc71f55 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Rename unsafeGetUnitInfo into unsafeLookupUnit - - - - - f6be6e43 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Add allowVirtualUnits field in PackageState Instead of always querying DynFlags to know whether we are allowed to use virtual units (i.e. instantiated on-the-fly, cf Note [About units] in GHC.Unit), we store it once for all in `PackageState.allowVirtualUnits`. This avoids using DynFlags too much (cf #17957) and is preliminary work for #14335. - - - - - e7272d53 by Sylvain Henry at 2020-06-13T02:13:02-04:00 Enhance UnitId use * use UnitId instead of String to identify wired-in units * use UnitId instead of Unit in the backend (Unit are only use by Backpack to produce type-checked interfaces, not real code) * rename lookup functions for consistency * documentation - - - - - 9c5572cd by Sylvain Henry at 2020-06-13T02:13:02-04:00 Remove LinkerUnitId type alias - - - - - d345edfe by Sylvain Henry at 2020-06-13T02:13:02-04:00 Refactor WiredMap * Remove WiredInUnitId and WiredUnitId type aliases - - - - - 3d171cd6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document and refactor `mkUnit` and `mkUnitInfoMap` - - - - - d2109b4f by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove PreloadUnitId type alias - - - - - f50c19b8 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename listUnitInfoMap into listUnitInfo There is no Map involved - - - - - ed533ec2 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit The terminology changed over time and now package databases contain "units" (there can be several units compiled from a single Cabal package: one per-component, one for each option set, one per instantiation, etc.). We should try to be consistent internally and use "units": that's what this renaming does. Maybe one day we'll fix the UI too (e.g. replace -package-id with -unit-id, we already have -this-unit-id and ghc-pkg has -unit-id...) but it's not done in this patch. * rename getPkgFrameworkOpts into getUnitFrameworkOpts * rename UnitInfoMap into ClosureUnitInfoMap * rename InstalledPackageIndex into UnitInfoMap * rename UnusablePackages into UnusableUnits * rename PackagePrecedenceIndex into UnitPrecedenceMap * rename PackageDatabase into UnitDatabase * rename pkgDatabase into unitDatabases * rename pkgState into unitState * rename initPackages into initUnits * rename renamePackage into renameUnitInfo * rename UnusablePackageReason into UnusableUnitReason * rename getPackage* into getUnit* * etc. - - - - - 202728e5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Make ClosureUnitInfoMap uses UnitInfoMap - - - - - 55b4263e by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove ClosureUnitInfoMap - - - - - 653d17bd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Rename Package into Unit (2) * rename PackageState into UnitState * rename findWiredInPackages into findWiredInUnits * rename lookupModuleInAll[Packages,Units] * etc. - - - - - ae900605 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move dump_mod_map into initUnits - - - - - 598cc1dd by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move wiring of homeUnitInstantiations outside of mkUnitState - - - - - 437265eb by Sylvain Henry at 2020-06-13T02:13:03-04:00 Avoid timing module map dump in initUnits - - - - - 9400aa93 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Remove preload parameter of mkUnitState * Remove preload parameter (unused) * Don't explicitly return preloaded units: redundant because already returned as "preloadUnits" field of UnitState - - - - - 266bc3d9 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: refactor unwireUnit - - - - - 9e715c1b by Sylvain Henry at 2020-06-13T02:13:03-04:00 Document getPreloadUnitsAnd - - - - - bd5810dc by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: remove useless add_package parameter - - - - - 36e1daf0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: make listVisibleModuleNames take a UnitState - - - - - 5226da37 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document add_package - - - - - 4b53aac1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Refactor and document closeUnitDeps - - - - - 42c054f6 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: findWiredInUnits - - - - - a444d01b by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: reportCycles, reportUnusable - - - - - 8408d521 by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: merge_databases - - - - - fca2d25f by Sylvain Henry at 2020-06-13T02:13:03-04:00 DynFlags: add UnitConfig datatype Avoid directly querying flags from DynFlags to build the UnitState. Instead go via UnitConfig so that we could reuse this to make another UnitState for plugins. - - - - - 4274688a by Sylvain Henry at 2020-06-13T02:13:03-04:00 Move distrustAll into mkUnitState - - - - - 28d804e1 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Create helper upd_wired_in_home_instantiations - - - - - ac964c83 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Put database cache in UnitConfig - - - - - bfd0a78c by Sylvain Henry at 2020-06-13T02:13:03-04:00 Don't return preload units when we set DyNFlags Preload units can be retrieved in UnitState when needed (i.e. in GHCi) - - - - - 1fbb4bf5 by Sylvain Henry at 2020-06-13T02:13:03-04:00 NCGConfig: remove useless ncgUnitId field - - - - - c10ff7e7 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Doc: fix some comments - - - - - 456e17f0 by Sylvain Henry at 2020-06-13T02:13:03-04:00 Bump haddock submodule and allow metric decrease Metric Decrease: T12150 T12234 T5837 Metric Increase: T16190 - - - - - 42953902 by Simon Peyton Jones at 2020-06-13T02:13:03-04:00 Trim the demand for recursive product types Ticket #18304 showed that we need to be very careful when exploring the demand (esp usage demand) on recursive product types. This patch solves the problem by trimming the demand on such types -- in effect, a form of "widening". See the Note [Trimming a demand to a type] in DmdAnal, which explains how I did this by piggy-backing on an existing mechansim for trimming demands becuase of GADTs. The significant payload of this patch is very small indeed: * Make GHC.Core.Opt.WorkWrap.Utils.typeShape use RecTcChecker to avoid looking through recursive types. But on the way * I found that ae_rec_tc was entirely inoperative and did nothing. So I removed it altogether from DmdAnal. * I moved some code around in DmdAnal and Demand. (There are no actual changes in dmdFix.) * I changed the API of DmsAnal.dmdAnalRhsLetDown to return a StrictSig rather than a decorated Id * I removed the dead function peelTsFuns from Demand Performance effects: Nofib: 0.0% changes. Not surprising, because they don't use recursive products Perf tests T12227: 1% increase in compiler allocation, becuase $cto gets w/w'd. It did not w/w before because it takes a deeply nested argument, so the worker gets too many args, so we abandon w/w altogether (see GHC.Core.Opt.WorkWrap.Utils.isWorkerSmallEnough) With this patch we trim the demands. That is not strictly necessary (since these Generic type constructors are like tuples -- they can't cause a loop) but the net result is that we now w/w $cto which is fine. UniqLoop: 16% decrease in /runtime/ allocation. The UniqSupply is a recursive product, so currently we abandon all strictness on 'churn'. With this patch 'churn' gets useful strictness, and we w/w it. Hooray Metric Decrease: UniqLoop Metric Increase: T12227 - - - - - 87d504f4 by Viktor Dukhovni at 2020-06-13T02:13:05-04:00 Add introductory prose for Data.Traversable - - - - - 9f09b608 by Oleg Grenrus at 2020-06-13T02:13:07-04:00 Fix #12073: Add MonadFix Q instance - - - - - 220c2d34 by Ben Gamari at 2020-06-13T02:13:07-04:00 testsuite: Increase size of T12150 As noted in #18319, this test was previously very fragile. Increase its size to make it more likely that its fails with its newly-increased acceptance threshold. Metric Increase: T12150 - - - - - 8bba1c26 by Ben Gamari at 2020-06-13T04:59:06-04:00 gitlab-ci: Always push perf notes Previously we ci.sh would run with `set -e` implying that we wouldn't push perf notes if the testsuite were to fail, even if it *only* failed due to perf notes. This rendered the whole performance testing story quite fragile as a single regressing commit would cause every successive commit to fail since a new baseline would not be uploaded. Fix this by ensuring that we always push performance notes. - - - - - 7a773f16 by Ben Gamari at 2020-06-13T15:10:55-04:00 gitlab-ci: Eliminate redundant push of CI metrics - - - - - a31218f7 by Ryan Scott at 2020-06-13T15:58:37-04:00 Use HsForAllTelescope to avoid inferred, visible foralls Currently, `HsForAllTy` permits the combination of `ForallVis` and `Inferred`, but you can't actually typecheck code that uses it (e.g., `forall {a} ->`). This patch refactors `HsForAllTy` to use a new `HsForAllTelescope` data type that makes a type-level distinction between visible and invisible `forall`s such that visible `forall`s do not track `Specificity`. That part of the patch is actually quite small; the rest is simply changing consumers of `HsType` to accommodate this new type. Fixes #18235. Bumps the `haddock` submodule. - - - - - c0e6dee9 by Tamar Christina at 2020-06-14T09:07:44-04:00 winio: Add Atomic Exchange PrimOp and implement Atomic Ptr exchanges. The initial version was rewritten by Tamar Christina. It was rewritten in large parts by Andreas Klebinger. Co-authored-by: Andreas Klebinger <klebinger.andreas at gmx.at> - - - - - 9a7462fb by Ben Gamari at 2020-06-14T15:35:23-04:00 codeGen: Don't discard live case binders in unsafeEqualityProof logic Previously CoreToStg would unconditionally discard cases of the form: case unsafeEqualityProof of wild { _ -> rhs } and rather replace the whole thing with `rhs`. However, in some cases (see #18227) the case binder is still live, resulting in unbound occurrences in `rhs`. Fix this by only discarding the case if the case binder is dead. Fixes #18227. - - - - - e4137c48 by Ben Gamari at 2020-06-14T15:35:23-04:00 testsuite: Add tests for #18227 T18227A is the original issue which gave rise to the ticket and depends upon bytestring. T18227B is a minimized reproducer. - - - - - 8bab9ff1 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Fix rts include and library paths Fixes two bugs: * (?) and (<>) associated in a surprising way * We neglected to include libdw paths in the rts configure flags - - - - - bd761185 by Ben Gamari at 2020-06-14T15:35:59-04:00 hadrian: Drop redundant GHC arguments Cabal should already be passing this arguments to GHC. - - - - - 01f7052c by Peter Trommler at 2020-06-14T15:36:38-04:00 FFI: Fix pass small ints in foreign call wrappers The Haskell calling convention requires integer parameters smaller than wordsize to be promoted to wordsize (where the upper bits are don't care). To access such small integer parameter read a word from the parameter array and then cast that word to the small integer target type. Fixes #15933 - - - - - 502647f7 by Krzysztof Gogolewski at 2020-06-14T15:37:14-04:00 Fix "ndecreasingIndentation" in manual (#18116) - - - - - 9a9cc089 by Simon Jakobi at 2020-06-15T13:10:00-04:00 Use foldl' in unionManyUniqDSets - - - - - 761dcb84 by Moritz Angermann at 2020-06-15T13:10:36-04:00 Load .lo as well. Some archives contain so called linker objects, with the affectionate .lo suffic. For example the musl libc.a will come in that form. We still want to load those objects, hence we should not discard them and look for .lo as well. Ultimately we might want to fix this proerly by looking at the file magic. - - - - - cf01477f by Vladislav Zavialov at 2020-06-15T13:11:20-04:00 User's Guide: KnownNat evidence is Natural This bit of documentation got outdated after commit 1fcede43d2b30f33b7505e25eb6b1f321be0407f - - - - - d0dcbfe6 by Jan Hrček at 2020-06-16T20:36:38+02:00 Fix typos and formatting in user guide - - - - - 56a9e95f by Jan Hrček at 2020-06-16T20:36:38+02:00 Resolve TODO - - - - - 3e884d14 by Jan Hrček at 2020-06-16T20:36:38+02:00 Rename TcHoleErrors to GHC.Tc.Errors.Hole - - - - - d23fc678 by Stefan Schulze Frielinghaus at 2020-06-17T15:31:09-04:00 hadrian: Build with threaded runtime if available See #16873. - - - - - 0639dc10 by Sylvain Henry at 2020-06-17T15:31:53-04:00 T16190: only measure bytes_allocated Just adding `{-# LANGUAGE BangPatterns #-}` makes the two other metrics fluctuate by 13%. - - - - - 4cab6897 by Adam Sandberg Ericsson at 2020-06-17T15:32:44-04:00 docs: fix formatting in users guide - - - - - eb8115a8 by Sylvain Henry at 2020-06-17T15:33:23-04:00 Move CLabel assertions into smart constructors (#17957) It avoids using DynFlags in the Outputable instance of Clabel to check assertions at pretty-printing time. - - - - - 7faa4509 by Ben Gamari at 2020-06-17T15:43:31-04:00 base: Bump to 4.15.0.0 - - - - - 20616959 by Ben Gamari at 2020-06-17T15:43:31-04:00 configure: Use grep -q instead of --quiet The latter is apparently not supported by busybox. - - - - - 40fa237e by Krzysztof Gogolewski at 2020-06-17T16:21:58-04:00 Linear types (#15981) This is the first step towards implementation of the linear types proposal (https://github.com/ghc-proposals/ghc-proposals/pull/111). It features * A language extension -XLinearTypes * Syntax for linear functions in the surface language * Linearity checking in Core Lint, enabled with -dlinear-core-lint * Core-to-core passes are mostly compatible with linearity * Fields in a data type can be linear or unrestricted; linear fields have multiplicity-polymorphic constructors. If -XLinearTypes is disabled, the GADT syntax defaults to linear fields The following items are not yet supported: * a # m -> b syntax (only prefix FUN is supported for now) * Full multiplicity inference (multiplicities are really only checked) * Decent linearity error messages * Linear let, where, and case expressions in the surface language (each of these currently introduce the unrestricted variant) * Multiplicity-parametric fields * Syntax for annotating lambda-bound or let-bound with a multiplicity * Syntax for non-linear/multiple-field-multiplicity records * Linear projections for records with a single linear field * Linear pattern synonyms * Multiplicity coercions (test LinearPolyType) A high-level description can be found at https://ghc.haskell.org/trac/ghc/wiki/LinearTypes/Implementation Following the link above you will find a description of the changes made to Core. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Matthew Pickering * Arnaud Spiwack With contributions from: * Mark Barbone * Alexander Vershilov Updates haddock submodule. - - - - - 6cb84c46 by Krzysztof Gogolewski at 2020-06-17T16:22:03-04:00 Various performance improvements This implements several general performance improvements to GHC, to offset the effect of the linear types change. General optimisations: - Add a `coreFullView` function which iterates `coreView` on the head. This avoids making function recursive solely because the iterate `coreView` themselves. As a consequence, this functions can be inlined, and trigger case-of-known constructor (_e.g._ `kindRep_maybe`, `isLiftedRuntimeRep`, `isMultiplicityTy`, `getTyVar_maybe`, `splitAppTy_maybe`, `splitFunType_maybe`, `tyConAppTyCon_maybe`). The common pattern about all these functions is that they are almost always used as views, and immediately consumed by a case expression. This commit also mark them asx `INLINE`. - In `subst_ty` add a special case for nullary `TyConApp`, which avoid allocations altogether. - Use `mkTyConApp` in `subst_ty` for the general `TyConApp`. This required quite a bit of module shuffling. case. `myTyConApp` enforces crucial sharing, which was lost during substitution. See also !2952 . - Make `subst_ty` stricter. - In `eqType` (specifically, in `nonDetCmpType`), add a special case, tested first, for the very common case of nullary `TyConApp`. `nonDetCmpType` has been made `INLINE` otherwise it is actually a regression. This is similar to the optimisations in !2952. Linear-type specific optimisations: - Use `tyConAppTyCon_maybe` instead of the more complex `eqType` in the definition of the pattern synonyms `One` and `Many`. - Break the `hs-boot` cycles between `Multiplicity.hs` and `Type.hs`: `Multiplicity` now import `Type` normally, rather than from the `hs-boot`. This way `tyConAppTyCon_maybe` can inline properly in the `One` and `Many` pattern synonyms. - Make `updateIdTypeAndMult` strict in its type and multiplicity - The `scaleIdBy` gets a specialised definition rather than being an alias to `scaleVarBy` - `splitFunTy_maybe` is given the type `Type -> Maybe (Mult, Type, Type)` instead of `Type -> Maybe (Scaled Type, Type)` - Remove the `MultMul` pattern synonym in favour of a view `isMultMul` because pattern synonyms appear not to inline well. - in `eqType`, in a `FunTy`, compare multiplicities last: they are almost always both `Many`, so it helps failing faster. - Cache `manyDataConTy` in `mkTyConApp`, to make sure that all the instances of `TyConApp ManyDataConTy []` are physically the same. This commit has been authored by * Richard Eisenberg * Krzysztof Gogolewski * Arnaud Spiwack Metric Decrease: haddock.base T12227 T12545 T12990 T1969 T3064 T5030 T9872b Metric Increase: haddock.base haddock.Cabal haddock.compiler T12150 T12234 T12425 T12707 T13035 T13056 T15164 T16190 T18304 T1969 T3064 T3294 T5631 T5642 T5837 T6048 T9020 T9233 T9675 T9872a T9961 WWRec - - - - - 57db91d8 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Remove integer-simple integer-simple uses lists of words (`[Word]`) to represent big numbers instead of ByteArray#: * it is less efficient than the newer ghc-bignum native backend * it isn't compatible with the big number representation that is now shared by all the ghc-bignum backends (based on the one that was used only in integer-gmp before). As a consequence, we simply drop integer-simple - - - - - 9f96bc12 by Sylvain Henry at 2020-06-17T16:22:03-04:00 ghc-bignum library ghc-bignum is a newer package that aims to replace the legacy integer-simple and integer-gmp packages. * it supports several backends. In particular GMP is still supported and most of the code from integer-gmp has been merged in the "gmp" backend. * the pure Haskell "native" backend is new and is much faster than the previous pure Haskell implementation provided by integer-simple * new backends are easier to write because they only have to provide a few well defined functions. All the other code is common to all backends. In particular they all share the efficient small/big number distinction previously used only in integer-gmp. * backends can all be tested against the "native" backend with a simple Cabal flag. Backends are only allowed to differ in performance, their results should be the same. * Add `integer-gmp` compat package: provide some pattern synonyms and function aliases for those in `ghc-bignum`. It is intended to avoid breaking packages that depend on `integer-gmp` internals. Update submodules: text, bytestring Metric Decrease: Conversions ManyAlternatives ManyConstructors Naperian T10359 T10547 T10678 T12150 T12227 T12234 T12425 T13035 T13719 T14936 T1969 T4801 T4830 T5237 T5549 T5837 T8766 T9020 parsing001 space_leak_001 T16190 haddock.base On ARM and i386, T17499 regresses (+6% > 5%). On x86_64 unregistered, T13701 sometimes regresses (+2.2% > 2%). Metric Increase: T17499 T13701 - - - - - 96aa5787 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update compiler Thanks to ghc-bignum, the compiler can be simplified: * Types and constructors of Integer and Natural can be wired-in. It means that we don't have to query them from interfaces. It also means that numeric literals don't have to carry their type with them. * The same code is used whatever ghc-bignum backend is enabled. In particular, conversion of bignum literals into final Core expressions is now much more straightforward. Bignum closure inspection too. * GHC itself doesn't depend on any integer-* package anymore * The `integerLibrary` setting is gone. - - - - - 0f67e344 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `base` package * GHC.Natural isn't implemented in `base` anymore. It is provided by ghc-bignum in GHC.Num.Natural. It means that we can safely use Natural primitives in `base` without fearing issues with built-in rewrite rules (cf #15286) * `base` doesn't conditionally depend on an integer-* package anymore, it depends on ghc-bignum * Some duplicated code in integer-* can now be factored in GHC.Float * ghc-bignum tries to use a uniform naming convention so most of the other changes are renaming - - - - - aa9e7b71 by Sylvain Henry at 2020-06-17T16:22:03-04:00 Update `make` based build system * replace integer-* package selection with ghc-bignum backend selection - - - - - f817d816 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update testsuite * support detection of slow ghc-bignum backend (to replace the detection of integer-simple use). There are still some test cases that the native backend doesn't handle efficiently enough. * remove tests for GMP only functions that have been removed from ghc-bignum * fix test results showing dependent packages (e.g. integer-gmp) or showing suggested instances * fix test using Integer/Natural API or showing internal names - - - - - dceecb09 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Update Hadrian * support ghc-bignum backend selection in flavours and command-line * support ghc-bignum "--check" flag (compare results of selected backend against results of the native one) in flavours and command-line (e.g. pass --bignum=check-gmp" to check the "gmp" backend) * remove the hack to workaround #15286 * build GMP only when the gmp backend is used * remove hacks to workaround `text` package flags about integer-*. We fix `text` to use ghc-bignum unconditionally in another patch - - - - - fa4281d6 by Sylvain Henry at 2020-06-17T16:22:04-04:00 Bump bytestring and text submodules - - - - - 1a3f6f34 by Adam Sandberg Ericsson at 2020-06-18T23:03:36-04:00 docs: mention -hiedir in docs for -outputdir [skip ci] - - - - - 729bcb02 by Sylvain Henry at 2020-06-18T23:04:17-04:00 Hadrian: fix build on Mac OS Catalina (#17798) - - - - - 95e18292 by Andreas Klebinger at 2020-06-18T23:04:58-04:00 Relax allocation threshold for T12150. This test performs little work, so the most minor allocation changes often cause the test to fail. Increasing the threshold to 2% should help with this. - - - - - 8ce6c393 by Sebastian Graf at 2020-06-18T23:05:36-04:00 hadrian: Bump pinned cabal.project to an existent index-state - - - - - 08c1cb0f by Ömer Sinan Ağacan at 2020-06-18T23:06:21-04:00 Fix uninitialized field read in Linker.c Valgrind report of the bug when running the test `linker_unload`: ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x36C027A: loadArchive_ (LoadArchive.c:522) ==29666== by 0x36C0600: loadArchive (LoadArchive.c:626) ==29666== by 0x2C144CD: ??? (in /home/omer/haskell/ghc_2/testsuite/tests/rts/linker/linker_unload.run/linker_unload) ==29666== ==29666== Conditional jump or move depends on uninitialised value(s) ==29666== at 0x369C5B4: setOcInitialStatus (Linker.c:1305) ==29666== by 0x369C6C5: mkOc (Linker.c:1347) ==29666== by 0x369C9F6: preloadObjectFile (Linker.c:1507) ==29666== by 0x369CA8D: loadObj_ (Linker.c:1536) ==29666== by 0x369CB17: loadObj (Linker.c:1557) ==29666== by 0x3866BC: main (linker_unload.c:33) The problem is `mkOc` allocates a new `ObjectCode` and calls `setOcInitialStatus` without initializing the `status` field. `setOcInitialStatus` reads the field as first thing: static void setOcInitialStatus(ObjectCode* oc) { if (oc->status == OBJECT_DONT_RESOLVE) return; if (oc->archiveMemberName == NULL) { oc->status = OBJECT_NEEDED; } else { oc->status = OBJECT_LOADED; } } `setOcInitialStatus` is unsed in two places for two different purposes: in `mkOc` where we don't have the `status` field initialized yet (`mkOc` is supposed to initialize it), and `loadOc` where we do have `status` field initialized and we want to update it. Instead of splitting the function into two functions which are both called just once I inline the functions in the use sites and remove it. Fixes #18342 - - - - - da18ff99 by Tamar Christina at 2020-06-18T23:07:03-04:00 fix windows bootstrap due to linker changes - - - - - 2af0ec90 by Sylvain Henry at 2020-06-18T23:07:47-04:00 DynFlags: store default depth in SDocContext (#17957) It avoids having to use DynFlags to reach for pprUserLength. - - - - - d4a0be75 by Sylvain Henry at 2020-06-18T23:08:35-04:00 Move tablesNextToCode field into Platform tablesNextToCode is a platform setting and doesn't belong into DynFlags (#17957). Doing this is also a prerequisite to fix #14335 where we deal with two platforms (target and host) that may have different platform settings. - - - - - 809caedf by John Ericson at 2020-06-23T22:47:37-04:00 Switch from HscSource to IsBootInterface for module lookup in GhcMake We look up modules by their name, and not their contents. There is no way to separately reference a signature vs regular module; you get what you get. Only boot files can be referenced indepenently with `import {-# SOURCE #-}`. - - - - - 7750bd45 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Cmm: introduce SAVE_REGS/RESTORE_REGS We don't want to save both Fn and Dn register sets on x86-64 as they are aliased to the same arch register (XMMn). Moreover, when SAVE_STGREGS was used in conjunction with `jump foo [*]` which makes a set of Cmm registers alive so that they cover all arch registers used to pass parameter, we could have Fn, Dn and XMMn alive at the same time. It made the LLVM code generator choke (see #17920). Now `SAVE_REGS/RESTORE_REGS` and `jump foo [*]` use the same set of registers. - - - - - 2636794d by Sylvain Henry at 2020-06-23T22:48:18-04:00 CmmToC: don't add extern decl to parsed Cmm data Previously, if a .cmm file *not in the RTS* contained something like: ```cmm section "rodata" { msg : bits8[] "Test\n"; } ``` It would get compiled by CmmToC into: ```c ERW_(msg); const char msg[] = "Test\012"; ``` and fail with: ``` /tmp/ghc32129_0/ghc_4.hc:5:12: error: error: conflicting types for \u2018msg\u2019 const char msg[] = "Test\012"; ^~~ In file included from /tmp/ghc32129_0/ghc_4.hc:3:0: error: /tmp/ghc32129_0/ghc_4.hc:4:6: error: note: previous declaration of \u2018msg\u2019 was here ERW_(msg); ^ /builds/hsyl20/ghc/_build/install/lib/ghc-8.11.0.20200605/lib/../lib/x86_64-linux-ghc-8.11.0.20200605/rts-1.0/include/Stg.h:253:46: error: note: in definition of macro \u2018ERW_\u2019 #define ERW_(X) extern StgWordArray (X) ^ ``` See the rationale for this on https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/compiler/backends/ppr-c#prototypes Now we don't generate these extern declarations (ERW_, etc.) for top-level data. It shouldn't change anything for the RTS (the only place we use .cmm files) as it is already special cased in `GHC.Cmm.CLabel.needsCDecl`. And hand-written Cmm can use explicit extern declarations when needed. Note that it allows `cgrun069` test to pass with CmmToC (cf #15467). - - - - - 5f6a0665 by Sylvain Henry at 2020-06-23T22:48:18-04:00 LLVM: refactor and comment register padding code (#17920) - - - - - cad62ef1 by Sylvain Henry at 2020-06-23T22:48:18-04:00 Add tests for #17920 Metric Decrease: T12150 T12234 - - - - - a2a9006b by Xavier Denis at 2020-06-23T22:48:56-04:00 Fix issue #18262 by zonking constraints after solving Zonk residual constraints in checkForExistence to reveal user type errors. Previously when `:instances` was used with instances that have TypeError constraints the result would look something like: instance [safe] s0 => Err 'A -- Defined at ../Bug2.hs:8:10 whereas after zonking, `:instances` now sees the `TypeError` and properly eliminates the constraint from the results. - - - - - 181516bc by Simon Peyton Jones at 2020-06-23T22:49:33-04:00 Fix a buglet in Simplify.simplCast This bug, revealed by #18347, is just a missing update to sc_hole_ty in simplCast. I'd missed a code path when I made the recentchanges in commit 6d49d5be904c0c01788fa7aae1b112d5b4dfaf1c Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 21 12:53:35 2020 +0100 Implement cast worker/wrapper properly The fix is very easy. Two other minor changes * Tidy up in SimpleOpt.simple_opt_expr. In fact I think this is an outright bug, introduced in the fix to #18112: we were simplifying the same coercion twice *with the same substitution*, which is just wrong. It'd be a hard bug to trigger, so I just fixed it; less code too. * Better debug printing of ApplyToVal - - - - - 625a7f54 by Simon Peyton Jones at 2020-06-23T22:50:11-04:00 Two small tweaks to Coercion.simplifyArgsWorker These tweaks affect the inner loop of simplifyArgsWorker, which in turn is called from the flattener in Flatten.hs. This is a key perf bottleneck to T9872{a,b,c,d}. These two small changes have a modest but useful benefit. No change in functionality whatsoever. Relates to #18354 - - - - - b5768cce by Sylvain Henry at 2020-06-23T22:50:49-04:00 Don't use timesInt2# with GHC < 8.11 (fix #18358) - - - - - 7ad4085c by Sylvain Henry at 2020-06-23T22:51:27-04:00 Fix invalid printf format - - - - - a1f34d37 by Krzysztof Gogolewski at 2020-06-23T22:52:09-04:00 Add missing entry to freeNamesItem (#18369) - - - - - 03a708ba by Andreas Klebinger at 2020-06-25T03:54:37-04:00 Enable large address space optimization on windows. Starting with Win 8.1/Server 2012 windows no longer preallocates page tables for reserverd memory eagerly, which prevented us from using this approach in the past. We also try to allocate the heap high in the memory space. Hopefully this makes it easier to allocate things in the low 4GB of memory that need to be there. Like jump islands for the linker. - - - - - 7e6d3d09 by Roland Senn at 2020-06-25T03:54:38-04:00 In `:break ident` allow out of scope and nested identifiers (Fix #3000) This patch fixes the bug and implements the feature request of #3000. 1. If `Module` is a real module name and `identifier` a name of a top-level function in `Module` then `:break Module.identifer` works also for an `identifier` that is out of scope. 2. Extend the syntax for `:break identifier` to: :break [ModQual.]topLevelIdent[.nestedIdent]...[.nestedIdent] `ModQual` is optional and is either the effective name of a module or the local alias of a qualified import statement. `topLevelIdent` is the name of a top level function in the module referenced by `ModQual`. `nestedIdent` is optional and the name of a function nested in a let or where clause inside the previously mentioned function `nestedIdent` or `topLevelIdent`. If `ModQual` is a module name, then `topLevelIdent` can be any top level identifier in this module. If `ModQual` is missing or a local alias of a qualified import, then `topLevelIdent` must be in scope. Breakpoints can be set on arbitrarily deeply nested functions, but the whole chain of nested function names must be specified. 3. To support the new functionality rewrite the code to tab complete `:break`. - - - - - 30e42652 by Ben Gamari at 2020-06-25T03:54:39-04:00 make: Respect XELATEX variable Previously we simply ignored the XELATEX variable when building PDF documentation. - - - - - 4acc2934 by Ben Gamari at 2020-06-25T03:54:39-04:00 hadrian/make: Detect makeindex Previously we would simply assume that makeindex was available. Now we correctly detect it in `configure` and respect this conclusion in hadrian and make. - - - - - 0d61f866 by Simon Peyton Jones at 2020-06-25T03:54:40-04:00 Expunge GhcTcId GHC.Hs.Extension had type GhcPs = GhcPass 'Parsed type GhcRn = GhcPass 'Renamed type GhcTc = GhcPass 'Typechecked type GhcTcId = GhcTc The last of these, GhcTcId, is a vestige of the past. This patch expunges it from GHC. - - - - - 8ddbed4a by Adam Wespiser at 2020-06-25T03:54:40-04:00 add examples to Data.Traversable - - - - - 284001d0 by Oleg Grenrus at 2020-06-25T03:54:42-04:00 Export readBinIface_ - - - - - 90f43872 by Zubin Duggal at 2020-06-25T03:54:43-04:00 Export everything from HsToCore. This lets us reuse these functions in haddock, avoiding synchronization bugs. Also fixed some divergences with haddock in that file Updates haddock submodule - - - - - c7dd6da7 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part1) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Hs.* - GHC.Core.* - GHC.Stg.* - GHC.Cmm.* - GHC.Types.* - GHC.Data.* - GHC.Builtin.* - GHC.Parser.* - GHC.Driver.* - GHC top - - - - - 1eb997a8 by Takenobu Tani at 2020-06-25T03:54:44-04:00 Clean up haddock hyperlinks of GHC.* (part2) This updates haddock comments only. This patch focuses to update for hyperlinks in GHC API's haddock comments, because broken links especially discourage newcomers. This includes the following hierarchies: - GHC.Iface.* - GHC.Llvm.* - GHC.Rename.* - GHC.Tc.* - GHC.HsToCore.* - GHC.StgToCmm.* - GHC.CmmToAsm.* - GHC.Runtime.* - GHC.Unit.* - GHC.Utils.* - GHC.SysTools.* - - - - - 67a86b4d by Oleg Grenrus at 2020-06-25T03:54:46-04:00 Add MonadZip and MonadFix instances for Complex These instances are taken from https://hackage.haskell.org/package/linear-1.21/docs/Linear-Instances.html They are the unique possible, so let they be in `base`. - - - - - c50ef26e by Artem Pelenitsyn at 2020-06-25T03:54:47-04:00 test suite: add reproducer for #17516 - - - - - fe281b27 by Roland Senn at 2020-06-25T03:54:48-04:00 Enable maxBound checks for OverloadedLists (Fixes #18172) Consider the Literal `[256] :: [Data.Word.Word8]` When the `OverloadedLists` extension is not active, then the `ol_ext` field in the `OverLitTc` record that is passed to the function `getIntegralLit` contains the type `Word8`. This is a simple type, and we can use its type constructor immediately for the `warnAboutOverflowedLiterals` function. When the `OverloadedLists` extension is active, then the `ol_ext` field contains the type family `Item [Word8]`. The function `nomaliseType` is used to convert it to the needed type `Word8`. - - - - - a788d4d1 by Ben Gamari at 2020-06-25T03:54:52-04:00 rts/Hash: Simplify freeing of HashListChunks While looking at #18348 I noticed that the treatment of HashLists are a bit more complex than necessary (which lead to some initial confusion on my part). Specifically, we allocate HashLists in chunks. Each chunk allocation makes two allocations: one for the chunk itself and one for a HashListChunk to link together the chunks for the purposes of freeing. Simplify this (and hopefully make the relationship between these clearer) but allocating the HashLists and HashListChunk in a single malloc. This will both make the implementation easier to follow and reduce C heap fragmentation. Note that even after this patch we fail to bound the size of the free HashList pool. However, this is a separate bug. - - - - - d3c2d59b by Sylvain Henry at 2020-06-25T03:54:55-04:00 RTS: avoid overflow on 32-bit arch (#18375) We're now correctly computing allocated bytes on 32-bit arch, so we get huge increases. Metric Increase: haddock.Cabal haddock.base haddock.compiler space_leak_001 - - - - - a3d69dc6 by Sebastian Graf at 2020-06-25T23:06:18-04:00 GHC.Core.Unify: Make UM actions one-shot by default This MR makes the UM monad in GHC.Core.Unify into a one-shot monad. See the long Note [The one-shot state monad trick]. See also #18202 and !3309, which applies this to all Reader/State-like monads in GHC for compile-time perf improvements. The pattern used here enables something similar to the state-hack, but is applicable to user-defined monads, not just `IO`. Metric Decrease 'runtime/bytes allocated' (test_env='i386-linux-deb9'): haddock.Cabal - - - - - 9ee58f8d by Matthias Pall Gissurarson at 2020-06-26T17:12:45+00:00 Implement the proposed -XQualifiedDo extension Co-authored-by: Facundo Domínguez <facundo.dominguez at tweag.io> QualifiedDo is implemented using the same placeholders for operation names in the AST that were devised for RebindableSyntax. Whenever the renamer checks which names to use for do syntax, it first checks if the do block is qualified (e.g. M.do { stmts }), in which case it searches for qualified names in the module M. This allows users to write {-# LANGUAGE QualifiedDo #-} import qualified SomeModule as M f x = M.do -- desugars to: y <- M.return x -- M.return x M.>>= \y -> M.return y -- M.return y M.>> M.return y -- M.return y See Note [QualifiedDo] and the users' guide for more details. Issue #18214 Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0216-qualified-do.rst Since we change the constructors `ITdo` and `ITmdo` to carry the new module name, we need to bump the haddock submodule to account or the new shape of these constructors. - - - - - ce987865 by Ryan Scott at 2020-06-27T11:55:21-04:00 Revamp the treatment of auxiliary bindings for derived instances This started as a simple fix for #18321 that organically grew into a much more sweeping refactor of how auxiliary bindings for derived instances are handled. I have rewritten `Note [Auxiliary binders]` in `GHC.Tc.Deriv.Generate` to explain all of the moving parts, but the highlights are: * Previously, the OccName of each auxiliary binding would be given a suffix containing a hash of its package name, module name, and parent data type to avoid name clashes. This was needlessly complicated, so we take the more direct approach of generating `Exact` `RdrName`s for each auxiliary binding with the same `OccName`, but using an underlying `System` `Name` with a fresh `Unique` for each binding. Unlike hashes, allocating new `Unique`s does not require any cleverness and avoid name clashes all the same... * ...speaking of which, in order to convince the renamer that multiple auxiliary bindings with the same `OccName` (but different `Unique`s) are kosher, we now use `rnLocalValBindsLHS` instead of `rnTopBindsLHS` to rename auxiliary bindings. Again, see `Note [Auxiliary binders]` for the full story. * I have removed the `DerivHsBind` constructor for `DerivStuff`—which was only used for `Data.Data`-related auxiliary bindings—and refactored `gen_Data_binds` to use `DerivAuxBind` instead. This brings the treatment of `Data.Data`-related auxiliary bindings in line with every other form of auxiliary binding. Fixes #18321. - - - - - a403eb91 by Sylvain Henry at 2020-06-27T11:55:59-04:00 ghc-bignum: fix division by zero (#18359) - - - - - 1b3d13b6 by Sylvain Henry at 2020-06-27T11:55:59-04:00 Fix ghc-bignum exceptions We must ensure that exceptions are not simplified. Previously we used: case raiseDivZero of _ -> 0## -- dummyValue But it was wrong because the evaluation of `raiseDivZero` was removed and the dummy value was directly returned. See new Note [ghc-bignum exceptions]. I've also removed the exception triggering primops which were fragile. We don't need them to be primops, we can have them exported by ghc-prim. I've also added a test for #18359 which triggered this patch. - - - - - a74ec37c by Simon Peyton Jones at 2020-06-27T11:56:34-04:00 Better loop detection in findTypeShape Andreas pointed out, in !3466, that my fix for #18304 was not quite right. This patch fixes it properly, by having just one RecTcChecker rather than (implicitly) two nested ones, in findTypeShape. - - - - - a04020b8 by Sylvain Henry at 2020-06-27T11:57:11-04:00 DynFlags: don't store buildTag `DynFlags.buildTag` was a field created from the set of Ways in `DynFlags.ways`. It had to be kept in sync with `DynFlags.ways` which was fragile. We want to avoid global state like this (#17957). Moreover in #14335 we also want to support loading units with different ways: target units would still use `DynFlags.ways` but plugins would use `GHC.Driver.Ways.hostFullWays`. To avoid having to deal both with build tag and with ways, we recompute the buildTag on-the-fly (should be pretty cheap) and we remove `DynFlags.buildTag` field. - - - - - 0e83efa2 by Krzysztof Gogolewski at 2020-06-27T11:57:49-04:00 Don't generalize when typechecking a tuple section The code is simpler and cleaner. - - - - - d8ba9e6f by Peter Trommler at 2020-06-28T09:19:11-04:00 RTS: Refactor Haskell-C glue for PPC 64-bit Make sure the stack is 16 byte aligned even when reserved stack bytes are not a multiple of 16 bytes. Avoid saving r2 (TOC). On ELF v1 the function descriptor of StgReturn has the same TOC as StgRun, on ELF v2 the TOC is recomputed in the function prologue. Use the ABI provided functions to save clobbered GPRs and FPRs. Improve comments. Describe what the stack looks like and how it relates to the respective ABIs. - - - - - 42f797b0 by Ryan Scott at 2020-06-28T09:19:46-04:00 Use NHsCoreTy to embed types into GND-generated code `GeneralizedNewtypeDeriving` is in the unique situation where it must produce an `LHsType GhcPs` from a Core `Type`. Historically, this was done with the `typeToLHsType` function, which walked over the entire `Type` and attempted to construct an `LHsType` with the same overall structure. `typeToLHsType` is quite complicated, however, and has been the subject of numerous bugs over the years (e.g., #14579). Luckily, there is an easier way to accomplish the same thing: the `XHsType` constructor of `HsType`. `XHsType` bundles an `NHsCoreTy`, which allows embedding a Core `Type` directly into an `HsType`, avoiding the need to laboriously convert from one to another (as `typeToLHsType` did). Moreover, renaming and typechecking an `XHsType` is simple, since one doesn't need to do anything to a Core `Type`... ...well, almost. For the reasons described in `Note [Typechecking NHsCoreTys]` in `GHC.Tc.Gen.HsType`, we must apply a substitution that we build from the local `tcl_env` type environment. But that's a relatively modest price to pay. Now that `GeneralizedNewtypeDeriving` uses `NHsCoreTy`, the `typeToLHsType` function no longer has any uses in GHC, so this patch rips it out. Some additional tweaks to `hsTypeNeedsParens` were necessary to make the new `-ddump-deriv` output correctly parenthesized, but other than that, this patch is quite straightforward. This is a mostly internal refactoring, although it is likely that `GeneralizedNewtypeDeriving`-generated code will now need fewer language extensions in certain situations than it did before. - - - - - 68530b1c by Jan Hrček at 2020-06-28T09:20:22-04:00 Fix duplicated words and typos in comments and user guide - - - - - 15b79bef by Ryan Scott at 2020-06-28T09:20:57-04:00 Add integer-gmp's ghc.mk and GNUmakefile to .gitignore - - - - - bfa5698b by Simon Peyton Jones at 2020-06-28T09:21:32-04:00 Fix a typo in Lint This simple error in GHC.Core.Litn.lintJoinLams meant that Lint reported bogus errors. Fixes #18399 - - - - - 71006532 by Ryan Scott at 2020-06-30T07:10:42-04:00 Reject nested foralls/contexts in instance types more consistently GHC is very wishy-washy about rejecting instance declarations with nested `forall`s or contexts that are surrounded by outermost parentheses. This can even lead to some strange interactions with `ScopedTypeVariables`, as demonstrated in #18240. This patch makes GHC more consistently reject instance types with nested `forall`s/contexts so as to prevent these strange interactions. On the implementation side, this patch tweaks `splitLHsInstDeclTy` and `getLHsInstDeclHead` to not look through parentheses, which can be semantically significant. I've added a `Note [No nested foralls or contexts in instance types]` in `GHC.Hs.Type` to explain why. This also introduces a `no_nested_foralls_contexts_err` function in `GHC.Rename.HsType` to catch nested `forall`s/contexts in instance types. This function is now used in `rnClsInstDecl` (for ordinary instance declarations) and `rnSrcDerivDecl` (for standalone `deriving` declarations), the latter of which fixes #18271. On the documentation side, this adds a new "Formal syntax for instance declaration types" section to the GHC User's Guide that presents a BNF-style grammar for what is and isn't allowed in instance types. Fixes #18240. Fixes #18271. - - - - - bccf3351 by Sylvain Henry at 2020-06-30T07:10:46-04:00 Add ghc-bignum to 8.12 release notes - - - - - 81704a6f by David Eichmann at 2020-06-30T07:10:48-04:00 Update ssh keys in CI performance metrics upload script - - - - - 85310fb8 by Joshua Price at 2020-06-30T07:10:49-04:00 Add missing Ix instances for tuples of size 6 through 15 (#16643) - - - - - cbb6b62f by Vladislav Zavialov at 2020-07-01T15:41:38-04:00 Implement -XLexicalNegation (GHC Proposal #229) This patch introduces a new extension, -XLexicalNegation, which detects whether the minus sign stands for negation or subtraction using the whitespace-based rules described in GHC Proposal #229. Updates haddock submodule. - - - - - fb5a0d01 by Martin Handley at 2020-07-01T15:42:14-04:00 #17169: Clarify Fixed's Enum instance. - - - - - b316804d by Simon Peyton Jones at 2020-07-01T15:42:49-04:00 Improve debug tracing for substitution This patch improves debug tracing a bit (#18395) * Remove the ancient SDoc argument to substitution, replacing it with a HasDebugCallStack constraint. The latter does the same job (indicate the call site) but much better. * Add HasDebugCallStack to simpleOptExpr, exprIsConApp_maybe I needed this to help nail the lookupIdSubst panic in #18326, #17784 - - - - - 5c9fabb8 by Hécate at 2020-07-01T15:43:25-04:00 Add most common return values for `os` and `arch` - - - - - 76d8cc74 by Ryan Scott at 2020-07-01T15:44:01-04:00 Desugar quoted uses of DerivingVia and expression type signatures properly The way that `GHC.HsToCore.Quote` desugared quoted `via` types (e.g., `deriving via forall a. [a] instance Eq a => Eq (List a)`) and explicit type annotations in signatures (e.g., `f = id @a :: forall a. a -> a`) was completely wrong, as it did not implement the scoping guidelines laid out in `Note [Scoped type variables in bindings]`. This is easily fixed. While I was in town, I did some minor cleanup of related Notes: * `Note [Scoped type variables in bindings]` and `Note [Scoped type variables in class and instance declarations]` say very nearly the same thing. I decided to just consolidate the two Notes into `Note [Scoped type variables in quotes]`. * `Note [Don't quantify implicit type variables in quotes]` is somewhat outdated, as it predates GHC 8.10, where the `forall`-or-nothing rule requires kind variables to be explicitly quantified in the presence of an explicit `forall`. As a result, the running example in that Note doesn't even compile. I have changed the example to something simpler that illustrates the same point that the original Note was making. Fixes #18388. - - - - - 44d6a335 by Andreas Klebinger at 2020-07-02T02:54:54-04:00 T16012: Be verbose on failure. - - - - - f9853330 by Ryan Scott at 2020-07-02T02:55:29-04:00 Bump ghc-prim version to 0.7.0 Fixes #18279. Bumps the `text` submodule. - - - - - 23e4e047 by Sylvain Henry at 2020-07-02T10:46:31-04:00 Hadrian: fix PowerPC64le support (#17601) [ci skip] - - - - - 3cdd8d69 by Sylvain Henry at 2020-07-02T10:47:08-04:00 NCG: correctly handle addresses with huge offsets (#15570) Before this patch we could generate addresses of this form: movzbl cP0_str+-9223372036854775808,%eax The linker can't handle them because the offset is too large: ld.lld: error: Main.o:(.text+0xB3): relocation R_X86_64_32S out of range: -9223372036852653050 is not in [-2147483648, 2147483647] With this patch we detect those cases and generate: movq $-9223372036854775808,%rax addq $cP0_str,%rax movzbl (%rax),%eax I've also refactored `getAmode` a little bit to make it easier to understand and to trace. - - - - - 4d90b3ff by Gabor Greif at 2020-07-02T20:07:59-04:00 No need for CURSES_INCLUDE_DIRS This is a leftover from ef63ff27251a20ff11e58c9303677fa31e609a88 - - - - - f08d6316 by Sylvain Henry at 2020-07-02T20:08:36-04:00 Replace Opt_SccProfilingOn flag with sccProfilingEnabled helper function SCC profiling was enabled in a convoluted way: if WayProf was enabled, Opt_SccProfilingOn general flag was set (in `GHC.Driver.Ways.wayGeneralFlags`), and then this flag was queried in various places. There is no need to go via general flags, so this patch defines a `sccProfilingEnabled :: DynFlags -> Bool` helper function that just checks whether WayProf is enabled. - - - - - 8cc7274b by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Only allocate the Censuses that we need When not LDV profiling there is no reason to allocate 32 Censuses; one will do. This is a very small memory footprint optimisation, but it comes for free. - - - - - b835112c by Ben Gamari at 2020-07-03T02:49:27-04:00 rts/ProfHeap: Free old allocations when reinitialising Censuses Previously when not LDV profiling we would repeatedly reinitialise `censuses[0]` with `initEra`. This failed to free the `Arena` and `HashTable` from the old census, resulting in a memory leak. Fixes #18348. - - - - - 34be6523 by Valery Tolstov at 2020-07-03T02:50:03-04:00 Mention flags that are not enabled by -Wall (#18372) * Mention missing flags that are not actually enabled by -Wall (docs/users_guide/using-warnings.rst) * Additionally remove -Wmissing-monadfail-instances from the list of flags enabled by -Wcompat, as it is not the case since 8.8 - - - - - edc8d22b by Sylvain Henry at 2020-07-03T02:50:40-04:00 LLVM: support R9 and R10 registers d535ef006d85dbdb7cda2b09c5bc35cb80108909 allowed the use of up to 10 vanilla registers but didn't update LLVM backend to support them. This patch fixes it. - - - - - 4bf18646 by Simon Peyton Jones at 2020-07-03T08:37:42+01:00 Improve handling of data type return kinds Following a long conversation with Richard, this patch tidies up the handling of return kinds for data/newtype declarations (vanilla, family, and instance). I have substantially edited the Notes in TyCl, so they would bear careful reading. Fixes #18300, #18357 In GHC.Tc.Instance.Family.newFamInst we were checking some Lint-like properties with ASSSERT. Instead Richard and I have added a proper linter for axioms, and called it from lintGblEnv, which in turn is called in tcRnModuleTcRnM New tests (T18300, T18357) cause an ASSERT failure in HEAD. - - - - - 41d26492 by Sylvain Henry at 2020-07-03T17:33:59-04:00 DynFlags: avoid the use of sdocWithDynFlags in GHC.Core.Rules (#17957) - - - - - 7aa6ef11 by Hécate at 2020-07-03T17:34:36-04:00 Add the __GHC_FULL_VERSION__ CPP macro to expose the full GHC version - - - - - e61d5395 by Chaitanya Koparkar at 2020-07-07T13:55:59-04:00 ghc-prim: Turn some comments into haddocks [ci skip] - - - - - 37743f91 by John Ericson at 2020-07-07T13:56:00-04:00 Support `timesInt2#` in LLVM backend - - - - - 46397e53 by John Ericson at 2020-07-07T13:56:00-04:00 `genericIntMul2Op`: Call `genericWordMul2Op` directly This unblocks a refactor, and removes partiality. It might be a PowerPC regression but that should be fixable. - - - - - 8a1c0584 by John Ericson at 2020-07-07T13:56:00-04:00 Simplify `PrimopCmmEmit` Follow @simonpj's suggestion of pushing the "into regs" logic into `emitPrimOp`. With the previous commit getting rid of the recursion in `genericIntMul2Op`, this is now an easy refactor. - - - - - 6607f203 by John Ericson at 2020-07-07T13:56:00-04:00 `opAllDone` -> `opIntoRegs` The old name was and terrible and became worse after the previous commit's refactor moved non-trivial funcationlity into its body. - - - - - fdcc53ba by Sylvain Henry at 2020-07-07T13:56:00-04:00 Optimise genericIntMul2Op We shouldn't directly call 'genericWordMul2Op' in genericIntMul2Op because a target may provide a faster primop for 'WordMul2Op': we'd better use it! - - - - - 686e7225 by Moritz Angermann at 2020-07-07T13:56:01-04:00 [linker/rtsSymbols] More linker symbols Mostly symbols needed for aarch64/armv7l and in combination with musl, where we have to rely on loading *all* objects/archives - __stack_chk_* only when not DYNAMIC - - - - - 3f60b94d by Moritz Angermann at 2020-07-07T13:56:01-04:00 better if guards. - - - - - 7abffced by Moritz Angermann at 2020-07-07T13:56:01-04:00 Fix (1) - - - - - cdfeb3f2 by Moritz Angermann at 2020-07-07T13:56:01-04:00 AArch32 symbols only on aarch32. - - - - - f496c955 by Adam Sandberg Ericsson at 2020-07-07T13:56:02-04:00 add -flink-rts flag to link the rts when linking a shared or static library #18072 By default we don't link the RTS when linking shared libraries because in the most usual mode a shared library is an intermediary product, for example a Haskell library, that will be linked into some executable in the end. So we wish to defer the RTS flavour to link to the final link. However sometimes the final product is the shared library, for example when writing a plugin for some other system, so we do wish the shared library to link the RTS. For consistency we also make -staticlib honor this flag and its inversion. -staticlib currently implies -flink-shared. - - - - - c59faf67 by Stefan Schulze Frielinghaus at 2020-07-07T13:56:04-04:00 hadrian: link check-ppr against debugging RTS if ghcDebugged - - - - - 0effc57d by Adam Sandberg Ericsson at 2020-07-07T13:56:05-04:00 rts linker: teach the linker about GLIBC's special handling of *stat, mknod and atexit functions #7072 - - - - - 96153433 by Adam Sandberg Ericsson at 2020-07-07T13:56:06-04:00 hadrian: make hadrian/ghci use the bootstrap compiler from configure #18190 - - - - - 4d24f886 by Adam Sandberg Ericsson at 2020-07-07T13:56:07-04:00 hadrian: ignore cabal configure verbosity related flags #18131 - - - - - 7332bbff by Ben Gamari at 2020-07-07T13:56:08-04:00 testsuite: Widen T12234 acceptance window to 2% Previously it wasn't uncommon to see +/-1% fluctuations in compiler allocations on this test. - - - - - 180b6313 by Gabor Greif at 2020-07-07T13:56:08-04:00 When running libtool, report it as such - - - - - d3bd6897 by Sylvain Henry at 2020-07-07T13:56:11-04:00 BigNum: rename BigNat types Before this patch BigNat names were confusing because we had: * GHC.Num.BigNat.BigNat: unlifted type used everywhere else * GHC.Num.BigNat.BigNatW: lifted type only used to share static constants * GHC.Natural.BigNat: lifted type only used for backward compatibility After this patch we have: * GHC.Num.BigNat.BigNat#: unlifted type * GHC.Num.BigNat.BigNat: lifted type (reexported from GHC.Natural) Thanks to @RyanGlScott for spotting this. - - - - - 929d26db by Sylvain Henry at 2020-07-07T13:56:12-04:00 Bignum: don't build ghc-bignum with stage0 Noticed by @Ericson2314 - - - - - d25b6851 by Sylvain Henry at 2020-07-07T13:56:12-04:00 Hadrian: ghc-gmp.h shouldn't be a compiler dependency - - - - - 0ddae2ba by Sylvain Henry at 2020-07-07T13:56:14-04:00 DynFlags: factor out pprUnitId from "Outputable UnitId" instance - - - - - 204f3f5d by Krzysztof Gogolewski at 2020-07-07T13:56:18-04:00 Remove unused function pprHsForAllExtra (#18423) The function `pprHsForAllExtra` was called only on `Nothing` since 2015 (1e041b7382b6aa). - - - - - 3033e0e4 by Adam Sandberg Ericsson at 2020-07-08T20:36:49-04:00 hadrian: add flag to skip rebuilding dependency information #17636 - - - - - b7de4b96 by Stefan Schulze Frielinghaus at 2020-07-09T09:49:22-04:00 Fix GHCi :print on big-endian platforms On big-endian platforms executing import GHC.Exts data Foo = Foo Float# deriving Show foo = Foo 42.0# foo :print foo results in an arithmetic overflow exception which is caused by function index where moveBytes equals word_size - (r + item_size_b) * 8 Here we have a mixture of units. Both, word_size and item_size_b have unit bytes whereas r has unit bits. On 64-bit platforms moveBytes equals then 8 - (0 + 4) * 8 which results in a negative and therefore invalid second parameter for a shiftL operation. In order to make things more clear the expression (word .&. (mask `shiftL` moveBytes)) `shiftR` moveBytes is equivalent to (word `shiftR` moveBytes) .&. mask On big-endian platforms the shift must be a left shift instead of a right shift. For symmetry reasons not a mask is used but two shifts in order to zero out bits. Thus the fixed version equals case endian of BigEndian -> (word `shiftL` moveBits) `shiftR` zeroOutBits `shiftL` zeroOutBits LittleEndian -> (word `shiftR` moveBits) `shiftL` zeroOutBits `shiftR` zeroOutBits Fixes #16548 and #14455 - - - - - 3656dff8 by Sylvain Henry at 2020-07-09T09:50:01-04:00 LLVM: fix MO_S_Mul2 support (#18434) The value indicating if the carry is useful wasn't taken into account. - - - - - d9f09506 by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Define multiShotIO and use it in mkSplitUniqueSupply This patch is part of the ongoing eta-expansion saga; see #18238. It implements a neat trick (suggested by Sebastian Graf) that allows the programmer to disable the default one-shot behaviour of IO (the "state hack"). The trick is to use a new multiShotIO function; see Note [multiShotIO]. For now, multiShotIO is defined here in Unique.Supply; but it should ultimately be moved to the IO library. The change is necessary to get good code for GHC's unique supply; see Note [Optimising the unique supply]. However it makes no difference to GHC as-is. Rather, it makes a difference when a subsequent commit Improve eta-expansion using ArityType lands. - - - - - bce695cc by Simon Peyton Jones at 2020-07-10T10:33:44-04:00 Make arityType deal with join points As Note [Eta-expansion and join points] describes, this patch makes arityType deal correctly with join points. What was there before was not wrong, but yielded lower arities than it could. Fixes #18328 In base GHC this makes no difference to nofib. Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- n-body -0.1% -0.1% -1.2% -1.1% 0.0% -------------------------------------------------------------------------------- Min -0.1% -0.1% -55.0% -56.5% 0.0% Max -0.0% 0.0% +16.1% +13.4% 0.0% Geometric Mean -0.0% -0.0% -30.1% -31.0% -0.0% But it starts to make real difference when we land the change to the way mkDupableAlts handles StrictArg, in fixing #13253 and friends. I think this is because we then get more non-inlined join points. - - - - - 2b7c71cb by Simon Peyton Jones at 2020-07-11T12:17:02-04:00 Improve eta-expansion using ArityType As #18355 shows, we were failing to preserve one-shot info when eta-expanding. It's rather easy to fix, by using ArityType more, rather than just Arity. This patch is important to suport the one-shot monad trick; see #18202. But the extra tracking of one-shot-ness requires the patch Define multiShotIO and use it in mkSplitUniqueSupply If that patch is missing, ths patch makes things worse in GHC.Types.Uniq.Supply. With it, however, we see these improvements T3064 compiler bytes allocated -2.2% T3294 compiler bytes allocated -1.3% T12707 compiler bytes allocated -1.3% T13056 compiler bytes allocated -2.2% Metric Decrease: T3064 T3294 T12707 T13056 - - - - - de139cc4 by Artem Pelenitsyn at 2020-07-12T02:53:20-04:00 add reproducer for #15630 - - - - - c4de6a7a by Andreas Klebinger at 2020-07-12T02:53:55-04:00 Give Uniq[D]FM a phantom type for its key. This fixes #17667 and should help to avoid such issues going forward. The changes are mostly mechanical in nature. With two notable exceptions. * The register allocator. The register allocator references registers by distinct uniques. However they come from the types of VirtualReg, Reg or Unique in various places. As a result we sometimes cast the key type of the map and use functions which operate on the now typed map but take a raw Unique as actual key. The logic itself has not changed it just becomes obvious where we do so now. * <Type>Env Modules. As an example a ClassEnv is currently queried using the types `Class`, `Name`, and `TyCon`. This is safe since for a distinct class value all these expressions give the same unique. getUnique cls getUnique (classTyCon cls) getUnique (className cls) getUnique (tcName $ classTyCon cls) This is for the most part contained within the modules defining the interface. However it requires us to play dirty when we are given a `Name` to lookup in a `UniqFM Class a` map. But again the logic did not change and it's for the most part hidden behind the Env Module. Some of these cases could be avoided by refactoring but this is left for future work. We also bump the haddock submodule as it uses UniqFM. - - - - - c2cfdfde by Aaron Allen at 2020-07-13T09:00:33-04:00 Warn about empty Char enumerations (#18402) Currently the "Enumeration is empty" warning (-Wempty-enumerations) only fires for numeric literals. This patch adds support for `Char` literals so that enumerating an empty list of `Char`s will also trigger the warning. - - - - - c3ac87ec by Stefan Schulze Frielinghaus at 2020-07-13T09:01:10-04:00 hadrian: build check-ppr dynamic if GHC is build dynamic Fixes #18361 - - - - - 9ad072b4 by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Use dumpStyle when printing inlinings This just makes debug-printing consistent, and more informative. - - - - - e78c4efb by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Comments only - - - - - 7ccb760b by Simon Peyton Jones at 2020-07-13T14:52:49-04:00 Reduce result discount in conSize Ticket #18282 showed that the result discount given by conSize was massively too large. This patch reduces that discount to a constant 10, which just balances the cost of the constructor application itself. Note [Constructor size and result discount] elaborates, as does the ticket #18282. Reducing result discount reduces inlining, which affects perf. I found that I could increase the unfoldingUseThrehold from 80 to 90 in compensation; in combination with the result discount change I get these overall nofib numbers: Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- boyer -0.2% +5.4% -3.2% -3.4% 0.0% cichelli -0.1% +5.9% -11.2% -11.7% 0.0% compress2 -0.2% +9.6% -6.0% -6.8% 0.0% cryptarithm2 -0.1% -3.9% -6.0% -5.7% 0.0% gamteb -0.2% +2.6% -13.8% -14.4% 0.0% genfft -0.1% -1.6% -29.5% -29.9% 0.0% gg -0.0% -2.2% -17.2% -17.8% -20.0% life -0.1% -2.2% -62.3% -63.4% 0.0% mate +0.0% +1.4% -5.1% -5.1% -14.3% parser -0.2% -2.1% +7.4% +6.7% 0.0% primetest -0.2% -12.8% -14.3% -14.2% 0.0% puzzle -0.2% +2.1% -10.0% -10.4% 0.0% rsa -0.2% -11.7% -3.7% -3.8% 0.0% simple -0.2% +2.8% -36.7% -38.3% -2.2% wheel-sieve2 -0.1% -19.2% -48.8% -49.2% -42.9% -------------------------------------------------------------------------------- Min -0.4% -19.2% -62.3% -63.4% -42.9% Max +0.3% +9.6% +7.4% +11.0% +16.7% Geometric Mean -0.1% -0.3% -17.6% -18.0% -0.7% I'm ok with these numbers, remembering that this change removes an *exponential* increase in code size in some in-the-wild cases. I investigated compress2. The difference is entirely caused by this function no longer inlining WriteRoutines.$woutputCodes = \ (w :: [CodeEvent]) -> let result_s1Sr = case WriteRoutines.outputCodes_$s$woutput w 0# 0# 8# 9# of (# ww1, ww2 #) -> (ww1, ww2) in (# case result_s1Sr of (x, _) -> map @Int @Char WriteRoutines.outputCodes1 x , case result_s1Sr of { (_, y) -> y } #) It was right on the cusp before, driven by the excessive result discount. Too bad! Happily, the compiler/perf tests show a number of improvements: T12227 compiler bytes-alloc -6.6% T12545 compiler bytes-alloc -4.7% T13056 compiler bytes-alloc -3.3% T15263 runtime bytes-alloc -13.1% T17499 runtime bytes-alloc -14.3% T3294 compiler bytes-alloc -1.1% T5030 compiler bytes-alloc -11.7% T9872a compiler bytes-alloc -2.0% T9872b compiler bytes-alloc -1.2% T9872c compiler bytes-alloc -1.5% Metric Decrease: T12227 T12545 T13056 T15263 T17499 T3294 T5030 T9872a T9872b T9872c - - - - - 7f0b671e by Ben Gamari at 2020-07-13T14:52:49-04:00 testsuite: Widen acceptance threshold on T5837 This test is positively tiny and consequently the bytes allocated measurement will be relatively noisy. Consequently I have seen this fail spuriously quite often. - - - - - 118e1c3d by Alp Mestanogullari at 2020-07-14T21:30:52-04:00 compiler: re-engineer the treatment of rebindable if Executing on the plan described in #17582, this patch changes the way if expressions are handled in the compiler in the presence of rebindable syntax. We get rid of the SyntaxExpr field of HsIf and instead, when rebindable syntax is on, we rewrite the HsIf node to the appropriate sequence of applications of the local `ifThenElse` function. In order to be able to report good error messages, with expressions as they were written by the user (and not as desugared by the renamer), we make use of TTG extensions to extend GhcRn expression ASTs with an `HsExpansion` construct, which keeps track of a source (GhcPs) expression and the desugared (GhcRn) expression that it gives rise to. This way, we can typecheck the latter while reporting the former in error messages. In order to discard the error context lines that arise from typechecking the desugared expressions (because they talk about expressions that the user has not written), we carefully give a special treatment to the nodes fabricated by this new renaming-time transformation when typechecking them. See Note [Rebindable syntax and HsExpansion] for more details. The note also includes a recipe to apply the same treatment to other rebindable constructs. Tests 'rebindable11' and 'rebindable12' have been added to make sure we report identical error messages as before this patch under various circumstances. We also now disable rebindable syntax when processing untyped TH quotes, as per the discussion in #18102 and document the interaction of rebindable syntax and Template Haskell, both in Note [Template Haskell quotes and Rebindable Syntax] and in the user guide, adding a test to make sure that we do not regress in that regard. - - - - - 64c774b0 by Andreas Klebinger at 2020-07-14T21:31:27-04:00 Explain why keeping DynFlags in AnalEnv saves allocation. - - - - - 254245d0 by Ben Gamari at 2020-07-14T21:32:03-04:00 docs/users-guide: Update default -funfolding-use-threshold value This was changed in 3d2991f8 but I neglected to update the documentation. Fixes #18419. - - - - - 4c259f86 by Andreas Klebinger at 2020-07-14T21:32:41-04:00 Escape backslashes in json profiling reports properly. I also took the liberty to do away the fixed buffer size for escaping. Using a fixed size here can only lead to issues down the line. Fixes #18438. - - - - - 23797224 by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 .gitlab: re-enable integer-simple substitute (BIGNUM_BACKEND) Recently build system migrated from INTEGER_LIBRARY to BIGNUM_BACKEND. But gitlab CI was never updated. Let's enable BIGNUM_BACKEND=native. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - e0db878a by Sergei Trofimovich at 2020-07-14T21:33:19-04:00 ghc-bignum: bring in sync .hs-boot files with module declarations Before this change `BIGNUM_BACKEND=native` build was failing as: ``` libraries/ghc-bignum/src/GHC/Num/BigNat/Native.hs:708:16: error: * Variable not in scope: naturalFromBigNat# :: WordArray# -> t * Perhaps you meant one of these: `naturalFromBigNat' (imported from GHC.Num.Natural), `naturalToBigNat' (imported from GHC.Num.Natural) | 708 | m' = naturalFromBigNat# m | ``` This happens because `.hs-boot` files are slightly out of date. This change brings in data and function types in sync. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - c9f65c36 by Stefan Schulze Frielinghaus at 2020-07-14T21:33:57-04:00 rts/Disassembler.c: Use FMT_HexWord for printing values in hex format - - - - - 58ae62eb by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - cdc4a6b0 by Matthias Andreas Benkard at 2020-07-14T21:34:35-04:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 51dbfa52 by Ben Gamari at 2020-07-15T04:05:34-04:00 StgToCmm: Use CmmRegOff smart constructor Previously we would generate expressions of the form `CmmRegOff BaseReg 0`. This should do no harm (and really should be handled by the NCG anyways) but it's better to just generate a plain `CmmReg`. - - - - - ae11bdfd by Ben Gamari at 2020-07-15T04:06:08-04:00 testsuite: Add regression test for #17744 Test due to @monoidal. - - - - - 0e3c277a by Ben Gamari at 2020-07-15T16:41:01-04:00 Bump Cabal submodule Updates a variety of tests as Cabal is now more strict about Cabal file form. - - - - - ceed994a by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Drop Windows Vista support, require Windows 7 - - - - - 00a23bfd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Update Windows FileSystem wrapper utilities. - - - - - 459e1c5f by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Use SlimReaderLocks and ConditonalVariables provided by the OS instead of emulated ones - - - - - 763088fc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Small linker comment and ifdef cleanups - - - - - 1a228ff9 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Flush event logs eagerly. - - - - - e9e04dda by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Refactor Buffer structures to be able to track async operations - - - - - 356dc3fe by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Implement new Console API - - - - - 90e69f77 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add IOPort synchronization primitive - - - - - 71245fcc by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add new io-manager cmdline options - - - - - d548a3b3 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Init Windows console Codepage to UTF-8. - - - - - 58ef6366 by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add unsafeSplat to GHC.Event.Array - - - - - d660725e by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Add size and iterate to GHC.Event.IntTable. - - - - - 050da6dd by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Switch Testsuite to test winio by default - - - - - 4bf542bf by Tamar Christina at 2020-07-15T16:41:01-04:00 winio: Multiple refactorings and support changes. - - - - - 4489af6b by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core threaded I/O manager - - - - - 64d8f2fe by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: core non-threaded I/O manager - - - - - 8da15a09 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix a scheduler bug with the threaded-runtime. - - - - - 84ea3d14 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Relaxing some constraints in io-manager. - - - - - ccf0d107 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Fix issues with non-threaded I/O manager after split. - - - - - b492fe6e by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Remove some barf statements that are a bit strict. - - - - - 01423fd2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Expand comments describing non-threaded loop - - - - - 4b69004f by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: fix FileSize unstat-able handles - - - - - 9b384270 by Tamar Christina at 2020-07-15T16:41:02-04:00 winio: Implement new tempfile routines for winio - - - - - f1e0be82 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix input truncation when reading from handle. This was caused by not upholding the read buffer invariant that bufR == bufL == 0 for empty read buffers. - - - - - e176b625 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix output truncation for writes larger than buffer size - - - - - a831ce0e by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Rewrite bufWrite. I think it's far easier to follow the code now. It's also correct now as I had still missed a spot where we didn't update the offset. - - - - - 6aefdf62 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix offset set by bufReadEmpty. bufReadEmpty returns the bytes read *including* content that was already buffered, But for calculating the offset we only care about the number of bytes read into the new buffer. - - - - - 750ebaee by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Clean up code surrounding IOPort primitives. According to phyx these should only be read and written once per object. Not neccesarily in that order. To strengthen that guarantee the primitives will now throw an exception if we violate this invariant. As a consequence we can eliminate some code from their primops. In particular code dealing with multiple queued readers/writers now simply checks the invariant and throws an exception if it was violated. That is in contrast to mvars which will do things like wake up all readers, queue multi writers etc. - - - - - ffd31db9 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix multi threaded threadDelay and a few other small changes. Multithreaded threadDelay suffered from a race condition based on the ioManagerStatus. Since the status isn't needed for WIO I removed it completely. This resulted in a light refactoring, as consequence we will always wake up the IO manager using interruptSystemManager, which uses `postQueuedCompletionStatus` internally. I also added a few comments which hopefully makes the code easier to dive into for the next person diving in. - - - - - 6ec26df2 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 wionio: Make IO subsystem check a no-op on non-windows platforms. - - - - - 29bcd936 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Set handle offset when opening files in Append mode. Otherwise we would truncate the file. - - - - - 55c29700 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Remove debug event log trace - - - - - 9acb9f40 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix sqrt and openFile009 test cases - - - - - 57017cb7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Allow hp2ps to build with -DDEBUG - - - - - b8cd9995 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update output of T9681 since we now actually run it. - - - - - 10af5b14 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: A few more improvements to the IOPort primitives. - - - - - 39afc4a7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix expected tempfiles output. Tempfiles now works properly on windows, as such we can delete the win32 specific output. - - - - - 99db46e0 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Assign thread labels to IOManager threads. - - - - - be6af732 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Properly check for the tso of an incall to be zero. - - - - - e2c6dac7 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark FD instances as unsupported under WINIO. - - - - - fd02ceed by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Fix threadDelay maxBound invocations. Instead of letting the ns timer overflow now clamp it at (maxBound :: Word64) ns. That still gives a few hundred years. - - - - - bc79f9f1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comments/cleanup an import in base - - - - - 1d197f4b by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Mark outstanding_service_requests volatile. As far as I know C(99) gives no guarantees for code like bool condition; ... while(condition) sleep(); that condition will be updated if it's changed by another thread. So we are explicit here and mark it as volatile, this will force a reload from memory on each iteration. - - - - - dc438186 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Make last_event a local variable - - - - - 2fc957c5 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add comment about thread safety of processCompletion. - - - - - 4c026b6c by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: nonthreaded: Create io processing threads in main thread. We now set a flag in the IO thread. The scheduler when looking for work will check the flag and create/queue threads accordingly. We used to create these in the IO thread. This improved performance but caused frequent segfaults. Thread creation/allocation is only safe to do if nothing currently accesses the storeagemanager. However without locks in the non-threaded runtime this can't be guaranteed. This shouldn't change performance all too much. In the past we had: * IO: Create/Queue thread. * Scheduler: Runs a few times. Eventually picks up IO processing thread. Now it's: * IO: Set flag to queue thread. * Scheduler: Pick up flag, if set create/queue thread. Eventually picks up IO processing thread. - - - - - f47c7208 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Add an exported isHeapAlloced function to the RTS - - - - - cc5d7bb1 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Queue IO processing threads at the front of the queue. This will unblock the IO thread sooner hopefully leading to higher throughput in some situations. - - - - - e7630115 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: ThreadDelay001: Use higher resolution timer. - - - - - 451b5f96 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Update T9681 output, disable T4808 on windows. T4808 tests functionality of the FD interface which won't be supported under WINIO. T9681 just has it's expected output tweaked. - - - - - dd06f930 by Andreas Klebinger at 2020-07-15T16:41:02-04:00 winio: Wake io manager once per registerTimeout. Which is implicitly done in editTimeouts, so need to wake it up twice. - - - - - e87d0bf9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update placeholder comment with actual function name. - - - - - fc9025db by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Always lock win32 event queue - - - - - c24c9a1f by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Display thread labels when tracing scheduler events. - - - - - 06542b03 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Refactor non-threaded runner thread and scheduler interface. Only use a single communication point (registerAlertableWait) to inform the C side aobut both timeouts to use as well as outstanding requests. Also queue a haskell processing thread after each return from alertable waits. This way there is no risk of us missing a timer event. - - - - - 256299b1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove outstanding_requests from runner. We used a variable to keep track of situations where we got entries from the IO port, but all of them had already been canceled. While we can avoid some work that way this case seems quite rare. So we give up on tracking this and instead always assume at least one of the returned entries is valid. If that's not the case no harm is done, we just perform some additional work. But it makes the runner easier to reason about. In particular we don't need to care if another thread modifies oustanding_requests after we return from waiting on the IO Port. - - - - - 3ebd8ad9 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Various fixes related to rebase and testdriver - - - - - 6be6bcba by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: Fix rebase artifacts - - - - - 2c649dc3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename unsafeSplat to unsafeCopyFromBuffer - - - - - a18b73f3 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove unused size/iterate operations from IntTable - - - - - 16bab48e by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Detect running IO Backend via peeking at RtsConfig - - - - - 8b8405a0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update temp path so GCC etc can handle it. Also fix PIPE support, clean up error casting, fix memory leaks - - - - - 2092bc54 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Minor comments/renamings - - - - - a5b5b6c0 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Checking if an error code indicates completion is now a function. - - - - - 362176fd by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Small refactor in withOverlappedEx - - - - - 32e20597 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: A few comments and commented out dbxIO - - - - - a4bfc1d9 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't drop buffer offset in byteView/cwcharView - - - - - b3ad2a54 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: revert BHandle changes. - - - - - 3dcd87e2 by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Fix imports - - - - - 5a371890 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: update ghc-cabal to handle new Cabal submodule bump - - - - - d07ebe0d by Ben Gamari at 2020-07-15T16:41:03-04:00 winio: Only compile sources on Windows - - - - - dcb42393 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Actually return Nothing on EOF for non-blocking read - - - - - 895a3beb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate logic in encodeMultiByte[Raw]IO. - - - - - e06e6734 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Deduplicate openFile logic - - - - - b59430c0 by Tamar Christina at 2020-07-15T16:41:03-04:00 winio: fix -werror issue in encoding file - - - - - f8d39a51 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Don't mention windows specific functions when building on Linux. - - - - - 6a533d2a by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add a note about file locking in the RTS. - - - - - cf37ce34 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Add version to @since annotation - - - - - 0fafa2eb by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename GHC.Conc.IOCP -> GHC.Conc.WinIO - - - - - 1854fc23 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Expand GHC.Conc.POSIX description It now explains users may not use these functions when using the old IO manager. - - - - - fcc7ba41 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Fix potential spaceleak in __createUUIDTempFileErrNo - - - - - 6b3fd9fa by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant -Wno-missing-signatures pragmas - - - - - 916fc861 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Make it explicit that we only create one IO manager - - - - - f260a721 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Note why we don't use blocking waits. - - - - - aa0a4bbf by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove commented out pragma - - - - - d679b544 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Remove redundant buffer write in Handle/Text.hs:bufReadEmpty - - - - - d3f94368 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Rename SmartHandles to StdHandles - - - - - bd6b8ec1 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: add comment stating failure behaviour for getUniqueFileInfo. - - - - - 12846b85 by Andreas Klebinger at 2020-07-15T16:41:03-04:00 winio: Update IOPort haddocks. - - - - - 9f39fb14 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Add a note cross reference - - - - - 62dd5a73 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Name Haskell/OS I/O Manager explicitly in Note - - - - - fa807828 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Expand BlockedOnIOCompletion description. - - - - - f0880a1d by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove historical todos - - - - - 8e58e714 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Update note, remove debugging pragma. - - - - - aa4d84d5 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: flushCharReadBuffer shouldn't need to adjust offsets. - - - - - e580893a by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Remove obsolete comment about cond. variables - - - - - d54e9d79 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix initial linux validate build - - - - - 3cd4de46 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix ThreadDelay001 CPP - - - - - c88b1b9f by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix openFile009 merge conflict leftover - - - - - 849e8889 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept T9681 output. GHC now reports String instead of [Char]. - - - - - e7701818 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix cabal006 after upgrading cabal submodule Demand cabal 2.0 syntax instead of >= 1.20 as required by newer cabal versions. - - - - - a44f0373 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Fix stderr output for ghci/linking/dyn tests. We used to filter rtsopts, i opted to instead just accept the warning of it having no effect. This works both for -rtsopts, as well as -with-rtsopts which winio adds. - - - - - 515d9896 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T15261b stdout for --io-manager flag. - - - - - 949aaacc by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Adjust T5435_dyn_asm stderr The warning about rtsopts having no consequences is expected. So accept new stderr. - - - - - 7d424e1e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Also accept T7037 stderr - - - - - 1f009768 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal04 by filtering rts args - - - - - 981a9f2e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix cabal01 by accepting expected stderr - - - - - b7b0464e by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix safePkg01 by accepting expected stderr - - - - - 32734b29 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix T5435_dyn_gcc by accepting expected stderr - - - - - acc5cebf by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: fix tempfiles test on linux - - - - - c577b789 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for T3807 - - - - - c108c527 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload - - - - - 2b0b9a08 by Andreas Klebinger at 2020-07-15T16:41:04-04:00 winio: Accept accepted stderr for linker_unload_multiple_objs - - - - - 67afb03c by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify wording on conditional variables. - - - - - 3bd41572 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: clarify comment on cooked mode. - - - - - ded58a03 by Tamar Christina at 2020-07-15T16:41:04-04:00 winio: update lockfile signature and remove mistaken symbol in rts. - - - - - 2143c492 by Ben Gamari at 2020-07-15T16:41:04-04:00 testsuite: Add winio and winio_threaded ways Reverts many of the testsuite changes - - - - - c0979cc5 by Ben Gamari at 2020-07-16T10:56:54-04:00 Merge remote-tracking branch 'origin/wip/winio' - - - - - 750a1595 by Ben Gamari at 2020-07-18T07:26:41-04:00 rts: Add --copying-gc flag to reverse effect of --nonmoving-gc Fixes #18281. - - - - - 6ba6a881 by Hécate at 2020-07-18T07:26:42-04:00 Implement `fullCompilerVersion` Follow-up of https://gitlab.haskell.org/ghc/ghc/-/issues/18403 This MR adds `fullCompilerVersion`, a function that shares the same backend as the `--numeric-version` GHC flag, exposing a full, three-digit version datatype. - - - - - e6cf27df by Hécate at 2020-07-18T07:26:43-04:00 Add a Lint hadrian rule and an .hlint.yaml file in base/ - - - - - bcb177dd by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Allow multiple case branches to have a higher rank type As #18412 points out, it should be OK for multiple case alternatives to have a higher rank type, provided they are all the same. This patch implements that change. It sweeps away GHC.Tc.Gen.Match.tauifyMultipleBranches, and friends, replacing it with an enhanced version of fillInferResult. The basic change to fillInferResult is to permit the case in which another case alternative has already filled in the result; and in that case simply unify. It's very simple actually. See the new Note [fillInferResult] in TcMType Other refactoring: - Move all the InferResult code to one place, in GHC.Tc.Utils.TcMType (previously some of it was in Unify) - Move tcInstType and friends from TcMType to Instantiate, where it more properly belongs. (TCMType was getting very long.) - - - - - e5525a51 by Simon Peyton Jones at 2020-07-18T07:26:43-04:00 Improve typechecking of NPlusK patterns This patch (due to Richard Eisenberg) improves documentation of the wrapper returned by tcSubMult (see Note [Wrapper returned from tcSubMult] in GHC.Tc.Utils.Unify). And, more substantially, it cleans up the multiplicity handling in the typechecking of NPlusKPat - - - - - 12f90352 by Krzysztof Gogolewski at 2020-07-18T07:26:45-04:00 Remove {-# CORE #-} pragma (part of #18048) This pragma has no effect since 2011. It was introduced for External Core, which no longer exists. Updates haddock submodule. - - - - - e504c913 by Simon Peyton Jones at 2020-07-18T07:26:45-04:00 Refactor the simplification of join binders This MR (for #18449) refactors the Simplifier's treatment of join-point binders. Specifically, it puts together, into GHC.Core.Opt.Simplify.Env.adjustJoinPointType two currently-separate ways in which we adjust the type of a join point. As the comment says: -- (adjustJoinPointType mult new_res_ty join_id) does two things: -- -- 1. Set the return type of the join_id to new_res_ty -- See Note [Return type for join points] -- -- 2. Adjust the multiplicity of arrows in join_id's type, as -- directed by 'mult'. See Note [Scaling join point arguments] I think this actually fixes a latent bug, by ensuring that the seIdSubst and seInScope have the right multiplicity on the type of join points. I did some tidying up while I was at it. No more setJoinResTy, or modifyJoinResTy: instead it's done locally in Simplify.Env.adjustJoinPointType - - - - - 49b265f0 by Chaitanya Koparkar at 2020-07-18T07:26:46-04:00 Fix minor typos in a Core.hs note - - - - - 8d59aed6 by Stefan Schulze Frielinghaus at 2020-07-18T07:26:47-04:00 GHCi: Fix isLittleEndian - - - - - c26e81d1 by Ben Gamari at 2020-07-18T07:26:47-04:00 testsuite: Mark ghci tests as fragile under unreg compiler In particular I have seen T16012 fail repeatedly under the unregisterised compiler. - - - - - 868e4523 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "AArch32 symbols only on aarch32." This reverts commit cdfeb3f24f76e8fd30452016676e56fbc827789a. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - c915ba84 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "Fix (1)" This reverts commit 7abffced01f5680efafe44f6be2733eab321b039. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 777c452a by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "better if guards." This reverts commit 3f60b94de1f460ca3f689152860b108a19ce193e. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 0dd40552 by Moritz Angermann at 2020-07-20T04:30:38-04:00 Revert "[linker/rtsSymbols] More linker symbols" This reverts commit 686e72253aed3880268dd6858eadd8c320f09e97. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 30caeee7 by Sylvain Henry at 2020-07-21T06:39:33-04:00 DynFlags: remove use of sdocWithDynFlags from GHC.Stg.* (#17957) * add StgPprOpts datatype * remove Outputable instances for types that need `StgPprOpts` to be pretty-printed and explicitly call type specific ppr functions * add default `panicStgPprOpts` for panic messages (when it's not convenient to thread StgPprOpts or DynFlags down to the ppr function call) - - - - - 863c544c by Mark at 2020-07-21T06:39:34-04:00 Fix a typo in existential_quantification.rst - - - - - 05910be1 by Krzysztof Gogolewski at 2020-07-21T14:47:07-04:00 Add release notes entry for #17816 [skip ci] - - - - - a6257192 by Matthew Pickering at 2020-07-21T14:47:19-04:00 Use a newtype `Code` for the return type of typed quotations (Proposal #195) There are three problems with the current API: 1. It is hard to properly write instances for ``Quote m => m (TExp a)`` as the type is the composition of two type constructors. Doing so in your program involves making your own newtype and doing a lot of wrapping/unwrapping. For example, if I want to create a language which I can either run immediately or generate code from I could write the following with the new API. :: class Lang r where _int :: Int -> r Int _if :: r Bool -> r a -> r a -> r a instance Lang Identity where _int = Identity _if (Identity b) (Identity t) (Identity f) = Identity (if b then t else f) instance Quote m => Lang (Code m) where _int = liftTyped _if cb ct cf = [|| if $$cb then $$ct else $$cf ||] 2. When doing code generation it is common to want to store code fragments in a map. When doing typed code generation, these code fragments contain a type index so it is desirable to store them in one of the parameterised map data types such as ``DMap`` from ``dependent-map`` or ``MapF`` from ``parameterized-utils``. :: compiler :: Env -> AST a -> Code Q a data AST a where ... data Ident a = ... type Env = MapF Ident (Code Q) newtype Code m a = Code (m (TExp a)) In this example, the ``MapF`` maps an ``Ident String`` directly to a ``Code Q String``. Using one of these map types currently requires creating your own newtype and constantly wrapping every quotation and unwrapping it when using a splice. Achievable, but it creates even more syntactic noise than normal metaprogramming. 3. ``m (TExp a)`` is ugly to read and write, understanding ``Code m a`` is easier. This is a weak reason but one everyone can surely agree with. Updates text submodule. - - - - - 58235d46 by Ben Gamari at 2020-07-21T14:47:28-04:00 users-guide: Fix :rts-flag:`--copying-gc` documentation It was missing a newline. - - - - - 19e80b9a by Vladislav Zavialov at 2020-07-21T14:50:01-04:00 Accumulate Haddock comments in P (#17544, #17561, #8944) Haddock comments are, first and foremost, comments. It's very annoying to incorporate them into the grammar. We can take advantage of an important property: adding a Haddock comment does not change the parse tree in any way other than wrapping some nodes in HsDocTy and the like (and if it does, that's a bug). This patch implements the following: * Accumulate Haddock comments with their locations in the P monad. This is handled in the lexer. * After parsing, do a pass over the AST to associate Haddock comments with AST nodes using location info. * Report the leftover comments to the user as a warning (-Winvalid-haddock). - - - - - 4c719460 by David Binder at 2020-07-22T20:17:35-04:00 Fix dead link to haskell prime discussion - - - - - f2f817e4 by BinderDavid at 2020-07-22T20:17:35-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 0bf8980e by Daniel Gröber at 2020-07-22T20:18:11-04:00 Remove length field from FastString - - - - - 1010c33b by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 8336ba78 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - 7484a9a4 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - 5536ed28 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 5b8902e3 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - 5976a161 by Daniel Gröber at 2020-07-22T20:18:11-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 9ddf1614 by Daniel Gröber at 2020-07-22T20:18:11-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - e9491668 by Ben Gamari at 2020-07-22T20:18:46-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 9f3ff8fd by Andreas Klebinger at 2020-07-22T20:19:22-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - 0f17b930 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - bab4ec8f by Sylvain Henry at 2020-07-22T20:19:59-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - 8ea33edb by Sylvain Henry at 2020-07-22T20:19:59-04:00 Remove unused sGhcWithNativeCodeGen - - - - - e079bb72 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - 735f9d6b by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - f7cc4313 by Sylvain Henry at 2020-07-22T20:19:59-04:00 Replace HscTarget with Backend They both have the same role and Backend name is more explicit. Metric Decrease: T3064 Update Haddock submodule - - - - - 15ce1804 by Andreas Klebinger at 2020-07-22T20:20:34-04:00 Deprecate -fdmd-tx-dict-sel. It's behaviour is now unconditionally enabled as it's slightly beneficial. There are almost no benchmarks which benefit from disabling it, so it's not worth the keep this configurable. This fixes #18429. - - - - - ff1b7710 by Sylvain Henry at 2020-07-22T20:21:11-04:00 Add test for #18064 It has been fixed by 0effc57d48ace6b719a9f4cbeac67c95ad55010b - - - - - cfa89149 by Krzysztof Gogolewski at 2020-07-22T20:21:48-04:00 Define type Void# = (# #) (#18441) There's one backwards compatibility issue: GHC.Prim no longer exports Void#, we now manually re-export it from GHC.Exts. - - - - - 02f40b0d by Sebastian Graf at 2020-07-22T20:22:23-04:00 Add regression test for #18478 !3392 backported !2993 to GHC 8.10.2 which most probably is responsible for fixing #18478, which triggered a pattern match checker performance regression in GHC 8.10.1 as first observed in #17977. - - - - - 7f44df1e by Sylvain Henry at 2020-07-22T20:23:00-04:00 Minor refactoring of Unit display * for consistency, try to always use UnitPprInfo to display units to users * remove some uses of `unitPackageIdString` as it doesn't show the component name and it uses String - - - - - dff1cb3d by Moritz Angermann at 2020-07-23T07:55:29-04:00 [linker] Fix out of range relocations. mmap may return address all over the place. mmap_next will ensure we get the next free page after the requested address. This is especially important for linking on aarch64, where the memory model with PIC admits relocations in the +-4GB range, and as such we can't work with arbitrary object locations in memory. Of note: we map the rts into process space, so any mapped objects must not be ouside of the 4GB from the processes address space. - - - - - cdd0ff16 by Tamar Christina at 2020-07-24T18:12:23-04:00 winio: restore console cp on exit - - - - - c1f4f81d by Tamar Christina at 2020-07-24T18:13:00-04:00 winio: change memory allocation strategy and fix double free errors. - - - - - ba205046 by Simon Peyton Jones at 2020-07-24T18:13:35-04:00 Care with occCheckExpand in kind of occurrences Issue #18451 showed that we could get an infinite type, through over-use of occCheckExpand in the kind of an /occurrence/ of a type variable. See Note [Occurrence checking: look inside kinds] in GHC.Core.Type This patch fixes the problem by making occCheckExpand less eager to expand synonyms in kinds. It also improves pretty printing of kinds, by *not* suppressing the kind on a tyvar-binder like (a :: Const Type b) where type Const p q = p. Even though the kind of 'a' is Type, we don't want to suppress the kind ascription. Example: the error message for polykinds/T18451{a,b}. See GHC.Core.TyCo.Ppr Note [Suppressing * kinds]. - - - - - 02133353 by Zubin Duggal at 2020-07-25T00:44:30-04:00 Simplify XRec definition Change `Located X` usage to `XRec pass X` This increases the scope of the LPat experiment to almost all of GHC. Introduce UnXRec and MapXRec classes Fixes #17587 and #18408 Updates haddock submodule Co-authored-by: Philipp Krüger <philipp.krueger1 at gmail.com> - - - - - e443846b by Sylvain Henry at 2020-07-25T00:45:07-04:00 DynFlags: store printer in TraceBinIfaceReading We don't need to pass the whole DynFlags, just pass the logging function, if any. - - - - - 15b2b44f by Sylvain Henry at 2020-07-25T00:45:08-04:00 Rename GHC.Driver.Ways into GHC.Platform.Ways - - - - - 342a01af by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add GHC.Platform.Profile - - - - - 6333d739 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Put PlatformConstants into Platform - - - - - 9dfeca6c by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove platform constant wrappers Platform constant wrappers took a DynFlags parameter, hence implicitly used the target platform constants. We removed them to allow support for several platforms at once (#14335) and to avoid having to pass the full DynFlags to every function (#17957). Metric Decrease: T4801 - - - - - 73145d57 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Remove dead code in utils/derivConstants - - - - - 7721b923 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Move GHC.Platform into the compiler Previously it was in ghc-boot so that ghc-pkg could use it. However it wasn't necessary because ghc-pkg only uses a subset of it: reading target arch and OS from the settings file. This is now done via GHC.Platform.ArchOS (was called PlatformMini before). - - - - - 459afeb5 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Fix build systems - - - - - 9e2930c3 by Sylvain Henry at 2020-07-25T00:45:08-04:00 Bump CountParserDeps - - - - - 6e2db34b by Sylvain Henry at 2020-07-25T00:45:08-04:00 Add accessors to ArchOS - - - - - fc0f6fbc by Stefan Schulze Frielinghaus at 2020-07-25T00:45:45-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 - - - - - a7c4439a by Matthias Andreas Benkard at 2020-07-26T13:23:24-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - da7269a4 by Ben Gamari at 2020-07-26T13:23:59-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. - - - - - f153a1d0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Update win32 output for parseTree - - - - - e91672f0 by Ben Gamari at 2020-07-26T13:23:59-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. - - - - - 9cbfe086 by Ben Gamari at 2020-07-26T13:23:59-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. - - - - - 8236925f by Tamar Christina at 2020-07-26T13:24:35-04:00 winio: remove dead argument to stg_newIOPortzh - - - - - ce0a1d67 by Tamar Christina at 2020-07-26T13:25:11-04:00 winio: fix detection of tty terminals - - - - - 52685cf7 by Tamar Christina at 2020-07-26T13:25:48-04:00 winio: update codeowners - - - - - aee45d9e by Vladislav Zavialov at 2020-07-27T07:06:56-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. - - - - - 667ab69e by leiftw at 2020-07-27T07:07:32-04:00 fix typo referring to non-existent `-ohidir` flag, should be `-hidir` I think - - - - - 6ff89c17 by Vladislav Zavialov at 2020-07-27T07:08:07-04:00 Refactor the parser a little * Create a dedicated production for type operators * Create a dedicated type for the UNPACK pragma * Remove an outdated part of Note [Parsing data constructors is hard] - - - - - aa054d32 by Ben Gamari at 2020-07-27T20:09:07-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. - - - - - 6da73bbf by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Add minimal test for #12492 - - - - - 47680cb7 by Michalis Pardalos at 2020-07-27T20:09:44-04:00 Use allocate, not ALLOC_PRIM_P for unpackClosure# ALLOC_PRIM_P fails for large closures, by directly using allocate we can handle closures which are larger than the block size. Fixes #12492 - - - - - 3d345c96 by Simon Peyton Jones at 2020-07-27T20:10:19-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 - - - - - 57aca6bb by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. - - - - - 0a815cea by Ben Gamari at 2020-07-27T20:10:54-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. - - - - - 0bd60059 by Simon Peyton Jones at 2020-07-28T02:01:49-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 - - - - - 6ee07b49 by Sylvain Henry at 2020-07-28T02:02:27-04:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - f305bbfd by Peter Trommler at 2020-07-28T02:03:02-04:00 config: Fix Haskell platform constructor w/ params Fixes #18505 - - - - - 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - 3dd29496 by Ben Gamari at 2020-11-10T16:25:01-05:00 Notes from call - - - - - 0d67d728 by Ben Gamari at 2020-11-10T16:25:01-05:00 Shortcut mkTvSubstPrs on empty list Surprisingly enough this reduces compilation time on Cabal by nearly 1%. - - - - - c84636c9 by Ben Gamari at 2020-11-10T16:25:01-05:00 Shortcut coreView - - - - - 2fa58a71 by Ben Gamari at 2020-11-10T16:25:40-05:00 expandSynTyCon_maybe: Special-case nullary tycons This avoids both allocation and some instructions. - - - - - 41a1178d by Ben Gamari at 2020-11-10T16:25:40-05:00 Optimise tcView - - - - - bd87df89 by Ben Gamari at 2020-11-10T16:25:40-05:00 Inline expandSynTyCon_maybe This is necessary to avoid some needless allocation since we currently lack nested CPR on sums. Metric Decrease: T12227 T12545 T12707 T14683 T3064 T5631 T5642 T9020 T9872a - - - - - 72756a7d by Ben Gamari at 2020-11-10T16:30:41-05:00 Some cleanup - - - - - 7d611567 by Ben Gamari at 2020-11-10T16:31:12-05:00 hi Metric Decrease: T13035 haddock.Cabal haddock.base Metric Increase: T9872c - - - - - f0b1b84a by Ben Gamari at 2020-11-10T16:34:18-05:00 Fix it - - - - - 17 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - .gitlab/test-metrics.sh - .gitmodules - CODEOWNERS - Makefile - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Builtin/RebindableNames.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7951df0db45713b316de80b12509babaea73d9af...f0b1b84ac5423339c6b6c40c6ac4c454f486a6af -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7951df0db45713b316de80b12509babaea73d9af...f0b1b84ac5423339c6b6c40c6ac4c454f486a6af 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 Tue Nov 10 22:23:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 17:23:25 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Fix it Message-ID: <5fab12ddb9e18_10ee3ffbadb16b681283723@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: e0c03f29 by Ben Gamari at 2020-11-10T17:23:11-05:00 Fix it - - - - - 4 changed files: - compiler/GHC/Builtin/Types/Prim.hs - + compiler/GHC/Builtin/Types/Prim.hs-boot - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -551,37 +551,6 @@ mkPrimTcName built_in_syntax occ key tycon = mkWiredInName gHC_PRIM (mkTcOccFS occ) key (mkATyCon tycon) built_in_syntax ----------------------------- --- | Given a RuntimeRep, applies TYPE to it. --- see Note [TYPE and RuntimeRep] -tYPE :: Type -> Type -tYPE (TyConApp tc []) - | tc `hasKey` liftedRepDataConKey = liftedTypeKind -- TYPE 'LiftedPtrRep -tYPE rr = TyConApp tYPETyCon [rr] - --- Note [Prefer Type over TYPE 'LiftedPtrRep] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ --- --- The Core of nearly any program will have numerous occurrences of --- @TYPE 'LiftedPtrRep@ floating about. Consequently, we try hard to ensure --- that operations on such types are efficient: --- --- * Instead of representing the lifted kind as --- @TyConApp tYPETyCon [liftedRepDataCon]@ we rather prefer to --- use the 'GHC.Types.Type' type synonym (available in GHC as --- 'TysPrim.liftedTypeKind'). Note only is this a smaller AST but it also --- guarantees sharing on the heap. --- --- * To avoid allocating 'TyConApp' constructors 'TysPrim.tYPE' --- catches the lifted case and uses `liftedTypeKind` instead of building an --- application. --- --- * Similarly, 'Type.mkTyConApp' catches applications of TYPE and --- handles them using 'TysPrim.tYPE', ensuring that it benefits from the --- optimisation described above. --- --- * Since 'liftedTypeKind' is a nullary type synonym application, --- it benefits from the optimisation described in Note [Comparing nullary --- type synonyms] in "GHC.Core.Type". -- Given a Multiplicity, applies FUN to it. functionWithMultiplicity :: Type -> Type ===================================== compiler/GHC/Builtin/Types/Prim.hs-boot ===================================== @@ -0,0 +1,5 @@ +module GHC.Builtin.Types.Prim where + +import GHC.Core.TyCon + +tYPETyCon :: TyCon ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -52,6 +52,7 @@ module GHC.Core.TyCo.Rep ( mkVisFunTyMany, mkVisFunTysMany, mkInvisFunTyMany, mkInvisFunTysMany, mkTyConApp, + tYPE, -- * Functions over binders TyCoBinder(..), TyCoVarBinder, TyBinder, @@ -90,8 +91,9 @@ import GHC.Core.TyCon import GHC.Core.Coercion.Axiom -- others -import GHC.Builtin.Names ( liftedTypeKindTyConKey, manyDataConKey ) -import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, manyDataConTy ) +import GHC.Builtin.Names ( liftedTypeKindTyConKey, liftedRepDataConKey, manyDataConKey, tYPETyConKey ) +import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, liftedTypeKind, manyDataConTy ) +import {-# SOURCE #-} GHC.Builtin.Types.Prim ( tYPETyCon ) import GHC.Types.Basic ( LeftOrRight(..), pickLR ) import GHC.Types.Unique ( hasKey ) import GHC.Utils.Outputable @@ -1018,14 +1020,46 @@ mkTyConApp tycon tys -- avoid reboxing every time `mkTyConApp` is called. = ASSERT2( null tys, ppr tycon $$ ppr tys ) manyDataConTy - -- See Note [Prefer Type over TYPE 'LiftedPtrRep] in GHC.BuiltIn.Types.Prim. - | tycon == tYPETyCon + -- See Note [Prefer Type over TYPE 'LiftedPtrRep]. + | tycon `hasKey` tYPETyConKey , [rep] <- tys = tYPE rep -- The catch-all case | otherwise = TyConApp tycon tys +-- Note [Prefer Type over TYPE 'LiftedPtrRep] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- The Core of nearly any program will have numerous occurrences of +-- @TYPE 'LiftedPtrRep@ floating about. Consequently, we try hard to ensure +-- that operations on such types are efficient: +-- +-- * Instead of representing the lifted kind as +-- @TyConApp tYPETyCon [liftedRepDataCon]@ we rather prefer to +-- use the 'GHC.Types.Type' type synonym (available in GHC as +-- 'TysPrim.liftedTypeKind'). Note only is this a smaller AST but it also +-- guarantees sharing on the heap. +-- +-- * To avoid allocating 'TyConApp' constructors 'TysPrim.tYPE' +-- catches the lifted case and uses `liftedTypeKind` instead of building an +-- application. +-- +-- * Similarly, 'Type.mkTyConApp' catches applications of TYPE and +-- handles them using 'TysPrim.tYPE', ensuring that it benefits from the +-- optimisation described above. +-- +-- * Since 'liftedTypeKind' is a nullary type synonym application, +-- it benefits from the optimisation described in Note [Comparing nullary +-- type synonyms] in "GHC.Core.Type". + +-- | Given a RuntimeRep, applies TYPE to it. +-- see Note [TYPE and RuntimeRep] +tYPE :: Type -> Type +tYPE (TyConApp tc []) + | tc `hasKey` liftedRepDataConKey = liftedTypeKind -- TYPE 'LiftedPtrRep +tYPE rr = TyConApp tYPETyCon [rr] + -- This is a single, global definition of the type `Type` -- Defined here so it is only allocated once. -- See Note [mkTyConApp and Type] ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -120,7 +120,6 @@ import GHC.Types.Id as Id import GHC.Types.Name import GHC.Types.Var.Set import GHC.Builtin.Types -import GHC.Builtin.Types.Prim import GHC.Types.Var.Env import GHC.Types.Name.Env import GHC.Utils.Misc View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0c03f29343f2920991b0c8b28d9e9fac3bf6979 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0c03f29343f2920991b0c8b28d9e9fac3bf6979 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 Tue Nov 10 23:07:20 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Tue, 10 Nov 2020 18:07:20 -0500 Subject: [Git][ghc/ghc][wip/T18914] Use HsOuterExplicit in instance sigs in deriving-generated code Message-ID: <5fab1d28a018a_10ee7ca009c12867c5@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: 22458bc9 by Ryan Scott at 2020-11-10T18:06:33-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). I also made `HsCoreTy` a type synonym instead of a newtype, as making it a distinct data type wasn't buying us much. * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - 10 changed files: - compiler/GHC/Hs/Type.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/deriving/should_compile/T14578.stderr - + testsuite/tests/deriving/should_compile/T18914.hs - testsuite/tests/deriving/should_compile/all.T - utils/haddock Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -24,7 +24,7 @@ module GHC.Hs.Type ( HsArrow(..), arrowToHsType, hsLinear, hsUnrestricted, isUnrestricted, - HsType(..), NewHsTypeX(..), LHsType, HsKind, LHsKind, + HsType(..), HsCoreTy, LHsType, HsKind, LHsKind, HsForAllTelescope(..), HsTyVarBndr(..), LHsTyVarBndr, LHsQTyVars(..), HsOuterTyVarBndrs(..), HsOuterFamEqnTyVarBndrs, HsOuterSigTyVarBndrs, @@ -1039,12 +1039,6 @@ data HsType pass -- For details on above see note [Api annotations] in GHC.Parser.Annotation - -- | HsCoreTy (XCoreTy pass) Type -- An escape hatch for tunnelling a *closed* - -- -- Core Type through HsSyn. - -- -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - - -- For details on above see note [Api annotations] in GHC.Parser.Annotation - | HsExplicitListTy -- A promoted explicit list (XExplicitListTy pass) PromotionFlag -- whether explicitly promoted, for pretty printer @@ -1077,16 +1071,13 @@ data HsType pass | XHsType (XXType pass) -data NewHsTypeX - = NHsCoreTy Type -- An escape hatch for tunnelling a *closed* - -- Core Type through HsSyn. - -- See also Note [Typechecking NHsCoreTys] in - -- GHC.Tc.Gen.HsType. - deriving Data - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -instance Outputable NewHsTypeX where - ppr (NHsCoreTy ty) = ppr ty +-- An escape hatch for tunnelling a Core 'Type' through 'HsType'. +-- For more details on how this works, see: +-- +-- * @Note [Renaming HsCoreTys]@ in "GHC.Rename.HsType" +-- +-- * @Note [Typechecking HsCoreTys]@ in "GHC.Tc.Gen.HsType" +type HsCoreTy = Type type instance XForAllTy (GhcPass _) = NoExtField type instance XQualTy (GhcPass _) = NoExtField @@ -1124,7 +1115,7 @@ type instance XTyLit (GhcPass _) = NoExtField type instance XWildCardTy (GhcPass _) = NoExtField -type instance XXType (GhcPass _) = NewHsTypeX +type instance XXType (GhcPass _) = HsCoreTy -- Note [Literal source text] in GHC.Types.Basic for SourceText fields in @@ -2250,7 +2241,7 @@ hsTypeNeedsParens p = go_hs_ty go_hs_ty (HsOpTy{}) = p >= opPrec go_hs_ty (HsParTy{}) = False go_hs_ty (HsDocTy _ (L _ t) _) = go_hs_ty t - go_hs_ty (XHsType (NHsCoreTy ty)) = go_core_ty ty + go_hs_ty (XHsType ty) = go_core_ty ty go_core_ty (TyVarTy{}) = False go_core_ty (AppTy{}) = p >= appPrec ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -39,6 +39,7 @@ import GHC.Prelude import {-# SOURCE #-} GHC.Rename.Splice( rnSpliceType ) +import GHC.Core.TyCo.FVs ( tyCoVarsOfTypeList ) import GHC.Driver.Session import GHC.Hs import GHC.Rename.Env @@ -48,6 +49,7 @@ import GHC.Rename.Utils ( HsDocContext(..), inHsDocContext, withHsDocContext , checkShadowedRdrNames ) import GHC.Rename.Fixity ( lookupFieldFixityRn, lookupFixityRn , lookupTyFixityRn ) +import GHC.Rename.Unbound ( notInScopeErr ) import GHC.Tc.Utils.Monad import GHC.Types.Name.Reader import GHC.Builtin.Names @@ -634,10 +636,20 @@ rnHsTyKi env (HsDocTy _ ty haddock_doc) = do { (ty', fvs) <- rnLHsTyKi env ty ; return (HsDocTy noExtField ty' haddock_doc, fvs) } -rnHsTyKi _ (XHsType (NHsCoreTy ty)) - = return (XHsType (NHsCoreTy ty), emptyFVs) - -- The emptyFVs probably isn't quite right - -- but I don't think it matters +-- See Note [Renaming HsCoreTys] +rnHsTyKi env (XHsType ty) + = do mapM_ (check_in_scope . nameRdrName) fvs_list + return (XHsType ty, fvs) + where + fvs_list = map getName $ tyCoVarsOfTypeList ty + fvs = mkFVs fvs_list + + check_in_scope :: RdrName -> RnM () + check_in_scope rdr_name = do + mb_name <- lookupLocalOccRn_maybe rdr_name + when (isNothing mb_name) $ + addErr $ withHsDocContext (rtke_ctxt env) $ + notInScopeErr rdr_name rnHsTyKi env ty@(HsExplicitListTy _ ip tys) = do { data_kinds <- xoptM LangExt.DataKinds @@ -661,6 +673,39 @@ rnHsArrow _env (HsLinearArrow u) = return (HsLinearArrow u, emptyFVs) rnHsArrow env (HsExplicitMult u p) = (\(mult, fvs) -> (HsExplicitMult u mult, fvs)) <$> rnLHsTyKi env p +{- +Note [Renaming HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to rename an HsCoreTy, +since it's already been renamed to some extent. However, in an attempt to +detect ill-formed HsCoreTys, the renamer checks to see if all free type +variables in an HsCoreTy are in scope. To see why this can matter, consider +this example from #18914: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +Because of #18914, a previous GHC would generate the following code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) -- The type within @(...) is an HsCoreTy + @(N f a) -- So is this + (m @f) + +There are two HsCoreTys in play—(f a) and (N f a)—both of which have +`f` and `a` as free type variables. The `f` is in scope from the instance head, +but `a` is completely unbound, which is what led to #18914. To avoid this sort +of mistake going forward, the renamer will now detect that `a` is unbound and +throw an error accordingly. +-} + -------------- rnTyVar :: RnTyKiEnv -> RdrName -> RnM Name rnTyVar env rdr_name ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1819,6 +1819,94 @@ a truly higher-rank type like so: Then the same situation will arise again. But at least it won't arise for the common case of methods with ordinary, prenex-quantified types. +----- +-- Wrinkle: Use HsOuterExplicit +----- + +One minor complication with the plan above is that we need to ensure that the +type variables from a method's instance signature properly scope over the body +of the method. For example, recall: + + instance (C m, forall p q. Coercible p q => Coercible (m p) (m q)) => + C (T m) where + join :: forall a. T m (T m a) -> T m a + join = coerce @( m (m a) -> m a) + @(T m (T m a) -> T m a) + join + +In the example above, it is imperative that the `a` in the instance signature +for `join` scope over the body of `join` by way of ScopedTypeVariables. +This might sound obvious, but note that in gen_Newtype_binds, which is +responsible for generating the code above, the type in `join`'s instance +signature is given as a Core type, whereas gen_Newtype_binds will eventually +produce HsBinds (i.e., source Haskell) that is renamed and typechecked. We +must ensure that `a` is in scope over the body of `join` during renaming +or else the generated code will be rejected. + +In short, we need to convert the instance signature from a Core type to an +HsType (i.e., a source Haskell type). Two possible options are: + +1. Convert the Core type entirely to an HsType (i.e., a source Haskell type). +2. Embed the entire Core type using HsCoreTy. + +Neither option is quite satisfactory: + +1. Converting a Core type to an HsType in full generality is surprisingly + complicated. Previous versions of GHCs did this, but it was the source of + numerous bugs (see #14579 and #16518, for instance). +2. While HsCoreTy is much less complicated that option (1), it's not quite + what we want. In order for `a` to be in scope over the body of `join` during + renaming, the `forall` must be contained in an HsOuterExplicit. + (See Note [Lexically scoped type variables] in GHC.Hs.Type.) HsCoreTy + bypasses HsOuterExplicit, so this won't work either. + +As a compromise, we adopt a combination of the two options above: + +* Split apart the top-level ForAllTys in the instance signature's Core type, +* Convert the top-level ForAllTys to an HsOuterExplicit, and +* Embed the remainder of the Core type in an HsCoreTy. + +This retains most of the simplicity of option (2) while still ensuring that +the type variables are correctly scoped. + +Note that splitting apart top-level ForAllTys will expand any type synonyms +in the Core type itself. This ends up being important to fix a corner case +observed in #18914. Consider this example: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +What code should `deriving C` generate? It will have roughly the following +shape: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(...) (...) (m @f) + +At a minimum, we must instantiate `coerce` with `@(T f)` and `@(T (N f))`, but +with the `forall`s removed in order to make them monotypes. However, the +`forall` is hidden underneath the `T` type synonym, so we must first expand `T` +before we can strip of the `forall`. Expanding `T`, we get +`coerce @(forall a. f a) @(forall a. N f a)`, and after omitting the `forall`s, +we get `coerce @(f a) @(N f a)`. + +We can't stop there, however, or else we would end up with this code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) @(N f a) (m @f) + +Notice that the type variable `a` is completely unbound. In order to make sure +that `a` is in scope, we must /also/ expand the `T` in `m :: T (N f)` to get +`m :: forall a. N f a`. Fortunately, we will do just that in the plan outlined +above, since when we split off the top-level ForAllTys in the instance +signature, we must first expand the T type synonym. + Note [GND and ambiguity] ~~~~~~~~~~~~~~~~~~~~~~~~ We make an effort to make the code generated through GND be robust w.r.t. @@ -1891,13 +1979,30 @@ gen_Newtype_binds loc cls inst_tvs inst_tys rhs_ty , -- The derived instance signature, e.g., -- -- op :: forall c. a -> [T x] -> c -> Int + -- + -- Make sure that `forall c` is in an HsOuterExplicit so that it + -- scopes over the body of `op`. See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. L loc $ ClassOpSig noExtField False [loc_meth_RDR] - $ L loc $ mkHsImplicitSigType $ nlHsCoreTy to_ty + $ L loc $ mkHsExplicitSigType + (map mk_hs_tvb to_tvbs) + (nlHsCoreTy to_rho) ) where Pair from_ty to_ty = mkCoerceClassMethEqn cls inst_tvs inst_tys rhs_ty meth_id - (_, _, from_tau) = tcSplitSigmaTy from_ty - (_, _, to_tau) = tcSplitSigmaTy to_ty + (_, _, from_tau) = tcSplitSigmaTy from_ty + (to_tvbs, to_rho) = tcSplitForAllTysInvis to_ty + (_, to_tau) = tcSplitPhiTy to_rho + -- The use of tcSplitForAllTysInvis above expands type synonyms, which + -- is important to ensure correct type variable scoping. + -- See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. + + mk_hs_tvb :: VarBndr TyVar flag -> LHsTyVarBndr flag GhcPs + mk_hs_tvb (Bndr tv flag) = noLoc $ KindedTyVar noExtField + flag + (noLoc (getRdrName tv)) + (nlHsCoreTy (tyVarKind tv)) meth_RDR = getRdrName meth_id loc_meth_RDR = L loc meth_RDR @@ -1950,8 +2055,8 @@ nlHsAppType e s = noLoc (HsAppType noExtField e hs_ty) where hs_ty = mkHsWildCardBndrs $ parenthesizeHsType appPrec $ nlHsCoreTy s -nlHsCoreTy :: Type -> LHsType GhcPs -nlHsCoreTy = noLoc . XHsType . NHsCoreTy +nlHsCoreTy :: HsCoreTy -> LHsType GhcPs +nlHsCoreTy = noLoc . XHsType mkCoerceClassMethEqn :: Class -- the class being derived -> [TyVar] -- the tvs in the instance head (this includes @@ -2079,15 +2184,15 @@ genAuxBindSpecDup loc original_rdr_name dup_spec genAuxBindSpecSig :: SrcSpan -> AuxBindSpec -> LHsSigWcType GhcPs genAuxBindSpecSig loc spec = case spec of DerivCon2Tag tycon _ - -> mk_sig $ L loc $ XHsType $ NHsCoreTy $ + -> mk_sig $ L loc $ XHsType $ mkSpecSigmaTy (tyConTyVars tycon) (tyConStupidTheta tycon) $ mkParentType tycon `mkVisFunTyMany` intPrimTy DerivTag2Con tycon _ -> mk_sig $ L loc $ - XHsType $ NHsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $ + XHsType $ mkSpecForAllTys (tyConTyVars tycon) $ intTy `mkVisFunTyMany` mkParentType tycon DerivMaxTag _ _ - -> mk_sig (L loc (XHsType (NHsCoreTy intTy))) + -> mk_sig (L loc (XHsType intTy)) DerivDataDataType _ _ _ -> mk_sig (nlHsTyVar dataType_RDR) DerivDataConstr _ _ _ ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -942,8 +942,8 @@ tc_infer_hs_type mode (HsSpliceTy _ (HsSpliced _ _ (HsSplicedTy ty))) tc_infer_hs_type mode (HsDocTy _ ty _) = tc_infer_lhs_type mode ty --- See Note [Typechecking NHsCoreTys] -tc_infer_hs_type _ (XHsType (NHsCoreTy ty)) +-- See Note [Typechecking HsCoreTys] +tc_infer_hs_type _ (XHsType ty) = do env <- getLclEnv -- Raw uniques since we go from NameEnv to TvSubstEnv. let subst_prs :: [(Unique, TcTyVar)] @@ -967,21 +967,21 @@ tc_infer_hs_type mode other_ty ; return (ty', kv) } {- -Note [Typechecking NHsCoreTys] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -NHsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. -As such, there's not much to be done in order to typecheck an NHsCoreTy, +Note [Typechecking HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to typecheck an HsCoreTy, since it's already been typechecked to some extent. There is one thing that we must do, however: we must substitute the type variables from the tcl_env. To see why, consider GeneralizedNewtypeDeriving, which is one of the main -clients of NHsCoreTy (example adapted from #14579): +clients of HsCoreTy (example adapted from #14579): newtype T a = MkT a deriving newtype Eq This will produce an InstInfo GhcPs that looks roughly like this: instance forall a_1. Eq a_1 => Eq (T a_1) where - (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an NHsCoreTy + (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an HsCoreTy @(T a_1 -> T a_1 -> Bool) -- So is this (==) @@ -997,9 +997,9 @@ environment (tcl_env) with [a_1 :-> a_2]. This gives us: To ensure that the body of this instance is well scoped, every occurrence of the `a` type variable should refer to a_2, the new skolem. However, the -NHsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the +HsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the substitution we need ([a_1 :-> a_2]) to fix up the scoping. We apply this -substitution to each NHsCoreTy and all is well: +substitution to each HsCoreTy and all is well: instance forall a_2. Eq a_2 => Eq (T a_2) where (==) = coerce @( a_2 -> a_2 -> Bool) @@ -1196,7 +1196,7 @@ tc_hs_type mode ty@(HsAppTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsAppKindTy{}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsOpTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsKindSig {}) ek = tc_infer_hs_type_ek mode ty ek -tc_hs_type mode ty@(XHsType (NHsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek +tc_hs_type mode ty@(XHsType {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsWildCardTy _) ek = tcAnonWildCardOcc mode ty ek {- ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -291,7 +291,7 @@ no_anon_wc_ty lty = go lty HsTyLit{} -> True HsTyVar{} -> True HsStarTy{} -> True - XHsType (NHsCoreTy{}) -> True -- Core type, which does not have any wildcard + XHsType{} -> True -- HsCoreTy, which does not have any wildcard gos = all go ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -2002,7 +2002,7 @@ mkDefMethBind dfun_id clas sel_id dm_name mk_vta :: LHsExpr GhcRn -> Type -> LHsExpr GhcRn mk_vta fun ty = noLoc (HsAppType noExtField fun (mkEmptyWildCardBndrs $ nlHsParTy - $ noLoc $ XHsType $ NHsCoreTy ty)) + $ noLoc $ XHsType ty)) -- NB: use visible type application -- See Note [Default methods in instances] ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -9,9 +9,8 @@ Derived class instances: GHC.Base.sconcat :: GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a GHC.Base.stimes :: - forall b. - GHC.Real.Integral b => - b -> T14578.Wat f g a -> T14578.Wat f g a + forall (b :: *). + GHC.Real.Integral b => b -> T14578.Wat f g a -> T14578.Wat f g a (GHC.Base.<>) = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a @@ -39,8 +38,10 @@ Derived class instances: instance GHC.Base.Functor f => GHC.Base.Functor (T14578.App f) where GHC.Base.fmap :: - forall a b. (a -> b) -> T14578.App f a -> T14578.App f b - (GHC.Base.<$) :: forall a b. a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + (a -> b) -> T14578.App f a -> T14578.App f b + (GHC.Base.<$) :: + forall (a :: *) (b :: *). a -> T14578.App f b -> T14578.App f a GHC.Base.fmap = GHC.Prim.coerce @((a -> b) -> f a -> f b) @@ -52,17 +53,19 @@ Derived class instances: instance GHC.Base.Applicative f => GHC.Base.Applicative (T14578.App f) where - GHC.Base.pure :: forall a. a -> T14578.App f a + GHC.Base.pure :: forall (a :: *). a -> T14578.App f a (GHC.Base.<*>) :: - forall a b. + forall (a :: *) (b :: *). T14578.App f (a -> b) -> T14578.App f a -> T14578.App f b GHC.Base.liftA2 :: - forall a b c. + forall (a :: *) (b :: *) (c :: *). (a -> b -> c) -> T14578.App f a -> T14578.App f b -> T14578.App f c (GHC.Base.*>) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f b + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f b (GHC.Base.<*) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f a GHC.Base.pure = GHC.Prim.coerce @(a -> f a) @(a -> T14578.App f a) (GHC.Base.pure @f) ===================================== testsuite/tests/deriving/should_compile/T18914.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE RankNTypes #-} +module T18914 where + +type T f = forall a. f a + +class C f where + m1 :: T f + m2 :: forall a. f a + +newtype N f a = MkN (f a) + deriving C ===================================== testsuite/tests/deriving/should_compile/all.T ===================================== @@ -127,3 +127,4 @@ test('T17339', normal, compile, test('T17880', normal, compile, ['']) test('T18055', normal, compile, ['']) test('T18321', normal, compile, ['']) +test('T18914', normal, compile, ['']) ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit ad9cbad7312a64e6757c32bd9488c55ba4f2fec9 +Subproject commit a6e9aa1bded7580cb8b0be6dcf46fa5dee96b631 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/22458bc95dc916a8ed93a431c5d2552b133257ee -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/22458bc95dc916a8ed93a431c5d2552b133257ee 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 Tue Nov 10 23:39:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 18:39:38 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Fix tests Message-ID: <5fab24ba2bbc1_10ee3ffbadb1cdec12934d1@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 26420a5f by Ben Gamari at 2020-11-10T18:39:28-05:00 Fix tests - - - - - 3 changed files: - testsuite/tests/printer/T18052a.stderr - testsuite/tests/simplCore/should_compile/T13143.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr Changes: ===================================== testsuite/tests/printer/T18052a.stderr ===================================== @@ -10,9 +10,9 @@ Dependent packages: [base-4.16.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 18, types: 53, coercions: 0, joins: 0/0} + = {terms: 24, types: 52, coercions: 0, joins: 0/0} --- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} T18052a.$b:||: :: forall {a} {b}. a -> b -> (a, b) [GblId, Arity=2, Unf=OtherCon []] T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) @@ -22,7 +22,7 @@ T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) [GblId] (+++) = ++ --- RHS size: {terms: 13, types: 20, coercions: 0, joins: 0/0} +-- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/0} T18052a.$m:||: :: forall {rep :: GHC.Types.RuntimeRep} {r :: TYPE rep} {a} {b}. (a, b) -> (a -> b -> r) -> ((# #) -> r) -> r ===================================== testsuite/tests/simplCore/should_compile/T13143.stderr ===================================== @@ -1,17 +1,17 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 71, types: 44, coercions: 0, joins: 0/0} + = {terms: 71, types: 40, coercions: 0, joins: 0/0} Rec { --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} T13143.$wf [InlPrag=NOINLINE, Occ=LoopBreaker] :: forall {a}. (# #) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] T13143.$wf = \ (@a) _ [Occ=Dead] -> T13143.$wf @a GHC.Prim.(##) end Rec } --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} f [InlPrag=[final]] :: forall a. Int -> a [GblId, Arity=1, ===================================== testsuite/tests/simplCore/should_compile/T18013.stderr ===================================== @@ -129,9 +129,9 @@ Rule fired: Class op fmap (BUILTIN) ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 52, types: 106, coercions: 15, joins: 0/1} + = {terms: 52, types: 101, coercions: 17, joins: 0/1} --- RHS size: {terms: 37, types: 87, coercions: 15, joins: 0/1} +-- RHS size: {terms: 37, types: 84, coercions: 17, joins: 0/1} mapMaybeRule :: forall a b. Rule IO a b -> Rule IO (Maybe a) (Maybe b) [GblId, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/26420a5f1ea11c2d54dad7c1e9ece5b28bfedfe1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/26420a5f1ea11c2d54dad7c1e9ece5b28bfedfe1 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 Wed Nov 11 02:20:01 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 10 Nov 2020 21:20:01 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags Message-ID: <5fab4a51bafe_10ee59f422813143ca@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 386976b4 by Ben Gamari at 2020-11-10T21:19:47-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 05011468 by Ben Gamari at 2020-11-10T21:19:47-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - 05ed098b by Ben Gamari at 2020-11-10T21:19:47-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 76961916 by Ben Gamari at 2020-11-10T21:19:47-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - 69640fe5 by Ömer Sinan Ağacan at 2020-11-10T21:19:47-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - c5008557 by Ray Shih at 2020-11-10T21:19:47-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 67942f2c by GHC GitLab CI at 2020-11-10T21:19:47-05:00 rts: Introduce highMemDynamic - - - - - 322e1165 by GHC GitLab CI at 2020-11-10T21:19:47-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - aa6c717c by Krzysztof Gogolewski at 2020-11-10T21:19:54-05:00 Force argument in setIdMult (#18925) - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Types/Var.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - includes/rts/Linker.h - includes/rts/storage/GC.h - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f799294a63bccbf287e091acd437be225bd57aa8...aa6c717c66fd545edb37f952064268f0622d89b0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f799294a63bccbf287e091acd437be225bd57aa8...aa6c717c66fd545edb37f952064268f0622d89b0 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 Wed Nov 11 03:44:27 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 10 Nov 2020 22:44:27 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5fab5e1b8493_10ee3ffbaed8428c132061e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: fec03b5e by Ben Gamari at 2020-11-10T22:44:21-05:00 Bump time submodule to 1.11 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 9 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/Main.hs - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 ===================================== utils/ghc-cabal/Main.hs ===================================== @@ -433,7 +433,7 @@ generate directory distdir config_args variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd), - variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), + variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fec03b5e1538d64310ceea2624f6f9b64aaa9271 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fec03b5e1538d64310ceea2624f6f9b64aaa9271 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 Wed Nov 11 07:24:43 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 11 Nov 2020 02:24:43 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] 3 commits: Introduce snapshotting of thread's own stack Message-ID: <5fab91bb76c9b_10ee3ffbadeaf20c13299a@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC Commits: 162747f9 by Sven Tennie at 2020-11-11T07:24:15+00:00 Introduce snapshotting of thread's own stack Introduce `StackSnapshot#` type and the `cloneMyStack#` primop, allowing the user to reify the state of the calling thread's stack for later inspection. The stack snapshot is offline/cold, i.e. it isn't evaluated any further. For technical details, please see note [Stack Cloning]. Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 89dbab58 by Sven Tennie at 2020-11-11T07:24:15+00:00 Introduce cloning of other threads' stacks Introduce `cloneThreadStack` function, allowing threads to request snapshots of other threads' stacks. For technical details, please see note [Stack Cloning]. Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - b3af82b7 by Matthew Pickering at 2020-11-11T07:24:15+00:00 Add another test for stack cloning This test triggers at least one GC, which showed up the problem with the stale sp field. - - - - - 22 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/StgToCmm/Prim.hs - includes/rts/storage/Closures.h - includes/stg/MiscClosures.h - + libraries/base/GHC/Stack/CloneStack.hs - libraries/base/base.cabal - + rts/CloneStack.c - + rts/CloneStack.h - rts/Messages.c - rts/PrimOps.cmm - rts/RtsSymbols.c - rts/StgMiscClosures.cmm - rts/package.conf.in - rts/rts.cabal.in - testsuite/tests/rts/all.T - + testsuite/tests/rts/cloneMyStack.hs - + testsuite/tests/rts/cloneMyStack2.hs - + testsuite/tests/rts/cloneStackLib.c - + testsuite/tests/rts/cloneThreadStack.hs - utils/genprimopcode/Main.hs Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -1770,7 +1770,7 @@ statePrimTyConKey, stableNamePrimTyConKey, stableNameTyConKey, typeConKey, threadIdPrimTyConKey, bcoPrimTyConKey, ptrTyConKey, funPtrTyConKey, tVarPrimTyConKey, eqPrimTyConKey, eqReprPrimTyConKey, eqPhantPrimTyConKey, - compactPrimTyConKey :: Unique + compactPrimTyConKey, stackSnapshotPrimTyConKey :: Unique statePrimTyConKey = mkPreludeTyConUnique 50 stableNamePrimTyConKey = mkPreludeTyConUnique 51 stableNameTyConKey = mkPreludeTyConUnique 52 @@ -1801,6 +1801,7 @@ ptrTyConKey = mkPreludeTyConUnique 77 funPtrTyConKey = mkPreludeTyConUnique 78 tVarPrimTyConKey = mkPreludeTyConUnique 79 compactPrimTyConKey = mkPreludeTyConUnique 80 +stackSnapshotPrimTyConKey = mkPreludeTyConUnique 81 eitherTyConKey :: Unique eitherTyConKey = mkPreludeTyConUnique 84 ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -69,6 +69,7 @@ module GHC.Builtin.Types.Prim( bcoPrimTyCon, bcoPrimTy, weakPrimTyCon, mkWeakPrimTy, threadIdPrimTyCon, threadIdPrimTy, + stackSnapshotPrimTyCon, stackSnapshotPrimTy, int8PrimTyCon, int8PrimTy, int8PrimTyConName, word8PrimTyCon, word8PrimTy, word8PrimTyConName, @@ -189,6 +190,7 @@ exposedPrimTyCons , word16PrimTyCon , word32PrimTyCon , word64PrimTyCon + , stackSnapshotPrimTyCon , tYPETyCon , funTyCon @@ -211,7 +213,7 @@ mkBuiltInPrimTc fs unique tycon BuiltInSyntax -charPrimTyConName, intPrimTyConName, int8PrimTyConName, int16PrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word8PrimTyConName, word16PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, proxyPrimTyConName, realWorldTyConName, arrayPrimTyConName, arrayArrayPrimTyConName, smallArrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutableArrayArrayPrimTyConName, smallMutableArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, ioPortPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, compactPrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName, eqPrimTyConName, eqReprPrimTyConName, eqPhantPrimTyConName :: Name +charPrimTyConName, intPrimTyConName, int8PrimTyConName, int16PrimTyConName, int32PrimTyConName, int64PrimTyConName, wordPrimTyConName, word32PrimTyConName, word8PrimTyConName, word16PrimTyConName, word64PrimTyConName, addrPrimTyConName, floatPrimTyConName, doublePrimTyConName, statePrimTyConName, proxyPrimTyConName, realWorldTyConName, arrayPrimTyConName, arrayArrayPrimTyConName, smallArrayPrimTyConName, byteArrayPrimTyConName, mutableArrayPrimTyConName, mutableByteArrayPrimTyConName, mutableArrayArrayPrimTyConName, smallMutableArrayPrimTyConName, mutVarPrimTyConName, mVarPrimTyConName, ioPortPrimTyConName, tVarPrimTyConName, stablePtrPrimTyConName, stableNamePrimTyConName, compactPrimTyConName, bcoPrimTyConName, weakPrimTyConName, threadIdPrimTyConName, eqPrimTyConName, eqReprPrimTyConName, eqPhantPrimTyConName, stackSnapshotPrimTyConName :: Name charPrimTyConName = mkPrimTc (fsLit "Char#") charPrimTyConKey charPrimTyCon intPrimTyConName = mkPrimTc (fsLit "Int#") intPrimTyConKey intPrimTyCon int8PrimTyConName = mkPrimTc (fsLit "Int8#") int8PrimTyConKey int8PrimTyCon @@ -247,6 +249,7 @@ tVarPrimTyConName = mkPrimTc (fsLit "TVar#") tVarPrimTyConKey tVarPr stablePtrPrimTyConName = mkPrimTc (fsLit "StablePtr#") stablePtrPrimTyConKey stablePtrPrimTyCon stableNamePrimTyConName = mkPrimTc (fsLit "StableName#") stableNamePrimTyConKey stableNamePrimTyCon compactPrimTyConName = mkPrimTc (fsLit "Compact#") compactPrimTyConKey compactPrimTyCon +stackSnapshotPrimTyConName = mkPrimTc (fsLit "StackSnapshot#") stackSnapshotPrimTyConKey stackSnapshotPrimTyCon bcoPrimTyConName = mkPrimTc (fsLit "BCO") bcoPrimTyConKey bcoPrimTyCon weakPrimTyConName = mkPrimTc (fsLit "Weak#") weakPrimTyConKey weakPrimTyCon threadIdPrimTyConName = mkPrimTc (fsLit "ThreadId#") threadIdPrimTyConKey threadIdPrimTyCon @@ -1087,6 +1090,21 @@ compactPrimTyCon = pcPrimTyCon0 compactPrimTyConName UnliftedRep compactPrimTy :: Type compactPrimTy = mkTyConTy compactPrimTyCon +{- +************************************************************************ +* * + The @StackSnapshot#@ type +* * +************************************************************************ +-} + +stackSnapshotPrimTyCon :: TyCon +stackSnapshotPrimTyCon = pcPrimTyCon0 stackSnapshotPrimTyConName UnliftedRep + +stackSnapshotPrimTy :: Type +stackSnapshotPrimTy = mkTyConTy stackSnapshotPrimTyCon + + {- ************************************************************************ * * ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3151,6 +3151,16 @@ primop SetThreadAllocationCounter "setThreadAllocationCounter#" GenPrimOp has_side_effects = True out_of_line = True +primtype StackSnapshot# + +primop CloneMyStack "cloneMyStack#" GenPrimOp + State# RealWorld -> (# State# RealWorld, StackSnapshot# #) + { Clones the stack of the current Haskell thread. } + with + has_side_effects = True + out_of_line = True + + ------------------------------------------------------------------------ section "Safe coercions" ------------------------------------------------------------------------ ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1521,6 +1521,7 @@ emitPrimOp dflags primop = case primop of TraceEventBinaryOp -> alwaysExternal TraceMarkerOp -> alwaysExternal SetThreadAllocationCounter -> alwaysExternal + CloneMyStack -> alwaysExternal where profile = targetProfile dflags ===================================== includes/rts/storage/Closures.h ===================================== @@ -431,6 +431,14 @@ typedef struct MessageBlackHole_ { StgClosure *bh; } MessageBlackHole; +typedef struct MessageCloneStack_ { + StgHeader header; + Message *link; + StgMVar *result; + StgTSO *tso; +} MessageCloneStack; + + /* ---------------------------------------------------------------------------- Compact Regions ------------------------------------------------------------------------- */ ===================================== includes/stg/MiscClosures.h ===================================== @@ -129,6 +129,7 @@ RTS_ENTRY(stg_STM_AWOKEN); RTS_ENTRY(stg_MSG_TRY_WAKEUP); RTS_ENTRY(stg_MSG_THROWTO); RTS_ENTRY(stg_MSG_BLACKHOLE); +RTS_ENTRY(stg_MSG_CLONE_STACK); RTS_ENTRY(stg_MSG_NULL); RTS_ENTRY(stg_MVAR_TSO_QUEUE); RTS_ENTRY(stg_catch); @@ -492,6 +493,7 @@ RTS_FUN_DECL(stg_traceBinaryEventzh); RTS_FUN_DECL(stg_traceMarkerzh); RTS_FUN_DECL(stg_getThreadAllocationCounterzh); RTS_FUN_DECL(stg_setThreadAllocationCounterzh); +RTS_FUN_DECL(stg_cloneMyStackzh); /* Other misc stuff */ ===================================== libraries/base/GHC/Stack/CloneStack.hs ===================================== @@ -0,0 +1,70 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE UnliftedFFITypes#-} + +-- | +-- This module exposes an interface for capturing the state of a thread's +-- execution stack for diagnostics purposes. +-- +-- @since 2.16.0.0 +module GHC.Stack.CloneStack ( + StackSnapshot(..), + cloneMyStack, + cloneThreadStack + ) where + +import GHC.Prim (StackSnapshot#, cloneMyStack#, ThreadId#) +import Control.Concurrent.MVar +import GHC.Conc.Sync +import GHC.Stable +import GHC.IO (IO(..)) + +-- | A frozen snapshot of the state of an execution stack. +-- +-- @since 2.16.0.0 +data StackSnapshot = StackSnapshot !StackSnapshot# + +{- +Note [Stack Cloning] +~~~~~~~~~~~~~~~~~~~~ +"Cloning" a stack means that it's StgStack closure is copied including the +stack memory (stack[]). The stack pointer (sp) of the clone is adjusted to be +valid. + +The clone is "offline"/"cold", i.e. it won't be evaluated any further. This is +useful for further analyses like stack unwinding or traversal. + +There are two different ways to clone a stack: +1. By the corresponding thread via a primop call (cloneMyStack#). +2. By sending a RTS message (Messages.c) with a MVar to the corresponding + thread and receiving the stack by taking it out of this MVar. + +A StackSnapshot# is really a pointer to an immutable StgStack closure with +the invariant that stack->sp points to a valid frame. +-} + +-- | Clone the stack of the executing thread +-- +-- @since 2.16.0.0 +cloneMyStack :: IO StackSnapshot +cloneMyStack = IO $ \s -> + case (cloneMyStack# s) of (# s1, stack #) -> (# s1, StackSnapshot stack #) + +foreign import ccall "sendCloneStackMessage" sendCloneStackMessage :: ThreadId# -> StablePtr PrimMVar -> IO () + +-- | Clone the stack of a thread identified by its 'ThreadId' +-- +-- @since 2.16.0.0 +cloneThreadStack :: ThreadId -> IO StackSnapshot +cloneThreadStack (ThreadId tid#) = do + resultVar <- newEmptyMVar @StackSnapshot + ptr <- newStablePtrPrimMVar resultVar + -- Use the RTS's "message" mechanism to request that + -- the thread captures its stack, saving the result + -- into resultVar. + sendCloneStackMessage tid# ptr + freeStablePtr ptr + takeMVar resultVar + ===================================== libraries/base/base.cabal ===================================== @@ -264,6 +264,7 @@ Library GHC.ResponseFile GHC.RTS.Flags GHC.ST + GHC.Stack.CloneStack GHC.StaticPtr GHC.STRef GHC.Show ===================================== rts/CloneStack.c ===================================== @@ -0,0 +1,104 @@ +/* --------------------------------------------------------------------------- + * + * (c) The GHC Team, 2001-2021 + * + * Stack snapshotting. + */ + +#include + +#include "Rts.h" +#include "rts/Messages.h" +#include "Messages.h" +#include "rts/storage/TSO.h" +#include "stg/Types.h" +#include "CloneStack.h" +#include "StablePtr.h" +#include "Threads.h" + +#if defined(DEBUG) +#include "sm/Sanity.h" +#endif + +static StgStack* cloneStackChunk(Capability* capability, const StgStack* stack) +{ + StgWord spOffset = stack->sp - stack->stack; + StgWord closureSizeBytes = sizeof(StgStack) + (stack->stack_size * sizeof(StgWord)); + + StgStack* newStackClosure = (StgStack*) allocate(capability, ROUNDUP_BYTES_TO_WDS(closureSizeBytes)); + + memcpy(newStackClosure, stack, closureSizeBytes); + + newStackClosure->sp = newStackClosure->stack + spOffset; + // The new stack is not on the mutable list; clear the dirty flag such that + // we don't claim that it is. + newStackClosure->dirty = 0; + +#if defined(DEBUG) + checkClosure((StgClosure*) newStackClosure); +#endif + + return newStackClosure; +} + +StgStack* cloneStack(Capability* capability, const StgStack* stack) +{ + StgStack *top_stack = cloneStackChunk(capability, stack); + StgStack *last_stack = top_stack; + while (true) { + // check whether the stack ends in an underflow frame + StgPtr top = last_stack->stack + last_stack->stack_size; + StgUnderflowFrame *underFlowFrame = ((StgUnderflowFrame *) top); + StgUnderflowFrame *frame = underFlowFrame--; + if (frame->info == &stg_stack_underflow_frame_info) { + StgStack *s = cloneStackChunk(capability, frame->next_chunk); + frame->next_chunk = s; + last_stack = s; + } else { + break; + } + } + return top_stack; +} + +#if defined(THREADED_RTS) + +// ThreadId# in Haskell is a StgTSO* in RTS. +void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar) { + Capability *srcCapability = rts_unsafeGetMyCapability(); + + MessageCloneStack *msg; + msg = (MessageCloneStack *)allocate(srcCapability, sizeofW(MessageCloneStack)); + msg->tso = tso; + msg->result = (StgMVar*)deRefStablePtr(mvar); + freeStablePtr(mvar); + SET_HDR(msg, &stg_MSG_CLONE_STACK_info, CCS_SYSTEM); + // Ensure that writes constructing Message are committed before sending. + write_barrier(); + + sendMessage(srcCapability, tso->cap, (Message *)msg); +} + +void handleCloneStackMessage(MessageCloneStack *msg){ + StgStack* newStackClosure = cloneStack(msg->tso->cap, msg->tso->stackobj); + + // Lift StackSnapshot# to StackSnapshot by applying it's constructor. + // This is necessary because performTryPutMVar() puts the closure onto the + // stack for evaluation and stacks can not be evaluated (entered). + HaskellObj result = rts_apply(msg->tso->cap, StackSnapshot_constructor_closure, (HaskellObj) newStackClosure); + + bool putMVarWasSuccessful = performTryPutMVar(msg->tso->cap, msg->result, result); + + if(!putMVarWasSuccessful) { + barf("Can't put stack cloning result into MVar."); + } +} + +#else // !defined(THREADED_RTS) + +GNU_ATTRIBUTE(__noreturn__) +void sendCloneStackMessage(StgTSO *tso STG_UNUSED, HsStablePtr mvar STG_UNUSED) { + barf("Sending CloneStackMessages is only available in threaded RTS!"); +} + +#endif // end !defined(THREADED_RTS) ===================================== rts/CloneStack.h ===================================== @@ -0,0 +1,23 @@ +/* --------------------------------------------------------------------------- + * + * (c) The GHC Team, 2001-2021 + * + * Stack snapshotting. + */ + +#pragma once + +extern StgClosure DLL_IMPORT_DATA_VARNAME(base_GHCziStackziCloneStack_StackSnapshot_closure); +#define StackSnapshot_constructor_closure DLL_IMPORT_DATA_REF(base_GHCziStackziCloneStack_StackSnapshot_closure) + +StgStack* cloneStack(Capability* capability, const StgStack* stack); + +void sendCloneStackMessage(StgTSO *tso, HsStablePtr mvar); + +#include "BeginPrivate.h" + +#if defined(THREADED_RTS) +void handleCloneStackMessage(MessageCloneStack *msg); +#endif + +#include "EndPrivate.h" ===================================== rts/Messages.c ===================================== @@ -14,6 +14,7 @@ #include "Threads.h" #include "RaiseAsync.h" #include "sm/Storage.h" +#include "CloneStack.h" /* ---------------------------------------------------------------------------- Send a message to another Capability @@ -32,7 +33,8 @@ void sendMessage(Capability *from_cap, Capability *to_cap, Message *msg) i != &stg_MSG_BLACKHOLE_info && i != &stg_MSG_TRY_WAKEUP_info && i != &stg_IND_info && // can happen if a MSG_BLACKHOLE is revoked - i != &stg_WHITEHOLE_info) { + i != &stg_WHITEHOLE_info && + i != &stg_MSG_CLONE_STACK_info) { barf("sendMessage: %p", i); } } @@ -131,6 +133,10 @@ loop: #endif goto loop; } + else if(i == &stg_MSG_CLONE_STACK_info){ + MessageCloneStack *cloneStackMessage = (MessageCloneStack*) m; + handleCloneStackMessage(cloneStackMessage); + } else { barf("executeMessage: %p", i); ===================================== rts/PrimOps.cmm ===================================== @@ -2840,3 +2840,14 @@ stg_setThreadAllocationCounterzh ( I64 counter ) StgTSO_alloc_limit(CurrentTSO) = counter + TO_I64(offset); return (); } + +stg_cloneMyStackzh () { + W_ stgStack; + W_ clonedStack; + stgStack = StgTSO_stackobj(CurrentTSO); + StgStack_sp(stgStack) = Sp; + + ("ptr" clonedStack) = ccall cloneStack(MyCapability() "ptr", stgStack "ptr"); + + return (clonedStack); +} ===================================== rts/RtsSymbols.c ===================================== @@ -12,6 +12,7 @@ #include "Rts.h" #include "TopHandler.h" #include "HsFFI.h" +#include "CloneStack.h" #include "sm/Storage.h" #include "sm/NonMovingMark.h" @@ -979,6 +980,7 @@ SymI_HasProto(stg_traceBinaryEventzh) \ SymI_HasProto(stg_getThreadAllocationCounterzh) \ SymI_HasProto(stg_setThreadAllocationCounterzh) \ + SymI_HasProto(stg_cloneMyStackzh) \ SymI_HasProto(getMonotonicNSec) \ SymI_HasProto(lockFile) \ SymI_HasProto(unlockFile) \ @@ -998,6 +1000,7 @@ SymI_HasProto(cas) \ SymI_HasProto(_assertFail) \ SymI_HasProto(keepCAFs) \ + SymI_HasProto(sendCloneStackMessage) \ RTS_USER_SIGNALS_SYMBOLS \ RTS_INTCHAR_SYMBOLS ===================================== rts/StgMiscClosures.cmm ===================================== @@ -573,6 +573,9 @@ INFO_TABLE_CONSTR(stg_MSG_BLACKHOLE,3,0,0,PRIM,"MSG_BLACKHOLE","MSG_BLACKHOLE") INFO_TABLE_CONSTR(stg_MSG_NULL,1,0,0,PRIM,"MSG_NULL","MSG_NULL") { foreign "C" barf("MSG_NULL object (%p) entered!", R1) never returns; } +INFO_TABLE_CONSTR(stg_MSG_CLONE_STACK,3,0,0,PRIM,"MSG_CLONE_STACK","MSG_CLONE_STACK") +{ foreign "C" barf("stg_MSG_CLONE_STACK object (%p) entered!", R1) never returns; } + /* ---------------------------------------------------------------------------- END_TSO_QUEUE ===================================== rts/package.conf.in ===================================== @@ -194,6 +194,7 @@ ld-options: * so we need to force it to be included in the binary. */ , "-Wl,-u,_findPtr" #endif + , "-Wl,-u,_base_GHCziStackziCloneStack_StackSnapshot_closure" #else "-Wl,-u,base_GHCziTopHandler_runIO_closure" , "-Wl,-u,base_GHCziTopHandler_runNonIO_closure" @@ -308,6 +309,7 @@ ld-options: * so we need to force it to be included in the binary. */ , "-Wl,-u,findPtr" #endif + , "-Wl,-u,base_GHCziStackziCloneStack_StackSnapshot_closure" #endif /* Pick up static libraries in preference over dynamic if in earlier search ===================================== rts/rts.cabal.in ===================================== @@ -286,6 +286,7 @@ library "-Wl,-u,_hs_atomicwrite8" "-Wl,-u,_hs_atomicwrite16" "-Wl,-u,_hs_atomicwrite32" + "-Wl,-u,_base_GHCziStackziCloneStack_StackSnapshot_closure" if flag(find-ptr) -- This symbol is useful in gdb, but not referred to anywhere, @@ -367,6 +368,7 @@ library "-Wl,-u,hs_atomicwrite8" "-Wl,-u,hs_atomicwrite16" "-Wl,-u,hs_atomicwrite32" + "-Wl,-u,base_GHCziStackziCloneStack_StackSnapshot_closure" if flag(find-ptr) -- This symbol is useful in gdb, but not referred to anywhere, @@ -410,6 +412,7 @@ library Arena.c Capability.c CheckUnload.c + CloneStack.c ClosureFlags.c Disassembler.c FileLock.c ===================================== testsuite/tests/rts/all.T ===================================== @@ -418,3 +418,8 @@ test('T17088', compile_and_run, ['-rtsopts -O2']) test('T15427', normal, compile_and_run, ['']) + +test('cloneMyStack', [extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c']) +test('cloneMyStack2', ignore_stdout, compile_and_run, ['']) + +test('cloneThreadStack', [only_ways(['threaded1']), extra_ways(['threaded1']), extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c -threaded']) ===================================== testsuite/tests/rts/cloneMyStack.hs ===================================== @@ -0,0 +1,22 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnliftedFFITypes #-} + +import GHC.Prim (StackSnapshot#) +import GHC.Stack.CloneStack +import Foreign +import Foreign.C.Types (CUInt) + +foreign import ccall "expectClosureTypes" expectClosureTypes:: StackSnapshot# -> Ptr CUInt -> Int -> IO () + +main :: IO () +main = do + stackSnapshot <- cloneMyStack + + let (StackSnapshot stack) = stackSnapshot + let expectedClosureTypes = [ 30 -- RET_SMALL + , 30 -- RET_SMALL + , 34 -- CATCH_FRAME + ,36 -- STOP_FRAME + ] + withArray expectedClosureTypes (\ptr -> expectClosureTypes stack ptr (length expectedClosureTypes)) ===================================== testsuite/tests/rts/cloneMyStack2.hs ===================================== @@ -0,0 +1,15 @@ +{-# LANGUAGE BangPatterns #-} +module Main where + +import GHC.Stack.CloneStack + +main = foo 100 + +{-# NOINLINE foo #-} +foo 0 = () <$ getStack +foo n = print "x" >> foo (n - 1) >> print "x" + +-- This shouldn't segfault +getStack = do + !s <- cloneMyStack + return () ===================================== testsuite/tests/rts/cloneStackLib.c ===================================== @@ -0,0 +1,55 @@ +#include "Rts.h" +#include "RtsAPI.h" +#include "rts/Messages.h" + + +void expectStacksToBeEqual(StgStack *clonedStack, StgTSO *tso) { + StgStack *liveStack = tso->stackobj; + + if(liveStack->header.info != clonedStack->header.info){ + barf("info table pointer not equal! Expected same pointer address, but got %p and %p", liveStack->header.info, clonedStack->header.info); + } + + StgInfoTable *info = INFO_PTR_TO_STRUCT(liveStack->header.info); + + if (info->type != STACK) { + barf("Expected a closure of type STACK!"); + } + + if(liveStack->stack_size != clonedStack->stack_size){ + barf("Expected same stack_size!"); + } + + if(liveStack->marking != clonedStack->marking){ + barf("Expected same marking flags!"); + } + + for(StgWord i = liveStack->stack_size - 1; (liveStack->stack + i) >= liveStack->sp; i--){ + if(liveStack->stack[i] != clonedStack->stack[i]){ + barf("Expected stack word %lu to be equal on both stacks.", i); + } + } +} + +void expectStackToBeNotDirty(StgStack *stack) { + if(stack->dirty != 0) { + barf("Expected stack to be not dirty. But dirty flag was set to %u", stack->dirty); + } +} + +void expectClosureTypes(StgStack *stack, unsigned int types[], size_t typesSize){ + StgPtr sp = stack->sp; + StgPtr spBottom = stack->stack + stack->stack_size; + + for (StgWord i = 0; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp), i++) { + const StgInfoTable *info = get_itbl((StgClosure *)sp); + + if(i >= typesSize) { + barf("Stack size exceeds expectation!"); + } + + if(info->type != types[i]) { + barf("Wrong closure type on stack! Expected %u but got %u in position %i", types[i], info->type, i); + } + } +} ===================================== testsuite/tests/rts/cloneThreadStack.hs ===================================== @@ -0,0 +1,49 @@ +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnliftedFFITypes #-} + +import GHC.Prim (StackSnapshot#, ThreadId#) +import GHC.Conc.Sync (ThreadId(..)) +import GHC.Stack.CloneStack +import Control.Concurrent +import GHC.Conc + +foreign import ccall "expectStacksToBeEqual" expectStacksToBeEqual:: StackSnapshot# -> ThreadId# -> IO () + +foreign import ccall "expectStackToBeNotDirty" expectStackToBeNotDirty:: StackSnapshot# -> IO () + +main :: IO () +main = do + mVarToBeBlockedOn <- newEmptyMVar + threadId <- forkIO $ immediatelyBlocking mVarToBeBlockedOn + + waitUntilBlocked threadId + + stackSnapshot <- cloneThreadStack threadId + + let (StackSnapshot stack) = stackSnapshot + let (ThreadId tid#) = threadId + expectStacksToBeEqual stack tid# + expectStackToBeNotDirty stack + +immediatelyBlocking :: MVar Int -> IO () +immediatelyBlocking mVarToBeBlockedOn = do + takeMVar mVarToBeBlockedOn + return () + +waitUntilBlocked :: ThreadId -> IO () +waitUntilBlocked tid = do + blocked <- isBlocked tid + if blocked then + return () + else + do + threadDelay 100000 + waitUntilBlocked tid + +isBlocked:: ThreadId -> IO Bool +isBlocked = fmap isThreadStatusBlocked . threadStatus + +isThreadStatusBlocked :: ThreadStatus -> Bool +isThreadStatusBlocked (ThreadBlocked _) = True +isThreadStatusBlocked _ = False ===================================== utils/genprimopcode/Main.hs ===================================== @@ -878,6 +878,7 @@ ppType (TyApp (TyCon "ThreadId#") []) = "threadIdPrimTy" ppType (TyApp (TyCon "ForeignObj#") []) = "foreignObjPrimTy" ppType (TyApp (TyCon "BCO") []) = "bcoPrimTy" ppType (TyApp (TyCon "Compact#") []) = "compactPrimTy" +ppType (TyApp (TyCon "StackSnapshot#") []) = "stackSnapshotPrimTy" ppType (TyApp (TyCon "()") []) = "unitTy" -- unitTy is GHC.Builtin.Types's name for () ppType (TyVar "a") = "alphaTy" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6b09e577cf7afb73a423db02a62a3eff150f8dde...b3af82b74cf8ac9f6523d0506d807b3e0c70c0eb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6b09e577cf7afb73a423db02a62a3eff150f8dde...b3af82b74cf8ac9f6523d0506d807b3e0c70c0eb 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 Wed Nov 11 08:20:08 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 11 Nov 2020 03:20:08 -0500 Subject: [Git][ghc/ghc][master] 4 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags Message-ID: <5fab9eb8ce895_10eecf772981335627@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - 12 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - testsuite/tests/regalloc/regalloc_unit_tests.hs Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -118,6 +118,7 @@ module GHC.Cmm.CLabel ( LabelStyle (..), pprDebugCLabel, pprCLabel, + ppInternalProcLabel, -- * Others dynamicLinkerLabelInfo, @@ -1082,8 +1083,8 @@ isLocalCLabel this_mod lbl = -- that data resides in a DLL or not. [Win32 only.] -- @labelDynamic@ returns @True@ if the label is located -- in a DLL, be it a data reference or not. -labelDynamic :: NCGConfig -> Module -> CLabel -> Bool -labelDynamic config this_mod lbl = +labelDynamic :: NCGConfig -> CLabel -> Bool +labelDynamic config lbl = case lbl of -- is the RTS in a DLL or not? RtsLabel _ -> @@ -1136,6 +1137,7 @@ labelDynamic config this_mod lbl = externalDynamicRefs = ncgExternalDynamicRefs config platform = ncgPlatform config os = platformOS platform + this_mod = ncgThisModule config this_unit = toUnitId (moduleUnit this_mod) @@ -1359,6 +1361,39 @@ pprCLabel platform sty lbl = CmmLabel _ _ fs CmmRet -> maybe_underscore $ ftext fs <> text "_ret" CmmLabel _ _ fs CmmClosure -> maybe_underscore $ ftext fs <> text "_closure" +-- Note [Internal proc labels] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- Some tools (e.g. the `perf` utility on Linux) rely on the symbol table +-- for resolution of function names. To help these tools we provide the +-- (enabled by default) -fexpose-all-symbols flag which causes GHC to produce +-- symbols even for symbols with are internal to a module (although such +-- symbols will have only local linkage). +-- +-- Note that these labels are *not* referred to by code. They are strictly for +-- diagnostics purposes. +-- +-- To avoid confusion, it is desireable to add a module-qualifier to the +-- symbol name. However, the Name type's Internal constructor doesn't carry +-- knowledge of the current Module. Consequently, we have to pass this around +-- explicitly. + +-- | Generate a label for a procedure internal to a module (if +-- 'Opt_ExposeAllSymbols' is enabled). +-- See Note [Internal proc labels]. +ppInternalProcLabel :: Module -- ^ the current module + -> CLabel + -> Maybe SDoc -- ^ the internal proc label +ppInternalProcLabel this_mod (IdLabel nm _ flavour) + | isInternalName nm + = Just + $ text "_" <> ppr this_mod + <> char '_' + <> ztext (zEncodeFS (occNameFS (occName nm))) + <> char '_' + <> pprUniqueAlways (getUnique nm) + <> ppIdFlavor flavour +ppInternalProcLabel _ _ = Nothing ppIdFlavor :: IdLabelInfo -> SDoc ppIdFlavor x = pp_cSEP <> case x of ===================================== compiler/GHC/Cmm/Info/Build.hs ===================================== @@ -946,7 +946,8 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do topSRT <- get let - config = initNCGConfig dflags + this_mod = thisModule topSRT + config = initNCGConfig dflags this_mod profile = targetProfile dflags platform = profilePlatform profile srtMap = moduleSRTMap topSRT @@ -1019,8 +1020,6 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do in state{ moduleSRTMap = srt_map } - this_mod = thisModule topSRT - allStaticData = all (\(CAFLabel clbl) -> Set.member clbl static_data) caf_lbls @@ -1048,7 +1047,7 @@ oneSRT dflags staticFuns lbls caf_lbls isCAF cafs static_data = do -- when dynamic linking is used we cannot guarantee that the offset -- between the SRT and the info table will fit in the offset field. -- Consequently we build a singleton SRT in this case. - not (labelDynamic config this_mod lbl) + not (labelDynamic config lbl) -- MachO relocations can't express offsets between compilation units at -- all, so we are always forced to build a singleton SRT in this case. ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -152,11 +152,11 @@ nativeCodeGen :: forall a . DynFlags -> Module -> ModLocation -> Handle -> UniqS -> Stream IO RawCmmGroup a -> IO a nativeCodeGen dflags this_mod modLoc h us cmms - = let config = initNCGConfig dflags + = let config = initNCGConfig dflags this_mod platform = ncgPlatform config nCG' :: ( OutputableP Platform statics, Outputable jumpDest, Instruction instr) => NcgImpl statics instr jumpDest -> IO a - nCG' ncgImpl = nativeCodeGen' dflags config this_mod modLoc ncgImpl h us cmms + nCG' ncgImpl = nativeCodeGen' dflags config modLoc ncgImpl h us cmms in case platformArch platform of ArchX86 -> nCG' (X86.ncgX86 config) ArchX86_64 -> nCG' (X86.ncgX86_64 config) @@ -221,20 +221,20 @@ See also Note [What is this unwinding business?] in "GHC.Cmm.DebugBlock". nativeCodeGen' :: (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> Handle -> UniqSupply -> Stream IO RawCmmGroup a -> IO a -nativeCodeGen' dflags config this_mod modLoc ncgImpl h us cmms +nativeCodeGen' dflags config modLoc ncgImpl h us cmms = do -- BufHandle is a performance hack. We could hide it inside -- Pretty if it weren't for the fact that we do lots of little -- printDocs here (in order to do codegen in constant space). bufh <- newBufHandle h let ngs0 = NGS [] [] [] [] [] [] emptyUFM mapEmpty - (ngs, us', a) <- cmmNativeGenStream dflags config this_mod modLoc ncgImpl bufh us + (ngs, us', a) <- cmmNativeGenStream dflags config modLoc ncgImpl bufh us cmms ngs0 _ <- finishNativeGen dflags config modLoc bufh us' ngs return a @@ -290,7 +290,7 @@ finishNativeGen dflags config modLoc bufh@(BufHandle _ _ h) us ngs -- write out the imports let ctx = ncgAsmContext config printSDocLn ctx Pretty.LeftMode h - $ makeImportsDoc dflags (concat (ngs_imports ngs)) + $ makeImportsDoc config (concat (ngs_imports ngs)) return us' where dump_stats = dumpAction dflags (mkDumpStyle alwaysQualify) @@ -300,7 +300,7 @@ finishNativeGen dflags config modLoc bufh@(BufHandle _ _ h) us ngs cmmNativeGenStream :: (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> BufHandle -> UniqSupply @@ -308,7 +308,7 @@ cmmNativeGenStream :: (OutputableP Platform statics, Outputable jumpDest, Instru -> NativeGenAcc statics instr -> IO (NativeGenAcc statics instr, UniqSupply, a) -cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs +cmmNativeGenStream dflags config modLoc ncgImpl h us cmm_stream ngs = do r <- Stream.runStream cmm_stream case r of Left a -> @@ -330,7 +330,7 @@ cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs dbgMap = debugToMap ndbgs -- Generate native code - (ngs',us') <- cmmNativeGens dflags config this_mod modLoc ncgImpl h + (ngs',us') <- cmmNativeGens dflags config modLoc ncgImpl h dbgMap us cmms ngs 0 -- Link native code information into debug blocks @@ -345,7 +345,7 @@ cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us cmm_stream ngs let ngs'' = ngs' { ngs_debug = ngs_debug ngs' ++ ldbgs, ngs_labels = [] } return (us', ngs'') - cmmNativeGenStream dflags config this_mod modLoc ncgImpl h us' + cmmNativeGenStream dflags config modLoc ncgImpl h us' cmm_stream' ngs'' where ncglabel = text "NCG" @@ -356,7 +356,7 @@ cmmNativeGens :: forall statics instr jumpDest. (OutputableP Platform statics, Outputable jumpDest, Instruction instr) => DynFlags -> NCGConfig - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> BufHandle -> LabelMap DebugBlock @@ -366,7 +366,7 @@ cmmNativeGens :: forall statics instr jumpDest. -> Int -> IO (NativeGenAcc statics instr, UniqSupply) -cmmNativeGens dflags config this_mod modLoc ncgImpl h dbgMap = go +cmmNativeGens dflags config modLoc ncgImpl h dbgMap = go where go :: UniqSupply -> [RawCmmDecl] -> NativeGenAcc statics instr -> Int @@ -379,7 +379,7 @@ cmmNativeGens dflags config this_mod modLoc ncgImpl h dbgMap = go let fileIds = ngs_dwarfFiles ngs (us', fileIds', native, imports, colorStats, linearStats, unwinds) <- {-# SCC "cmmNativeGen" #-} - cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap + cmmNativeGen dflags modLoc ncgImpl us fileIds dbgMap cmm count -- Generate .file directives for every new file that has been @@ -433,7 +433,7 @@ emitNativeCode dflags config h sdoc = do cmmNativeGen :: forall statics instr jumpDest. (Instruction instr, OutputableP Platform statics, Outputable jumpDest) => DynFlags - -> Module -> ModLocation + -> ModLocation -> NcgImpl statics instr jumpDest -> UniqSupply -> DwarfFiles @@ -449,7 +449,7 @@ cmmNativeGen , LabelMap [UnwindPoint] -- unwinding information for blocks ) -cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count +cmmNativeGen dflags modLoc ncgImpl us fileIds dbgMap cmm count = do let config = ncgConfig ncgImpl let platform = ncgPlatform config @@ -467,7 +467,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- cmm to cmm optimisations let (opt_cmm, imports) = {-# SCC "cmmToCmm" #-} - cmmToCmm config this_mod fixed_cmm + cmmToCmm config fixed_cmm dumpIfSet_dyn dflags Opt_D_dump_opt_cmm "Optimised Cmm" FormatCMM @@ -479,7 +479,7 @@ cmmNativeGen dflags this_mod modLoc ncgImpl us fileIds dbgMap cmm count -- generate native code from cmm let ((native, lastMinuteImports, fileIds', nativeCfgWeights), usGen) = {-# SCC "genMachCode" #-} - initUs us $ genMachCode config this_mod modLoc + initUs us $ genMachCode config modLoc (cmmTopCodeGen ncgImpl) fileIds dbgMap opt_cmm cmmCfg @@ -750,8 +750,8 @@ computeUnwinding _ ncgImpl (CmmProc _ _ _ (ListGraph blks)) = -- | Build a doc for all the imports. -- -makeImportsDoc :: DynFlags -> [CLabel] -> SDoc -makeImportsDoc dflags imports +makeImportsDoc :: NCGConfig -> [CLabel] -> SDoc +makeImportsDoc config imports = dyld_stubs imports $$ -- On recent versions of Darwin, the linker supports @@ -779,7 +779,6 @@ makeImportsDoc dflags imports else Outputable.empty) where - config = initNCGConfig dflags platform = ncgPlatform config -- Generate "symbol stubs" for all external symbols that might @@ -915,7 +914,7 @@ apply_mapping ncgImpl ufm (CmmProc info lbl live (ListGraph blocks)) genMachCode :: NCGConfig - -> Module -> ModLocation + -> ModLocation -> (RawCmmDecl -> NatM [NatCmmDecl statics instr]) -> DwarfFiles -> LabelMap DebugBlock @@ -928,9 +927,9 @@ genMachCode , CFG ) -genMachCode config this_mod modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg +genMachCode config modLoc cmmTopCodeGen fileIds dbgMap cmm_top cmm_cfg = do { initial_us <- getUniqueSupplyM - ; let initial_st = mkNatM_State initial_us 0 config this_mod + ; let initial_st = mkNatM_State initial_us 0 config modLoc fileIds dbgMap cmm_cfg (new_tops, final_st) = initNat initial_st (cmmTopCodeGen cmm_top) final_delta = natm_delta final_st @@ -967,10 +966,10 @@ Ideas for other things we could do (put these in Hoopl please!): temp assignments, and certain assigns to mem...) -} -cmmToCmm :: NCGConfig -> Module -> RawCmmDecl -> (RawCmmDecl, [CLabel]) -cmmToCmm _ _ top@(CmmData _ _) = (top, []) -cmmToCmm config this_mod (CmmProc info lbl live graph) - = runCmmOpt config this_mod $ +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') @@ -987,34 +986,33 @@ pattern OptMResult x y = (# x, y #) data OptMResult a = OptMResult !a ![CLabel] deriving (Functor) #endif -newtype CmmOptM a = CmmOptM (NCGConfig -> Module -> [CLabel] -> OptMResult a) +newtype CmmOptM a = CmmOptM (NCGConfig -> [CLabel] -> OptMResult a) deriving (Functor) instance Applicative CmmOptM where - pure x = CmmOptM $ \_ _ imports -> OptMResult x imports + pure x = CmmOptM $ \_ imports -> OptMResult x imports (<*>) = ap instance Monad CmmOptM where (CmmOptM f) >>= g = - CmmOptM $ \config this_mod imports0 -> - case f config this_mod imports0 of + CmmOptM $ \config imports0 -> + case f config imports0 of OptMResult x imports1 -> case g x of - CmmOptM g' -> g' config this_mod imports1 + CmmOptM g' -> g' config imports1 instance CmmMakeDynamicReferenceM CmmOptM where addImport = addImportCmmOpt - getThisModule = CmmOptM $ \_ this_mod imports -> OptMResult this_mod imports addImportCmmOpt :: CLabel -> CmmOptM () -addImportCmmOpt lbl = CmmOptM $ \_ _ imports -> OptMResult () (lbl:imports) +addImportCmmOpt lbl = CmmOptM $ \_ imports -> OptMResult () (lbl:imports) getCmmOptConfig :: CmmOptM NCGConfig -getCmmOptConfig = CmmOptM $ \config _ imports -> OptMResult config imports +getCmmOptConfig = CmmOptM $ \config imports -> OptMResult config imports -runCmmOpt :: NCGConfig -> Module -> CmmOptM a -> (a, [CLabel]) -runCmmOpt config this_mod (CmmOptM f) = - case f config this_mod [] of +runCmmOpt :: NCGConfig -> CmmOptM a -> (a, [CLabel]) +runCmmOpt config (CmmOptM f) = + case f config [] of OptMResult result imports -> (result, imports) cmmBlockConFold :: CmmBlock -> CmmOptM CmmBlock @@ -1144,9 +1142,10 @@ cmmExprNative referenceKind expr = do -> return other -- | Initialize the native code generator configuration from the DynFlags -initNCGConfig :: DynFlags -> NCGConfig -initNCGConfig dflags = NCGConfig +initNCGConfig :: DynFlags -> Module -> NCGConfig +initNCGConfig dflags this_mod = NCGConfig { ncgPlatform = targetPlatform dflags + , ncgThisModule = this_mod , ncgAsmContext = initSDocContext dflags (PprCode AsmStyle) , ncgProcAlignment = cmmProcAlignment dflags , ncgExternalDynamicRefs = gopt Opt_ExternalDynamicRefs dflags @@ -1191,5 +1190,6 @@ initNCGConfig dflags = NCGConfig , ncgDwarfEnabled = debugLevel dflags > 0 , ncgDwarfUnwindings = debugLevel dflags >= 1 , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. + , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags } ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -11,12 +11,14 @@ import GHC.Prelude import GHC.Platform import GHC.Cmm.Type (Width(..)) import GHC.CmmToAsm.CFG.Weight +import GHC.Unit.Module (Module) import GHC.Utils.Outputable -- | Native code generator configuration data NCGConfig = NCGConfig { ncgPlatform :: !Platform -- ^ Target platform , ncgAsmContext :: !SDocContext -- ^ Context for ASM code generation + , ncgThisModule :: !Module -- ^ The name of the module we are currently compiling , ncgProcAlignment :: !(Maybe Int) -- ^ Mandatory proc alignment , ncgExternalDynamicRefs :: !Bool -- ^ Generate code to link against dynamic libraries , ncgPIC :: !Bool -- ^ Enable Position-Independent Code @@ -37,6 +39,7 @@ data NCGConfig = NCGConfig , ncgDwarfEnabled :: !Bool -- ^ Enable Dwarf generation , ncgDwarfUnwindings :: !Bool -- ^ Enable unwindings , ncgDwarfStripBlockInfo :: !Bool -- ^ Strip out block information from generated Dwarf + , ncgExposeInternalSymbols :: !Bool -- ^ Expose symbol table entries for internal symbols } -- | Return Word size ===================================== compiler/GHC/CmmToAsm/Monad.hs ===================================== @@ -80,6 +80,8 @@ data NcgImpl statics instr jumpDest = NcgImpl { canShortcut :: instr -> Maybe jumpDest, shortcutStatics :: (BlockId -> Maybe jumpDest) -> statics -> statics, shortcutJump :: (BlockId -> Maybe jumpDest) -> instr -> instr, + -- | 'Module' is only for printing internal labels. See Note [Internal proc + -- labels] in CLabel. pprNatCmmDecl :: NatCmmDecl statics instr -> SDoc, maxSpillSlots :: Int, allocatableRegs :: [RealReg], @@ -107,7 +109,6 @@ data NatM_State natm_imports :: [(CLabel)], natm_pic :: Maybe Reg, natm_config :: NCGConfig, - natm_this_module :: Module, natm_modloc :: ModLocation, natm_fileid :: DwarfFiles, natm_debug_map :: LabelMap DebugBlock, @@ -125,9 +126,9 @@ newtype NatM result = NatM (NatM_State -> (result, NatM_State)) unNat :: NatM a -> NatM_State -> (a, NatM_State) unNat (NatM a) = a -mkNatM_State :: UniqSupply -> Int -> NCGConfig -> Module -> ModLocation -> +mkNatM_State :: UniqSupply -> Int -> NCGConfig -> ModLocation -> DwarfFiles -> LabelMap DebugBlock -> CFG -> NatM_State -mkNatM_State us delta config this_mod +mkNatM_State us delta config = \loc dwf dbg cfg -> NatM_State { natm_us = us @@ -135,7 +136,6 @@ mkNatM_State us delta config this_mod , natm_imports = [] , natm_pic = Nothing , natm_config = config - , natm_this_module = this_mod , natm_modloc = loc , natm_fileid = dwf , natm_debug_map = dbg @@ -198,10 +198,11 @@ getCfgWeights = NatM $ \ st -> (ncgCfgWeights (natm_config st), st) setDeltaNat :: Int -> NatM () setDeltaNat delta = NatM $ \ st -> ((), st {natm_delta = delta}) - getThisModuleNat :: NatM Module -getThisModuleNat = NatM $ \ st -> (natm_this_module st, st) +getThisModuleNat = NatM $ \ st -> (ncgThisModule $ natm_config st, st) +instance HasModule NatM where + getModule = getThisModuleNat addImportNat :: CLabel -> NatM () addImportNat imp ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -65,7 +65,6 @@ import GHC.Cmm import GHC.Cmm.CLabel import GHC.Types.Basic -import GHC.Unit.Module import GHC.Utils.Outputable import GHC.Utils.Panic @@ -95,11 +94,9 @@ data ReferenceKind class Monad m => CmmMakeDynamicReferenceM m where addImport :: CLabel -> m () - getThisModule :: m Module instance CmmMakeDynamicReferenceM NatM where addImport = addImportNat - getThisModule = getThisModuleNat cmmMakeDynamicReference :: CmmMakeDynamicReferenceM m @@ -113,13 +110,11 @@ cmmMakeDynamicReference config referenceKind lbl = return $ CmmLit $ CmmLabel lbl -- already processed it, pass through | otherwise - = do this_mod <- getThisModule - let platform = ncgPlatform config + = do let platform = ncgPlatform config case howToAccessLabel config (platformArch platform) (platformOS platform) - this_mod referenceKind lbl of AccessViaStub -> do @@ -208,7 +203,7 @@ data LabelAccessStyle | AccessViaSymbolPtr | AccessDirectly -howToAccessLabel :: NCGConfig -> Arch -> OS -> Module -> ReferenceKind -> CLabel -> LabelAccessStyle +howToAccessLabel :: NCGConfig -> Arch -> OS -> ReferenceKind -> CLabel -> LabelAccessStyle -- Windows -- In Windows speak, a "module" is a set of objects linked into the @@ -231,7 +226,7 @@ howToAccessLabel :: NCGConfig -> Arch -> OS -> Module -> ReferenceKind -> CLabel -- into the same .exe file. In this case we always access symbols directly, -- and never use __imp_SYMBOL. -- -howToAccessLabel config _ OSMinGW32 this_mod _ lbl +howToAccessLabel config _arch OSMinGW32 _kind lbl -- Assume all symbols will be in the same PE, so just access them directly. | not (ncgExternalDynamicRefs config) @@ -239,7 +234,7 @@ howToAccessLabel config _ OSMinGW32 this_mod _ lbl -- If the target symbol is in another PE we need to access it via the -- appropriate __imp_SYMBOL pointer. - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr -- Target symbol is in the same PE as the caller, so just access it directly. @@ -255,9 +250,9 @@ howToAccessLabel config _ OSMinGW32 this_mod _ lbl -- It is always possible to access something indirectly, -- even when it's not necessary. -- -howToAccessLabel config arch OSDarwin this_mod DataReference lbl +howToAccessLabel config arch OSDarwin DataReference lbl -- data access to a dynamic library goes via a symbol pointer - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr -- when generating PIC code, all cross-module data references must @@ -276,21 +271,21 @@ howToAccessLabel config arch OSDarwin this_mod DataReference lbl | otherwise = AccessDirectly -howToAccessLabel config arch OSDarwin this_mod JumpReference lbl +howToAccessLabel config arch OSDarwin JumpReference lbl -- dyld code stubs don't work for tailcalls because the -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: | arch == ArchX86 || arch == ArchX86_64 - , labelDynamic config this_mod lbl + , labelDynamic config lbl = AccessViaSymbolPtr -howToAccessLabel config arch OSDarwin this_mod _ lbl +howToAccessLabel config arch OSDarwin _kind lbl -- Code stubs are the usual method of choice for imported code; -- not needed on x86_64 because Apple's new linker, ld64, generates -- them automatically. | arch /= ArchX86_64 - , labelDynamic config this_mod lbl + , labelDynamic config lbl = AccessViaStub | otherwise @@ -301,7 +296,7 @@ howToAccessLabel config arch OSDarwin this_mod _ lbl -- AIX -- quite simple (for now) -howToAccessLabel _config _arch OSAIX _this_mod kind _lbl +howToAccessLabel _config _arch OSAIX kind _lbl = case kind of DataReference -> AccessViaSymbolPtr CallReference -> AccessDirectly @@ -318,7 +313,7 @@ howToAccessLabel _config _arch OSAIX _this_mod kind _lbl -- from position independent code. It is also required from the main program -- when dynamic libraries containing Haskell code are used. -howToAccessLabel _ (ArchPPC_64 _) os _ kind _ +howToAccessLabel _config (ArchPPC_64 _) os kind _lbl | osElfTarget os = case kind of -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC @@ -330,7 +325,7 @@ howToAccessLabel _ (ArchPPC_64 _) os _ kind _ -- regular calls are handled by the runtime linker _ -> AccessDirectly -howToAccessLabel config _ os _ _ _ +howToAccessLabel config _arch os _kind _lbl -- no PIC -> the dynamic linker does everything for us; -- if we don't dynamically link to Haskell code, -- it actually manages to do so without messing things up. @@ -339,11 +334,11 @@ howToAccessLabel config _ os _ _ _ not (ncgExternalDynamicRefs config) = AccessDirectly -howToAccessLabel config arch os this_mod DataReference lbl +howToAccessLabel config arch os DataReference lbl | osElfTarget os = case () of -- A dynamic label needs to be accessed via a symbol pointer. - _ | labelDynamic config this_mod lbl + _ | labelDynamic config lbl -> AccessViaSymbolPtr -- For PowerPC32 -fPIC, we have to access even static data @@ -369,25 +364,25 @@ howToAccessLabel config arch os this_mod DataReference lbl -- (AccessDirectly, because we get an implicit symbol stub) -- and calling functions from PIC code on non-i386 platforms (via a symbol stub) -howToAccessLabel config arch os this_mod CallReference lbl +howToAccessLabel config arch os CallReference lbl | osElfTarget os - , labelDynamic config this_mod lbl && not (ncgPIC config) + , labelDynamic config lbl && not (ncgPIC config) = AccessDirectly | osElfTarget os , arch /= ArchX86 - , labelDynamic config this_mod lbl + , labelDynamic config lbl , ncgPIC config = AccessViaStub -howToAccessLabel config _ os this_mod _ lbl +howToAccessLabel config _arch os _kind lbl | osElfTarget os - = if labelDynamic config this_mod lbl + = if labelDynamic config lbl then AccessViaSymbolPtr else AccessDirectly -- all other platforms -howToAccessLabel config _ _ _ _ _ +howToAccessLabel config _arch _os _kind _lbl | not (ncgPIC config) = AccessDirectly ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -90,6 +90,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = -- special case for code without info table: pprSectionAlign config (Section Text lbl) $$ pprProcAlignment config $$ + pprProcLabel config lbl $$ pprLabel platform lbl $$ -- blocks guaranteed not null, so label needed vcat (map (pprBasicBlock config top_info) blocks) $$ (if ncgDwarfEnabled config @@ -99,6 +100,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = Just (CmmStaticsRaw info_lbl _) -> pprSectionAlign config (Section Text info_lbl) $$ pprProcAlignment config $$ + pprProcLabel config lbl $$ (if platformHasSubsectionsViaSymbols platform then pdoc platform (mkDeadStripPreventer info_lbl) <> char ':' else empty) $$ @@ -114,6 +116,15 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = else empty) $$ pprSizeDecl platform info_lbl +-- | Output an internal proc label. See Note [Internal proc labels] in CLabel. +pprProcLabel :: NCGConfig -> CLabel -> SDoc +pprProcLabel config lbl + | ncgExposeInternalSymbols config + , Just lbl' <- ppInternalProcLabel (ncgThisModule config) lbl + = lbl' <> char ':' + | otherwise + = empty + -- | Output the ELF .size directive. pprSizeDecl :: Platform -> CLabel -> SDoc pprSizeDecl platform lbl ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -274,6 +274,7 @@ data GeneralFlag -- forwards all -L flags to the collect2 command without using a -- response file and as such breaking apart. | Opt_SingleLibFolder + | Opt_ExposeInternalSymbols | Opt_KeepCAFs | Opt_KeepGoing | Opt_ByteCode ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -376,7 +376,6 @@ import qualified GHC.LanguageExtensions as LangExt -- ----------------------------------------------------------------------------- -- DynFlags - -- | Used to differentiate the scope an include needs to apply to. -- We have to split the include paths to avoid accidentally forcing recursive -- includes since -I overrides the system search paths. See #14312. @@ -3417,6 +3416,7 @@ fFlagsDeps = [ flagSpec "error-spans" Opt_ErrorSpans, flagSpec "excess-precision" Opt_ExcessPrecision, flagSpec "expose-all-unfoldings" Opt_ExposeAllUnfoldings, + flagSpec "expose-internal-symbols" Opt_ExposeInternalSymbols, flagSpec "external-dynamic-refs" Opt_ExternalDynamicRefs, flagSpec "external-interpreter" Opt_ExternalInterpreter, flagSpec "flat-cache" Opt_FlatCache, @@ -4419,7 +4419,13 @@ setVerbosity :: Maybe Int -> DynP () setVerbosity mb_n = upd (\dfs -> dfs{ verbosity = mb_n `orElse` 3 }) setDebugLevel :: Maybe Int -> DynP () -setDebugLevel mb_n = upd (\dfs -> dfs{ debugLevel = mb_n `orElse` 2 }) +setDebugLevel mb_n = + upd (\dfs -> exposeSyms $ dfs{ debugLevel = n }) + where + n = mb_n `orElse` 2 + exposeSyms + | n > 2 = setGeneralFlag' Opt_ExposeInternalSymbols + | otherwise = id data PkgDbRef = GlobalPkgDb ===================================== docs/users_guide/debug-info.rst ===================================== @@ -14,6 +14,7 @@ useable by most UNIX debugging tools. :category: debugging :since: 7.10, numeric levels since 8.0 + :implies: :ghc-flag:`-fexpose-internal-symbols` when ⟨n⟩ >= 2. Emit debug information in object code. Currently only DWARF debug information is supported on x86-64 and i386. Currently debug levels 0 ===================================== docs/users_guide/phases.rst ===================================== @@ -720,6 +720,20 @@ Options affecting code generation all target platforms. See the :ghc-flag:`--print-object-splitting-supported` flag to check whether your GHC supports object splitting. +.. ghc-flag:: -fexpose-internal-symbols + :shortdesc: Produce symbols for all functions, including internal functions. + :type: dynamic + :category: codegen + + Request that GHC emits verbose symbol tables which include local symbols + for module-internal functions. These can be useful for tools like + :ref:`perf ` but increase object file sizes. + This is implied by :ghc-flag:`-g2 <-g>` and above. + + :ghc-flag:`-fno-expose-internal-symbols <-fexpose-internal-symbols>` + suppresses all non-global symbol table entries, resulting in smaller object + file sizes at the expense of debuggability. + .. _options-linker: Options affecting linking ===================================== testsuite/tests/regalloc/regalloc_unit_tests.hs ===================================== @@ -106,7 +106,7 @@ compileCmmForRegAllocStats :: IO [( Maybe [Color.RegAllocStats (Alignment, RawCmmStatics) X86.Instr.Instr] , Maybe [Linear.RegAllocStats])] compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do - let ncgImpl = ncgImplF (initNCGConfig dflags) + let ncgImpl = ncgImplF (initNCGConfig dflags thisMod) hscEnv <- newHscEnv dflags -- parse the cmm file and output any warnings or errors @@ -126,7 +126,7 @@ compileCmmForRegAllocStats dflags' cmmFile ncgImplF us = do -- compile and discard the generated code, returning regalloc stats mapM (\ (count, thisCmm) -> - cmmNativeGen dflags thisMod thisModLoc ncgImpl + cmmNativeGen dflags thisModLoc ncgImpl usb dwarfFileIds dbgMap thisCmm count >>= (\(_, _, _, _, colorStats, linearStats, _) -> -- scrub unneeded output from cmmNativeGen View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2e63a0fb1bdaecc7916a3cc35dcfd2b2ef37c328...584058ddff71460023712a8d816b83b581e6e78f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2e63a0fb1bdaecc7916a3cc35dcfd2b2ef37c328...584058ddff71460023712a8d816b83b581e6e78f 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 Wed Nov 11 08:20:43 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 11 Nov 2020 03:20:43 -0500 Subject: [Git][ghc/ghc][master] 4 commits: Fix and enable object unloading in GHCi Message-ID: <5fab9edb95def_10ee3ffb947686881341677@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 30 changed files: - compiler/GHC/Linker/Loader.hs - includes/rts/Linker.h - includes/rts/storage/GC.h - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - rts/sm/Storage.c - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/Makefile - testsuite/tests/rts/linker/all.T - testsuite/tests/rts/linker/linker_error.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/584058ddff71460023712a8d816b83b581e6e78f...e9e1b2e75de17be47ab887a26943f5517a8463ac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/584058ddff71460023712a8d816b83b581e6e78f...e9e1b2e75de17be47ab887a26943f5517a8463ac 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 Wed Nov 11 08:21:20 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 11 Nov 2020 03:21:20 -0500 Subject: [Git][ghc/ghc][master] Force argument in setIdMult (#18925) Message-ID: <5fab9f00ca3fb_10eecf772981344678@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 1 changed file: - compiler/GHC/Types/Var.hs Changes: ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -869,8 +869,8 @@ updateIdTypeAndMultM f id@(Id { varType = ty updateIdTypeAndMultM _ other = pprPanic "updateIdTypeAndMultM" (ppr other) setIdMult :: Id -> Mult -> Id -setIdMult id r | isId id = id { varMult = r } - | otherwise = pprPanic "setIdMult" (ppr id <+> ppr r) +setIdMult id !r | isId id = id { varMult = r } + | otherwise = pprPanic "setIdMult" (ppr id <+> ppr r) {- ************************************************************************ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5506f1342e51bad71a7525ddad0650d1ac63afeb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5506f1342e51bad71a7525ddad0650d1ac63afeb 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 Wed Nov 11 09:38:20 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 11 Nov 2020 04:38:20 -0500 Subject: [Git][ghc/ghc][wip/T18870] 2 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5fabb10c2ef01_10ee3ffbc96b853c1358297@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/T18870 at Glasgow Haskell Compiler / GHC Commits: a0dff89b by Sebastian Graf at 2020-11-11T10:38:11+01:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 6d868f11 by Sebastian Graf at 2020-11-11T10:38:11+01:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. - - - - - 6 changed files: - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity (AT oss div) ar + | oss `lengthAtMost` ar = AT (take ar oss) topDiv + | otherwise = AT (take ar oss) div + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac85229e2cba3571f6a205881beea304c270f483...6d868f11fe4c3c4f1892c22780d8742fb8a5e356 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac85229e2cba3571f6a205881beea304c270f483...6d868f11fe4c3c4f1892c22780d8742fb8a5e356 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 Wed Nov 11 10:03:58 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 11 Nov 2020 05:03:58 -0500 Subject: [Git][ghc/ghc][wip/T18870] 2 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5fabb70eeb9f3_10ee3ffbd5bed7d01361729@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/T18870 at Glasgow Haskell Compiler / GHC Commits: 18940dbf by Sebastian Graf at 2020-11-11T11:03:49+01:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - ff98c9f1 by Sebastian Graf at 2020-11-11T11:03:49+01:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. - - - - - 6 changed files: - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity at@(AT oss _) ar + | oss `lengthAtMost` ar = at + | otherwise = AT (take ar oss) topDiv + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d868f11fe4c3c4f1892c22780d8742fb8a5e356...ff98c9f1d91fc04378308f78d682b0f95bbe29ce -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d868f11fe4c3c4f1892c22780d8742fb8a5e356...ff98c9f1d91fc04378308f78d682b0f95bbe29ce 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 Wed Nov 11 10:47:06 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 11 Nov 2020 05:47:06 -0500 Subject: [Git][ghc/ghc][wip/T18870] Arity: Emit "Exciting arity" warning only after second iteration (#18937) Message-ID: <5fabc12a8435f_10ee3ffbaec1e67c13670d0@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/T18870 at Glasgow Haskell Compiler / GHC Commits: 93aa155c by Sebastian Graf at 2020-11-11T11:46:50+01:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - 2 changed files: - compiler/GHC/Core/Opt/Arity.hs - testsuite/tests/arityanal/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -639,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to -- old_arity, and then we stop right away, because old_arity is assumed -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(AT oss div) - | not (isDeadEndDiv div) -- the "stop right away" case - , length oss <= old_arity = cur_atype -- from above - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -706,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -20,4 +20,4 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) -test('T18937', [ only_ways(['optasm']), when(compiler_debugged(), expect_broken(18937)) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/93aa155c2b48d966f4b8df43483a00339e11eb6d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/93aa155c2b48d966f4b8df43483a00339e11eb6d 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 Wed Nov 11 12:17:34 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Wed, 11 Nov 2020 07:17:34 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18939 Message-ID: <5fabd65e59610_10ee3ffbd46de08813750b7@gitlab.haskell.org.mail> Ryan Scott pushed new branch wip/T18939 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18939 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 Wed Nov 11 15:05:40 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 11 Nov 2020 10:05:40 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 2 commits: Demand: Interleave usage and strictness demands (#18903) Message-ID: <5fabfdc4ec1d3_10ee3ffbae130bac139753c@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: b8070cdd by Sebastian Graf at 2020-11-11T15:56:38+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands ============ Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1((1(U),S(U)))`. This would allow Nested CPR to unbox the division, for example. Nested strict product demands ============================= Fixing #18903 gives us enough expressiveness to tackle #18885, where we have ```hs f :: Int -> Int f y = let x | expensive y == 1 = (expensive (y+1), expensive (y+2)) | otherwise = (expensive (y+3), expensive (y+4)) in case () of _ | expensive (y+5) == 42 -> fst x _ | expensive (y+6) == 41 -> fst x + snd x _ | otherwise -> 0 ``` Here, we used to give `x` demand `1P(1P(U),1P(U))`. The outer `1` is because `x` is used lazily and the inner `1`s are redundant with that fact. That leaves some expressiveness on the table. After this change, we infer `1P(SP(U),1P(U))`, meaning that *whenever we evaluate `x`*, we evaluate its first component strictly, effectively making strictness product demands apply *relatively*. Usage product demands still apply absolutely, though. More details on how we could exploit the new language in `Note [Absent sub-demands]`. Fixes #18903 and fixes #18885. - - - - - 390a17c5 by Sebastian Graf at 2020-11-11T16:05:14+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/edea2fb99faaa4706bcd781b508cc4e80b1715ba...390a17c5723c37c8f259d3fe60824933449a8a1b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/edea2fb99faaa4706bcd781b508cc4e80b1715ba...390a17c5723c37c8f259d3fe60824933449a8a1b 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 Wed Nov 11 15:14:13 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 11 Nov 2020 10:14:13 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 2 commits: Demand: Interleave usage and strictness demands (#18903) Message-ID: <5fabffc5ce4b9_10ee3ffbae036fe4139962d@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: c642a43a by Sebastian Graf at 2020-11-11T16:14:02+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands ============ Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1((1(U),S(U)))`. This would allow Nested CPR to unbox the division, for example. Nested strict product demands ============================= Fixing #18903 gives us enough expressiveness to tackle #18885, where we have ```hs f :: Int -> Int f y = let x | expensive y == 1 = (expensive (y+1), expensive (y+2)) | otherwise = (expensive (y+3), expensive (y+4)) in case () of _ | expensive (y+5) == 42 -> fst x _ | expensive (y+6) == 41 -> fst x + snd x _ | otherwise -> 0 ``` Here, we used to give `x` demand `1P(1P(U),1P(U))`. The outer `1` is because `x` is used lazily and the inner `1`s are redundant with that fact. That leaves some expressiveness on the table. After this change, we infer `1P(SP(U),1P(U))`, meaning that *whenever we evaluate `x`*, we evaluate its first component strictly, effectively making strictness product demands apply *relatively*. Usage product demands still apply absolutely, though. More details on how we could exploit the new language in `Note [Absent sub-demands]`. Fixes #18903 and fixes #18885. - - - - - 3d2d37c6 by Sebastian Graf at 2020-11-11T16:14:02+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/390a17c5723c37c8f259d3fe60824933449a8a1b...3d2d37c6d70a93854090a91467e5987102e4d4d7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/390a17c5723c37c8f259d3fe60824933449a8a1b...3d2d37c6d70a93854090a91467e5987102e4d4d7 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 Wed Nov 11 15:56:10 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Wed, 11 Nov 2020 10:56:10 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fac099a31e8f_10ee3ffbd5167ea0140206e@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: c6c9653e by Daniel Rogozin at 2020-11-11T18:55:31+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c6c9653e988274a2ee53dcea4f0fae9ec645ec22 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c6c9653e988274a2ee53dcea4f0fae9ec645ec22 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 Wed Nov 11 17:54:10 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 11 Nov 2020 12:54:10 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 4 commits: Improve some comments Message-ID: <5fac25423752a_10ee3ffb90fc7238141286d@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 57b64775 by Richard Eisenberg at 2020-11-11T08:56:13-05:00 Improve some comments - - - - - 150897ed by Richard Eisenberg at 2020-11-11T11:36:19-05:00 Checkpoint before adding filterTM - - - - - 65bd0608 by Richard Eisenberg at 2020-11-11T12:52:41-05:00 remove stale givens from famapp-cache - - - - - ef747932 by Richard Eisenberg at 2020-11-11T12:53:42-05:00 Remove unused parameter - - - - - 10 changed files: - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Types/Unique/DFM.hs Changes: ===================================== compiler/GHC/Cmm/Dataflow/Label.hs ===================================== @@ -141,6 +141,7 @@ instance TrieMap LabelMap where alterTM k f m = mapAlter f k m foldTM k m z = mapFoldr k z m mapTM f m = mapMap f m + filterTM f m = mapFilter f m ----------------------------------------------------------------------------- -- FactBase ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -80,7 +80,7 @@ module GHC.Core.Coercion ( -- ** Free variables tyCoVarsOfCo, tyCoVarsOfCos, coVarsOfCo, tyCoFVsOfCo, tyCoFVsOfCos, tyCoVarsOfCoDSet, - coercionSize, + coercionSize, anyFreeVarsOfCo, -- ** Substitution CvSubstEnv, emptyCvSubstEnv, ===================================== compiler/GHC/Core/Map.hs ===================================== @@ -116,6 +116,7 @@ instance TrieMap CoreMap where alterTM k f (CoreMap m) = CoreMap (alterTM (deBruijnize k) f m) foldTM k (CoreMap m) = foldTM k m mapTM f (CoreMap m) = CoreMap (mapTM f m) + filterTM f (CoreMap m) = CoreMap (filterTM f m) -- | @CoreMapG a@ is a map from @DeBruijn CoreExpr@ to @a at . The extended -- key makes it suitable for recursive traversal, since it can track binders, @@ -197,6 +198,7 @@ instance TrieMap CoreMapX where alterTM = xtE foldTM = fdE mapTM = mapE + filterTM = ftE -------------------------- mapE :: (a->b) -> CoreMapX a -> CoreMapX b @@ -213,6 +215,20 @@ mapE f (CM { cm_var = cvar, cm_lit = clit , cm_letr = mapTM (mapTM (mapTM f)) cletr, cm_case = mapTM (mapTM f) ccase , cm_ecase = mapTM (mapTM f) cecase, cm_tick = mapTM (mapTM f) ctick } +ftE :: (a->Bool) -> CoreMapX a -> CoreMapX a +ftE f (CM { cm_var = cvar, cm_lit = clit + , cm_co = cco, cm_type = ctype + , cm_cast = ccast , cm_app = capp + , cm_lam = clam, cm_letn = cletn + , cm_letr = cletr, cm_case = ccase + , cm_ecase = cecase, cm_tick = ctick }) + = CM { cm_var = filterTM f cvar, cm_lit = filterTM f clit + , cm_co = filterTM f cco, cm_type = filterTM f ctype + , cm_cast = mapTM (filterTM f) ccast, cm_app = mapTM (filterTM f) capp + , cm_lam = mapTM (filterTM f) clam, cm_letn = mapTM (mapTM (filterTM f)) cletn + , cm_letr = mapTM (mapTM (filterTM f)) cletr, cm_case = mapTM (filterTM f) ccase + , cm_ecase = mapTM (filterTM f) cecase, cm_tick = mapTM (filterTM f) ctick } + -------------------------- lookupCoreMap :: CoreMap a -> CoreExpr -> Maybe a lookupCoreMap cm e = lookupTM e cm @@ -330,6 +346,7 @@ instance TrieMap AltMap where alterTM = xtA emptyCME foldTM = fdA mapTM = mapA + filterTM = ftA instance Eq (DeBruijn CoreAlt) where D env1 a1 == D env2 a2 = go a1 a2 where @@ -348,6 +365,12 @@ mapA f (AM { am_deflt = adeflt, am_data = adata, am_lit = alit }) , am_data = mapTM (mapTM f) adata , am_lit = mapTM (mapTM f) alit } +ftA :: (a->Bool) -> AltMap a -> AltMap a +ftA f (AM { am_deflt = adeflt, am_data = adata, am_lit = alit }) + = AM { am_deflt = filterTM f adeflt + , am_data = mapTM (filterTM f) adata + , am_lit = mapTM (filterTM f) alit } + lkA :: CmEnv -> CoreAlt -> AltMap a -> Maybe a lkA env (DEFAULT, _, rhs) = am_deflt >.> lkG (D env rhs) lkA env (LitAlt lit, _, rhs) = am_lit >.> lookupTM lit >=> lkG (D env rhs) ===================================== compiler/GHC/Core/Map/Type.hs ===================================== @@ -90,6 +90,7 @@ instance TrieMap CoercionMap where alterTM k f (CoercionMap m) = CoercionMap (alterTM (deBruijnize k) f m) foldTM k (CoercionMap m) = foldTM k m mapTM f (CoercionMap m) = CoercionMap (mapTM f m) + filterTM f (CoercionMap m) = CoercionMap (filterTM f m) type CoercionMapG = GenMap CoercionMapX newtype CoercionMapX a = CoercionMapX (TypeMapX a) @@ -101,6 +102,7 @@ instance TrieMap CoercionMapX where alterTM = xtC foldTM f (CoercionMapX core_tm) = foldTM f core_tm mapTM f (CoercionMapX core_tm) = CoercionMapX (mapTM f core_tm) + filterTM f (CoercionMapX core_tm) = CoercionMapX (filterTM f core_tm) instance Eq (DeBruijn Coercion) where D env1 co1 == D env2 co2 @@ -176,6 +178,7 @@ instance TrieMap TypeMapX where alterTM = xtT foldTM = fdT mapTM = mapT + filterTM = filterT instance Eq (DeBruijn Type) where env_t@(D env t) == env_t'@(D env' t') @@ -289,6 +292,18 @@ fdT k m = foldTM k (tm_var m) . foldTyLit k (tm_tylit m) . foldMaybe k (tm_coerce m) +filterT :: (a -> Bool) -> TypeMapX a -> TypeMapX a +filterT f (TM { tm_var = tvar, tm_app = tapp, tm_tycon = ttycon + , tm_funty = tfunty, tm_forall = tforall, tm_tylit = tlit + , tm_coerce = tcoerce }) + = TM { tm_var = filterTM f tvar + , tm_app = mapTM (filterTM f) tapp + , tm_tycon = filterTM f ttycon + , tm_funty = mapTM (mapTM (filterTM f)) tfunty + , tm_forall = mapTM (filterTM f) tforall + , tm_tylit = filterTM f tlit + , tm_coerce = filterMaybe f tcoerce } + ------------------------ data TyLitMap a = TLM { tlm_number :: Map.Map Integer a , tlm_string :: UniqFM FastString a @@ -301,6 +316,7 @@ instance TrieMap TyLitMap where alterTM = xtTyLit foldTM = foldTyLit mapTM = mapTyLit + filterTM = filterTyLit emptyTyLitMap :: TyLitMap a emptyTyLitMap = TLM { tlm_number = Map.empty, tlm_string = emptyUFM } @@ -325,6 +341,10 @@ foldTyLit :: (a -> b -> b) -> TyLitMap a -> b -> b foldTyLit l m = flip (foldUFM l) (tlm_string m) . flip (Map.foldr l) (tlm_number m) +filterTyLit :: (a -> Bool) -> TyLitMap a -> TyLitMap a +filterTyLit f (TLM { tlm_number = tn, tlm_string = ts }) + = TLM { tlm_number = Map.filter f tn, tlm_string = filterUFM f ts } + ------------------------------------------------- -- | @TypeMap a@ is a map from 'Type' to @a at . If you are a client, this -- is the type you want. The keys in this map may have different kinds. @@ -348,6 +368,7 @@ instance TrieMap TypeMap where alterTM k f m = xtTT (deBruijnize k) f m foldTM k (TypeMap m) = foldTM (foldTM k) m mapTM f (TypeMap m) = TypeMap (mapTM (mapTM f) m) + filterTM f (TypeMap m) = TypeMap (mapTM (filterTM f) m) foldTypeMap :: (a -> b -> b) -> b -> TypeMap a -> b foldTypeMap k z m = foldTM k m z @@ -388,6 +409,7 @@ instance TrieMap LooseTypeMap where alterTM k f (LooseTypeMap m) = LooseTypeMap (alterTM (deBruijnize k) f m) foldTM f (LooseTypeMap m) = foldTM f m mapTM f (LooseTypeMap m) = LooseTypeMap (mapTM f m) + filterTM f (LooseTypeMap m) = LooseTypeMap (filterTM f m) {- ************************************************************************ @@ -462,6 +484,7 @@ instance TrieMap BndrMap where alterTM = xtBndr emptyCME foldTM = fdBndrMap mapTM = mapBndrMap + filterTM = ftBndrMap mapBndrMap :: (a -> b) -> BndrMap a -> BndrMap b mapBndrMap f (BndrMap tm) = BndrMap (mapTM (mapTM f) tm) @@ -483,6 +506,8 @@ xtBndr :: forall a . CmEnv -> Var -> XT a -> BndrMap a -> BndrMap a xtBndr env v xt (BndrMap tymap) = BndrMap (tymap |> xtG (D env (varType v)) |>> (alterTM (D env <$> varMultMaybe v) xt)) +ftBndrMap :: (a -> Bool) -> BndrMap a -> BndrMap a +ftBndrMap f (BndrMap tm) = BndrMap (mapTM (filterTM f) tm) --------- Variable occurrence ------------- data VarMap a = VM { vm_bvar :: BoundVarMap a -- Bound variable @@ -495,6 +520,7 @@ instance TrieMap VarMap where alterTM = xtVar emptyCME foldTM = fdVar mapTM = mapVar + filterTM = ftVar mapVar :: (a->b) -> VarMap a -> VarMap b mapVar f (VM { vm_bvar = bv, vm_fvar = fv }) @@ -520,6 +546,10 @@ lkDFreeVar var env = lookupDVarEnv env var xtDFreeVar :: Var -> XT a -> DVarEnv a -> DVarEnv a xtDFreeVar v f m = alterDVarEnv f m v +ftVar :: (a -> Bool) -> VarMap a -> VarMap a +ftVar f (VM { vm_bvar = bv, vm_fvar = fv }) + = VM { vm_bvar = filterTM f bv, vm_fvar = filterTM f fv } + ------------------------------------------------- lkDNamed :: NamedThing n => n -> DNameEnv a -> Maybe a lkDNamed n env = lookupDNameEnv env (getName n) ===================================== compiler/GHC/Core/TyCon/Env.hs ===================================== @@ -29,7 +29,7 @@ module GHC.Core.TyCon.Env ( emptyDTyConEnv, isEmptyDTyConEnv, lookupDTyConEnv, delFromDTyConEnv, filterDTyConEnv, - mapDTyConEnv, + mapDTyConEnv, mapMaybeDTyConEnv, adjustDTyConEnv, alterDTyConEnv, extendDTyConEnv, foldDTyConEnv ) where @@ -131,6 +131,9 @@ filterDTyConEnv = filterUDFM mapDTyConEnv :: (a -> b) -> DTyConEnv a -> DTyConEnv b mapDTyConEnv = mapUDFM +mapMaybeDTyConEnv :: (a -> Maybe b) -> DTyConEnv a -> DTyConEnv b +mapMaybeDTyConEnv = mapMaybeUDFM + adjustDTyConEnv :: (a -> a) -> DTyConEnv a -> TyCon -> DTyConEnv a adjustDTyConEnv = adjustUDFM ===================================== compiler/GHC/Data/TrieMap.hs ===================================== @@ -16,11 +16,11 @@ module GHC.Data.TrieMap( -- * Maps over 'Literal's LiteralMap, -- * 'TrieMap' class - TrieMap(..), insertTM, deleteTM, foldMapTM, + TrieMap(..), insertTM, deleteTM, foldMapTM, isEmptyTM, -- * Things helpful for adding additional Instances. (>.>), (|>), (|>>), XT, - foldMaybe, + foldMaybe, filterMaybe, -- * Map for leaf compression GenMap, lkG, xtG, mapG, fdG, @@ -72,6 +72,7 @@ class TrieMap m where lookupTM :: forall b. Key m -> m b -> Maybe b alterTM :: forall b. Key m -> XT b -> m b -> m b mapTM :: (a->b) -> m a -> m b + filterTM :: (a -> Bool) -> m a -> m a foldTM :: (a -> b -> b) -> m a -> b -> b -- The unusual argument order here makes @@ -87,6 +88,10 @@ deleteTM k m = alterTM k (\_ -> Nothing) m foldMapTM :: (TrieMap m, Monoid r) => (a -> r) -> m a -> r foldMapTM f m = foldTM (\ x r -> f x S.<> r) m mempty +-- This looks inefficient. +isEmptyTM :: TrieMap m => m a -> Bool +isEmptyTM m = foldTM (\ _ _ -> False) m True + ---------------------- -- Recall that -- Control.Monad.(>=>) :: (a -> Maybe b) -> (b -> Maybe c) -> a -> Maybe c @@ -126,6 +131,7 @@ instance TrieMap IntMap.IntMap where alterTM = xtInt foldTM k m z = IntMap.foldr k z m mapTM f m = IntMap.map f m + filterTM f m = IntMap.filter f m xtInt :: Int -> XT a -> IntMap.IntMap a -> IntMap.IntMap a xtInt k f m = IntMap.alter f k m @@ -137,6 +143,7 @@ instance Ord k => TrieMap (Map.Map k) where alterTM k f m = Map.alter f k m foldTM k m z = Map.foldr k z m mapTM f m = Map.map f m + filterTM f m = Map.filter f m {- @@ -213,6 +220,7 @@ instance forall key. Uniquable key => TrieMap (UniqDFM key) where alterTM k f m = alterUDFM f m k foldTM k m z = foldUDFM k z m mapTM f m = mapUDFM f m + filterTM f m = filterUDFM f m {- ************************************************************************ @@ -234,6 +242,7 @@ instance TrieMap m => TrieMap (MaybeMap m) where alterTM = xtMaybe alterTM foldTM = fdMaybe mapTM = mapMb + filterTM = ftMaybe instance TrieMap m => Foldable (MaybeMap m) where foldMap = foldMapTM @@ -256,6 +265,19 @@ fdMaybe :: TrieMap m => (a -> b -> b) -> MaybeMap m a -> b -> b fdMaybe k m = foldMaybe k (mm_nothing m) . foldTM k (mm_just m) +ftMaybe :: TrieMap m => (a -> Bool) -> MaybeMap m a -> MaybeMap m a +ftMaybe f (MM { mm_nothing = mn, mm_just = mj }) + = MM { mm_nothing = filterMaybe f mn, mm_just = filterTM f mj } + +foldMaybe :: (a -> b -> b) -> Maybe a -> b -> b +foldMaybe _ Nothing b = b +foldMaybe k (Just a) b = k a b + +filterMaybe :: (a -> Bool) -> Maybe a -> Maybe a +filterMaybe _ Nothing = Nothing +filterMaybe f input@(Just x) | f x = input + | otherwise = Nothing + {- ************************************************************************ * * @@ -275,6 +297,7 @@ instance TrieMap m => TrieMap (ListMap m) where alterTM = xtList alterTM foldTM = fdList mapTM = mapList + filterTM = ftList instance TrieMap m => Foldable (ListMap m) where foldMap = foldMapTM @@ -301,9 +324,9 @@ fdList :: forall m a b. TrieMap m fdList k m = foldMaybe k (lm_nil m) . foldTM (fdList k) (lm_cons m) -foldMaybe :: (a -> b -> b) -> Maybe a -> b -> b -foldMaybe _ Nothing b = b -foldMaybe k (Just a) b = k a b +ftList :: TrieMap m => (a -> Bool) -> ListMap m a -> ListMap m a +ftList f (LM { lm_nil = mnil, lm_cons = mcons }) + = LM { lm_nil = filterMaybe f mnil, lm_cons = mapTM (filterTM f) mcons } {- ************************************************************************ @@ -365,6 +388,7 @@ instance (Eq (Key m), TrieMap m) => TrieMap (GenMap m) where alterTM = xtG foldTM = fdG mapTM = mapG + filterTM = ftG instance (Eq (Key m), TrieMap m) => Foldable (GenMap m) where foldMap = foldMapTM @@ -417,3 +441,13 @@ fdG :: TrieMap m => (a -> b -> b) -> GenMap m a -> b -> b fdG _ EmptyMap = \z -> z fdG k (SingletonMap _ v) = \z -> k v z fdG k (MultiMap m) = foldTM k m + +{-# INLINEABLE ftG #-} +ftG :: TrieMap m => (a -> Bool) -> GenMap m a -> GenMap m a +ftG _ EmptyMap = EmptyMap +ftG f input@(SingletonMap _ v) + | f v = input + | otherwise = EmptyMap +ftG f (MultiMap m) = MultiMap (filterTM f m) + -- we don't have enough information to reconstruct the key to make + -- a SingletonMap ===================================== compiler/GHC/Stg/CSE.hs ===================================== @@ -130,6 +130,8 @@ instance TrieMap StgArgMap where foldTM k m = foldTM k (sam_var m) . foldTM k (sam_lit m) mapTM f (SAM {sam_var = varm, sam_lit = litm}) = SAM { sam_var = mapTM f varm, sam_lit = mapTM f litm } + filterTM f (SAM {sam_var = varm, sam_lit = litm}) = + SAM { sam_var = filterTM f varm, sam_lit = filterTM f litm } newtype ConAppMap a = CAM { un_cam :: DNameEnv (ListMap StgArgMap a) } @@ -141,6 +143,7 @@ instance TrieMap ConAppMap where m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f } foldTM k = un_cam >.> foldTM (foldTM k) mapTM f = un_cam >.> mapTM (mapTM f) >.> CAM + filterTM f = un_cam >.> mapTM (filterTM f) >.> CAM ----------------- -- The CSE Env -- ===================================== compiler/GHC/Tc/Solver/Flatten.hs ===================================== @@ -364,17 +364,18 @@ faster. This doesn't seem quite worth it, yet. Note [flatten_exact_fam_app_fully performance] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Once we've got a flat rhs, we extend the flat-cache to record +Once we've got a flat rhs, we extend the famapp-cache to record the result. Doing so can save lots of work when the same redex shows up more than once. Note that we record the link from the redex all the way to its -*final* value, not just the single step reduction. Interestingly, adding to the -flat-cache for the first reduction *doubles* the allocations -for the T9872a test. However, using the flat-cache in -the later reduction is a similar gain. I (Richard E) don't currently -(Dec '14 nor Nov '20) have any knowledge as to *why* these facts are true. -Perhaps the first use of the flat-cache doesn't add much, because we didn't -need to reduce in the arguments (and instance lookup is similar to cache -lookup). +*final* value, not just the single step reduction. + +If we can reduce the family application right away (the first call +to try_to_reduce), we do *not* add to the cache. There are two possibilities +here: 1) we just read the result from the cache, or 2) we used one type +family instance. In either case, recording the result in the cache doesn't +save much effort the next time around. And adding to the cache here is +actually disastrous: it more than doubles the allocations for T9872a. So +we skip adding to the cache here. -} {-# INLINE flatten_args_tc #-} @@ -765,7 +766,6 @@ flatten_fam_app tc tys -- Can be over-saturated ; flatten_app_ty_args xi1 co1 tys_rest } -- the [TcType] exactly saturate the TyCon --- See Note [flatten_exact_fam_app_fully performance] flatten_exact_fam_app_fully :: TyCon -> [TcType] -> FlatM (Xi, Coercion) flatten_exact_fam_app_fully tc tys = do { checkStackDepth (mkTyConApp tc tys) @@ -773,6 +773,8 @@ flatten_exact_fam_app_fully tc tys -- Step 1. Try to reduce without reducing arguments first. ; result1 <- try_to_reduce tc tys ; case result1 of + -- Don't use `finish`; + -- See Note [flatten_exact_fam_app_fully performance] { Just (co, xi) -> do { (xi2, co2) <- bumpDepth $ flatten_one xi ; return (xi2, co2 `mkTcTransCo` co) } ; Nothing -> @@ -815,7 +817,8 @@ flatten_exact_fam_app_fully tc tys do { result3 <- try_to_reduce tc xis ; case result3 of Just (co, xi) -> finish (homogenise xi co) - Nothing -> return (homogenise reduced (mkTcReflCo role reduced)) + Nothing -> -- we have made no progress at all + return (homogenise reduced (mkTcReflCo role reduced)) where reduced = mkTyConApp tc xis }}}}} where @@ -836,8 +839,7 @@ flatten_exact_fam_app_fully tc tys -- Returned coercion is output ~r input, where r is the role in the FlatM monad try_to_reduce :: TyCon -> [TcType] -> FlatM (Maybe (TcCoercion, TcType)) try_to_reduce tc tys - = do { flavour <- getFlavour - ; result <- liftTcS $ firstJustsM [ lookupFamAppCache flavour tc tys + = do { result <- liftTcS $ firstJustsM [ lookupFamAppCache tc tys , matchFam tc tys ] ; downgrade result } where ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -404,20 +404,14 @@ data InertSet -- Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical , inert_famapp_cache :: FunEqMap (TcCoercion, TcType) - -- If F tys :-> (co, rhs, flav), - -- then co :: rhs ~ F tys - -- all evidence is from instances or Givens - -- (We have no way of "kicking out" from the cache, so putting - -- wanteds here means we can end up solving a Wanted with itself. Bad) - -- - -- Some entries in the cache might have arisen from Wanteds, and - -- so this should be used only for rewriting Wanteds. - -- -- Just a hash-cons cache for use when reducing family applications -- only -- - -- Only nominal equalities end up in here (along with - -- top-level instances) + -- If F tys :-> (co, rhs, flav), + -- then co :: rhs ~N F tys + -- all evidence is from instances or Givens; no coercion holes here + -- (We have no way of "kicking out" from the cache, so putting + -- wanteds here means we can end up solving a Wanted with itself. Bad) , inert_solved_dicts :: DictMap CtEvidence -- All Wanteds, of form ev :: C t1 .. tn @@ -1600,6 +1594,20 @@ kickOutRewritable new_fr new_lhs ics ; unless (n_kicked == 0) $ do { updWorkListTcS (appendWorkList kicked_out) + + -- The famapp-cache contains Given evidence from the inert set. + -- If we're kicking out Givens, we need to remove this evidence + -- from the cache, too. + ; let kicked_given_ev_vars = + [ ev_var | ct <- wl_eqs kicked_out + , CtGiven { ctev_evar = ev_var } <- [ctEvidence ct] ] + ; when (new_fr `eqCanRewriteFR` (Given, NomEq) && + -- if this isn't true, no use looking through the constraints + not (null kicked_given_ev_vars)) $ + do { traceTcS "Given(s) have been kicked out; drop from famapp-cache" + (ppr kicked_given_ev_vars) + ; dropFromFamAppCache (mkVarSet kicked_given_ev_vars) } + ; csTraceTcS $ hang (text "Kick out, lhs =" <+> ppr new_lhs) 2 (vcat [ text "n-kicked =" <+> int n_kicked @@ -2387,17 +2395,6 @@ lookupFamAppInert fam_tc tys = Just (ctEvCoercion ctev, rhs, ctEvFlavourRole ctev) | otherwise = Nothing -lookupFamAppCache :: CtFlavour -> TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType)) -lookupFamAppCache _ fam_tc tys - = do { IS { inert_famapp_cache = famapp_cache } <- getTcSInerts - ; case findFunEq famapp_cache fam_tc tys of - result@(Just (co, ty)) -> - do { traceTcS "famapp_cache hit" (vcat [ ppr (mkTyConApp fam_tc tys) - , ppr ty - , ppr co ]) - ; return result } - Nothing -> return Nothing } - lookupInInerts :: CtLoc -> TcPredType -> TcS (Maybe CtEvidence) -- Is this exact predicate type cached in the solved or canonicals of the InertSet? lookupInInerts loc pty @@ -2423,6 +2420,40 @@ lookupSolvedDict (IS { inert_solved_dicts = solved }) loc cls tys Just ev -> Just ev _ -> Nothing +--------------------------- +lookupFamAppCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType)) +lookupFamAppCache fam_tc tys + = do { IS { inert_famapp_cache = famapp_cache } <- getTcSInerts + ; case findFunEq famapp_cache fam_tc tys of + result@(Just (co, ty)) -> + do { traceTcS "famapp_cache hit" (vcat [ ppr (mkTyConApp fam_tc tys) + , ppr ty + , ppr co ]) + ; return result } + Nothing -> return Nothing } + +extendFamAppCache :: TyCon -> [Type] -> (TcCoercion, TcType) -> TcS () +-- NB: co :: rhs ~ F tys, to match expectations of flattener +extendFamAppCache tc xi_args stuff@(_, ty) + = do { dflags <- getDynFlags + ; when (gopt Opt_FamAppCache dflags) $ + do { traceTcS "extendFamAppCache" (vcat [ ppr tc <+> ppr xi_args + , ppr ty ]) + -- 'co' can be bottom, in the case of derived items + ; updInertTcS $ \ is@(IS { inert_famapp_cache = fc }) -> + is { inert_famapp_cache = insertFunEq fc tc xi_args stuff } } } + +-- Remove entries from the cache whose evidence mentions variables in the +-- supplied set +dropFromFamAppCache :: VarSet -> TcS () +dropFromFamAppCache varset + = do { inerts@(IS { inert_famapp_cache = famapp_cache }) <- getTcSInerts + ; let filtered = filterTcAppMap check famapp_cache + ; setTcSInerts $ inerts { inert_famapp_cache = filtered } } + where + check :: (TcCoercion, TcType) -> Bool + check (co, _) = not (anyFreeVarsOfCo (`elemVarSet` varset) co) + {- ********************************************************************* * * Irreds @@ -2494,18 +2525,15 @@ alterTcApp m tc tys upd = alterDTyConEnv alter_tm m tc alter_tm :: Maybe (ListMap LooseTypeMap a) -> Maybe (ListMap LooseTypeMap a) alter_tm m_elt = Just (alterTM tys upd (m_elt `orElse` emptyTM)) -filterTcAppMap :: (Ct -> Bool) -> TcAppMap Ct -> TcAppMap Ct -filterTcAppMap f m - = mapDTyConEnv do_tm m +filterTcAppMap :: forall a. (a -> Bool) -> TcAppMap a -> TcAppMap a +filterTcAppMap f m = mapMaybeDTyConEnv one_tycon m where - do_tm tm = foldTM insert_mb tm emptyTM - insert_mb ct tm - | f ct = insertTM tys ct tm - | otherwise = tm - where - tys = case ct of - CDictCan { cc_tyargs = tys } -> tys - _ -> pprPanic "filterTcAppMap" (ppr ct) + one_tycon :: ListMap LooseTypeMap a -> Maybe (ListMap LooseTypeMap a) + one_tycon tm + | isEmptyTM filtered_tm = Nothing + | otherwise = Just filtered_tm + where + filtered_tm = filterTM f tm tcAppMapToBag :: TcAppMap a -> Bag a tcAppMapToBag m = foldTcAppMap consBag m emptyBag @@ -3218,17 +3246,6 @@ zonkTyCoVarKind :: TcTyCoVar -> TcS TcTyCoVar zonkTyCoVarKind tv = wrapTcS (TcM.zonkTyCoVarKind tv) ---------------------------- -extendFamAppCache :: TyCon -> [Type] -> (TcCoercion, TcType) -> TcS () --- NB: co :: rhs ~ F tys, to match expectations of flattener -extendFamAppCache tc xi_args stuff@(_, ty) - = do { dflags <- getDynFlags - ; when (gopt Opt_FamAppCache dflags) $ - do { traceTcS "extendFamAppCache" (vcat [ ppr tc <+> ppr xi_args - , ppr ty ]) - -- 'co' can be bottom, in the case of derived items - ; updInertTcS $ \ is@(IS { inert_famapp_cache = fc }) -> - is { inert_famapp_cache = insertFunEq fc tc xi_args stuff } } } - pprKicked :: Int -> SDoc pprKicked 0 = empty pprKicked n = parens (int n <+> text "kicked out") ===================================== compiler/GHC/Types/Unique/DFM.hs ===================================== @@ -15,8 +15,12 @@ is not deterministic. -} {-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveFoldable #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveTraversable #-} +{-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {-# OPTIONS_GHC -Wall #-} @@ -38,6 +42,7 @@ module GHC.Types.Unique.DFM ( adjustUDFM_Directly, alterUDFM, mapUDFM, + mapMaybeUDFM, plusUDFM, plusUDFM_C, lookupUDFM, lookupUDFM_Directly, @@ -121,7 +126,7 @@ data TaggedVal val = TaggedVal val {-# UNPACK #-} !Int -- ^ insertion time - deriving (Data, Functor) + deriving stock (Data, Functor, Foldable, Traversable) taggedFst :: TaggedVal val -> val taggedFst (TaggedVal v _) = v @@ -399,6 +404,10 @@ alterUDFM f (UDFM m i) k = mapUDFM :: (elt1 -> elt2) -> UniqDFM key elt1 -> UniqDFM key elt2 mapUDFM f (UDFM m i) = UDFM (M.map (fmap f) m) i +mapMaybeUDFM :: forall elt1 elt2 key. + (elt1 -> Maybe elt2) -> UniqDFM key elt1 -> UniqDFM key elt2 +mapMaybeUDFM f (UDFM m i) = UDFM (M.mapMaybe (traverse f) m) i + anyUDFM :: (elt -> Bool) -> UniqDFM key elt -> Bool anyUDFM p (UDFM m _i) = M.foldr ((||) . p . taggedFst) False m View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6cf1819f586e5abae39ca19430ad9d0f1fcb94d4...ef7479323a85c965b50fb2dfd71f537872cedab1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6cf1819f586e5abae39ca19430ad9d0f1fcb94d4...ef7479323a85c965b50fb2dfd71f537872cedab1 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 Wed Nov 11 20:07:41 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 15:07:41 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-hadrian-ticky Message-ID: <5fac448d4df90_10ee3ffb98637e04142426e@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-hadrian-ticky 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 Wed Nov 11 20:34:07 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 15:34:07 -0500 Subject: [Git][ghc/ghc][wip/T18566] 488 commits: Put CFG weights into their own module (#17957) Message-ID: <5fac4abf2a041_10ee3ffbac77e2cc1432520@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fca2cb54 by Ben Gamari at 2020-11-11T15:33:25-05:00 Add CALLER_CC pragma - - - - - 20 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Uniques.hs-boot - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1d2305d670e7f3befb849167fca22f91f5105a2...fca2cb54f882608a45247b1cf5e1d55e874e0390 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1d2305d670e7f3befb849167fca22f91f5105a2...fca2cb54f882608a45247b1cf5e1d55e874e0390 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 Wed Nov 11 21:18:29 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:18:29 -0500 Subject: [Git][ghc/ghc][wip/T18566] 2 commits: users-guide: A bit of clean-up in profiling flag documentation Message-ID: <5fac55252e10e_10ee3ffb9807af5c14360fa@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: d9639d62 by Ben Gamari at 2020-11-11T15:56:13-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 44927a55 by Ben Gamari at 2020-11-11T16:17:53-05:00 Add CALLER_CC pragma - - - - - 11 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,221 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = star <|> wildcard <|> char <|> end + where + star = PChar "*" <$ P.string "\\*" + wildcard = do + void $ P.char '*' + PWildcard <$> parseNamePattern + char = PChar <$> P.anyChar <*> parseNamePattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +157,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = gopt Opt_ProfCallerCcs dflags maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +224,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +377,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -216,6 +216,7 @@ data GeneralFlag -- profiling opts | Opt_AutoSccsOnIndividualCafs | Opt_ProfCountEntries + | Opt_ProfCallerCcs -- misc opts | Opt_Pp ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -700,6 +701,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1314,6 +1316,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2948,6 +2951,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -3468,6 +3475,7 @@ fFlagsDeps = [ flagSpec "print-typechecker-elaboration" Opt_PrintTypecheckerElaboration, flagSpec "prof-cafs" Opt_AutoSccsOnIndividualCafs, flagSpec "prof-count-entries" Opt_ProfCountEntries, + flagSpec "prof-callers" Opt_ProfCallerCcs, flagSpec "regs-graph" Opt_RegsGraph, flagSpec "regs-iterative" Opt_RegsIterative, depFlagSpec' "rewrite-rules" Opt_EnableRewriteRules @@ -3787,6 +3795,7 @@ defaultFlags settings Opt_OmitYields, Opt_PrintBindContents, Opt_ProfCountEntries, + Opt_ProfCallerCcs, Opt_SharedImplib, Opt_SimplPreInlining, Opt_VersionMacros @@ -4542,6 +4551,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-prof-callers=`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -332,19 +332,68 @@ Compiler options for profiling Without a :ghc-flag:`-prof` option, your ``SCC``\ s are ignored; so you can compile ``SCC``-laden code without changing it. +.. ghc-flag:: -fno-prof-count-entries + :shortdesc: Do not collect entry counts + :type: dynamic + :reverse: -fprof-count-entries + :category: + + Tells GHC not to collect information about how often functions are + entered at runtime (the "entries" column of the time profile), for + this module. This tends to make the profiled code run faster, and + hence closer to the speed of the unprofiled code, because GHC is + able to optimise more aggressively if it doesn't have to maintain + correct entry counts. This option can be useful if you aren't + interested in the entry counts (for example, if you only intend to + do heap profiling). + + There are a few other profiling-related compilation options. Use them *in addition to* :ghc-flag:`-prof`. These do not have to be used consistently for all modules in a program. +Automatically placing cost-centres +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +GHC has a number of flags for automatically inserting cost-centres into the +compiled program. + +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic :reverse: -fno-prof-auto :category: - *All* bindings not marked INLINE, whether exported or not, top level - or nested, will be given automatic ``SCC`` annotations. Functions - marked INLINE must be given a cost centre manually. + *All* bindings not marked :pragma:`INLINE`, whether exported or not, top + level or nested, will be given automatic ``SCC`` annotations. Functions + marked :pragma:`INLINE` must be given a cost centre manually. .. ghc-flag:: -fprof-auto-top :shortdesc: Auto-add ``SCC``\\ s to all top-level bindings not marked INLINE @@ -356,11 +405,11 @@ for all modules in a program. single: cost centres; automatically inserting GHC will automatically add ``SCC`` annotations for all top-level - bindings not marked INLINE. If you want a cost centre on an INLINE - function, you have to add it manually. + bindings not marked :pragma:`INLINE`. If you want a cost centre on an + :pragma:`INLINE` function, you have to add it manually. .. ghc-flag:: -fprof-auto-exported - :shortdesc: Auto-add ``SCC``\\ s to all exported bindings not marked INLINE + :shortdesc: Auto-add ``SCC``\\ s to all exported bindings not marked :pragma:`INLINE` :type: dynamic :reverse: -fno-prof-auto :category: @@ -369,8 +418,8 @@ for all modules in a program. single: cost centres; automatically inserting GHC will automatically add ``SCC`` annotations for all exported - functions not marked INLINE. If you want a cost centre on an INLINE - function, you have to add it manually. + functions not marked :pragma:`INLINE`. If you want a cost centre on an + :pragma:`INLINE` function, you have to add it manually. .. ghc-flag:: -fprof-auto-calls :shortdesc: Auto-add ``SCC``\\ s to all call sites @@ -392,41 +441,7 @@ for all modules in a program. The costs of all CAFs in a module are usually attributed to one "big" CAF cost-centre. With this option, all CAFs get their own - cost-centre. An “if all else fails” option… - -.. ghc-flag:: -fno-prof-auto - :shortdesc: Disables any previous :ghc-flag:`-fprof-auto`, - :ghc-flag:`-fprof-auto-top`, or :ghc-flag:`-fprof-auto-exported` options. - :type: dynamic - :reverse: -fprof-auto - :category: - - Disables any previous :ghc-flag:`-fprof-auto`, :ghc-flag:`-fprof-auto-top`, or - :ghc-flag:`-fprof-auto-exported` options. - -.. ghc-flag:: -fno-prof-cafs - :shortdesc: Disables any previous :ghc-flag:`-fprof-cafs` option. - :type: dynamic - :reverse: -fprof-cafs - :category: - - Disables any previous :ghc-flag:`-fprof-cafs` option. - -.. ghc-flag:: -fno-prof-count-entries - :shortdesc: Do not collect entry counts - :type: dynamic - :reverse: -fprof-count-entries - :category: - - Tells GHC not to collect information about how often functions are - entered at runtime (the "entries" column of the time profile), for - this module. This tends to make the profiled code run faster, and - hence closer to the speed of the unprofiled code, because GHC is - able to optimise more aggressively if it doesn't have to maintain - correct entry counts. This option can be useful if you aren't - interested in the entry counts (for example, if you only intend to - do heap profiling). - + cost-centre. An "if all else fails" option… .. ghc-flag:: -auto-all :shortdesc: *(deprecated)* Alias for :ghc-flag:`-fprof-auto` View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fca2cb54f882608a45247b1cf5e1d55e874e0390...44927a552865a7d5ebeb1d572dad3336b557ae44 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fca2cb54f882608a45247b1cf5e1d55e874e0390...44927a552865a7d5ebeb1d572dad3336b557ae44 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 Wed Nov 11 21:32:50 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:32:50 -0500 Subject: [Git][ghc/ghc][wip/T18566] Introduce -fprof-callers flag Message-ID: <5fac58823d370_10ee3ffb94cd130414371f9@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 39e987ba by Ben Gamari at 2020-11-11T16:32:20-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 13 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,221 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = star <|> wildcard <|> char <|> end + where + star = PChar "*" <$ P.string "\\*" + wildcard = do + void $ P.char '*' + PWildcard <$> parseNamePattern + char = PChar <$> P.anyChar <*> parseNamePattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +157,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = gopt Opt_ProfCallerCcs dflags maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +224,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +377,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -216,6 +216,7 @@ data GeneralFlag -- profiling opts | Opt_AutoSccsOnIndividualCafs | Opt_ProfCountEntries + | Opt_ProfCallerCcs -- misc opts | Opt_Pp ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -700,6 +701,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1314,6 +1316,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2948,6 +2951,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -3468,6 +3475,7 @@ fFlagsDeps = [ flagSpec "print-typechecker-elaboration" Opt_PrintTypecheckerElaboration, flagSpec "prof-cafs" Opt_AutoSccsOnIndividualCafs, flagSpec "prof-count-entries" Opt_ProfCountEntries, + flagSpec "prof-callers" Opt_ProfCallerCcs, flagSpec "regs-graph" Opt_RegsGraph, flagSpec "regs-iterative" Opt_RegsIterative, depFlagSpec' "rewrite-rules" Opt_EnableRewriteRules @@ -3787,6 +3795,7 @@ defaultFlags settings Opt_OmitYields, Opt_PrintBindContents, Opt_ProfCountEntries, + Opt_ProfCallerCcs, Opt_SharedImplib, Opt_SimplPreInlining, Opt_VersionMacros @@ -4542,6 +4551,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-prof-callers=`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -358,6 +358,33 @@ Automatically placing cost-centres GHC has a number of flags for automatically inserting cost-centres into the compiled program. +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,7 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) + +test('CallerCc1', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.map']) +test('CallerCc2', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=*.map']) +test('CallerCc3', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.con*t']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/39e987baf3b1905c87510119b8a8c7123a913447 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/39e987baf3b1905c87510119b8a8c7123a913447 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 Wed Nov 11 21:43:42 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:43:42 -0500 Subject: [Git][ghc/ghc][wip/fix-hadrian-ticky] 9 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fac5b0e1cbd5_10ee3ffbd56ca5dc143843f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - 31fe9a73 by Ben Gamari at 2020-11-11T16:43:04-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - c34f9e5a by Ben Gamari at 2020-11-11T16:43:04-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 20af5712 by Ben Gamari at 2020-11-11T16:43:35-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - 759fb39e by Ben Gamari at 2020-11-11T16:43:35-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 12 changed files: - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - hadrian/src/Settings/Flavours/Llvm.hs - includes/rts/storage/Closures.h - includes/rts/storage/Heap.h - includes/rts/storage/TSO.h - libraries/base/GHC/Exts.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/Heap.c - rts/linker/PEi386.c - + testsuite/tests/typecheck/should_compile/T17186.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== hadrian/src/Flavour.hs ===================================== @@ -1,17 +1,28 @@ module Flavour ( Flavour (..), werror , DocTargets, DocTarget(..) + , parseFlavour -- * Flavour transformers + , flavourTransformers , addArgs , splitSections, splitSectionsIf , enableThreadSanitizer , enableDebugInfo, enableTickyGhc + , viaLlvmBackend + , enableProfiledGhc + , disableDynamicGhcPrograms ) where import Expression import Data.Set (Set) +import Data.Map (Map) +import qualified Data.Map as M import Packages +import Text.Parsec.Prim as P +import Text.Parsec.Combinator as P +import Text.Parsec.Char as P + -- Please update doc/{flavours.md, user-settings.md} when changing this file. -- | 'Flavour' is a collection of build settings that fully define a GHC build. -- Note the following type semantics: @@ -69,6 +80,49 @@ type DocTargets = Set DocTarget data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) +flavourTransformers :: Map String (Flavour -> Flavour) +flavourTransformers = M.fromList + [ "werror" =: werror + , "debug_info" =: enableDebugInfo + , "ticky_ghc" =: enableTickyGhc + , "split_sections" =: splitSections + , "thread_sanitizer" =: enableThreadSanitizer + , "llvm" =: viaLlvmBackend + , "profiled_ghc" =: enableProfiledGhc + , "no_dynamic_ghc" =: disableDynamicGhcPrograms + ] + where (=:) = (,) + +type Parser = Parsec String () + +parseFlavour :: [Flavour] -- ^ base flavours + -> Map String (Flavour -> Flavour) -- ^ modifiers + -> String + -> Either String Flavour +parseFlavour baseFlavours transformers str = + case P.runParser parser () "" str of + Left perr -> Left $ "error parsing flavour specifier: " ++ show perr + Right f -> Right f + where + parser :: Parser Flavour + parser = do + base <- baseFlavour + transs <- P.many flavourTrans + return $ foldr ($) base transs + + baseFlavour :: Parser Flavour + baseFlavour = + P.choice [ f <$ P.string (name f) + | f <- baseFlavours + ] + + flavourTrans :: Parser (Flavour -> Flavour) + flavourTrans = do + void $ P.char '+' + P.choice [ trans <$ P.string nm + | (nm, trans) <- M.toList transformers + ] + -- | Add arguments to the 'args' of a 'Flavour'. addArgs :: Args -> Flavour -> Flavour addArgs args' fl = fl { args = args fl <> args' } @@ -94,7 +148,13 @@ enableTickyGhc = [ builder (Ghc CompileHs) ? ticky , builder (Ghc LinkHs) ? ticky ] - ticky = arg "-ticky" <> arg "-ticky-allocd" + ticky = mconcat + [ arg "-ticky" + , arg "-ticky-allocd" + -- You generally need STG dumps to interpret ticky profiles + , arg "-ddump-to-file" + , arg "-ddump-stg-final" + ] -- | Transform the input 'Flavour' so as to build with -- @-split-sections@ whenever appropriate. You can @@ -126,3 +186,17 @@ enableThreadSanitizer = addArgs $ mconcat , builder (Cabal Flags) ? arg "thread-sanitizer" , builder RunTest ? arg "--config=have_thread_sanitizer=True" ] + +-- | Use the LLVM backend in stages 1 and later. +viaLlvmBackend :: Flavour -> Flavour +viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm" + +-- | Build the GHC executable with profiling enabled. It is also recommended +-- that you use this with @'dynamicGhcPrograms' = False@ since GHC does not +-- support loading of profiled libraries with the dynamically-linker. +enableProfiledGhc :: Flavour -> Flavour +enableProfiledGhc flavour = flavour { ghcProfiled = True } + +-- | Disable 'dynamicGhcPrograms'. +disableDynamicGhcPrograms :: Flavour -> Flavour +disableDynamicGhcPrograms flavour = flavour { dynamicGhcPrograms = pure False } ===================================== hadrian/src/Settings.hs ===================================== @@ -75,11 +75,9 @@ flavour = do let flavours = hadrianFlavours ++ userFlavours (_settingErrs, tweak) = applySettings kvs - return $ - case filter (\fl -> name fl == flavourName) flavours of - [] -> error $ "Unknown build flavour: " ++ flavourName - [f] -> tweak f - _ -> error $ "Multiple build flavours named " ++ flavourName + case parseFlavour flavours flavourTransformers flavourName of + Left err -> fail err + Right f -> return $ tweak f -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. ===================================== hadrian/src/Settings/Flavours/Llvm.hs ===================================== @@ -5,7 +5,6 @@ module Settings.Flavours.Llvm ( quickLlvmFlavour, ) where -import Expression import Flavour import Settings.Flavours.Benchmark @@ -22,8 +21,5 @@ quickLlvmFlavour = mkLlvmFlavour quickFlavour -- | Turn a flavour into an LLVM flavour mkLlvmFlavour :: Flavour -> Flavour -mkLlvmFlavour flav = flav - { name = name flav ++ "-llvm" - , args = mconcat [ args flav - , builder Ghc ? arg "-fllvm" ] - } +mkLlvmFlavour flav = viaLlvmBackend $ flav + { name = name flav ++ "-llvm" } ===================================== includes/rts/storage/Closures.h ===================================== @@ -63,6 +63,11 @@ typedef struct { -------------------------------------------------------------------------- */ typedef struct { + // If TABLES_NEXT_TO_CODE is defined, then `info` is offset by + // `sizeof(StgInfoTable)` and so points to the `code` field of the + // StgInfoTable! You may want to use `get_itbl` to get the pointer to the + // start of the info table. See + // https://gitlab.haskell.org/ghc/ghc/-/wikis/commentary/rts/storage/heap-objects#tables_next_to_code. const StgInfoTable* info; #if defined(PROFILING) StgProfHeader prof; ===================================== includes/rts/storage/Heap.h ===================================== @@ -16,3 +16,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs , StgClosure *fun, StgClosure **payload, StgWord size); StgWord heap_view_closureSize(StgClosure *closure); + +/* + * Collect the pointers of a closure into the given array. `size` should be + * large enough to hold all collected pointers e.g. + * `heap_view_closureSize(closure)`. Returns the number of pointers collected. + * The caller must ensure that `closure` is not modified (or moved by the GC) + * for the duration of the call to `collect_pointers`. + */ +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[]); ===================================== includes/rts/storage/TSO.h ===================================== @@ -242,10 +242,22 @@ typedef struct StgTSO_ { typedef struct StgStack_ { StgHeader header; - StgWord32 stack_size; // stack size in *words* + + /* Size of the `stack` field in *words*. This is not affected by how much of + * the stack space is used, nor if more stack space is linked to by an + * UNDERFLOW_FRAME. + */ + StgWord32 stack_size; + StgWord8 dirty; // non-zero => dirty StgWord8 marking; // non-zero => someone is currently marking the stack - StgPtr sp; // current stack pointer + + /* Pointer to the "top" of the stack i.e. the most recently written address. + * The stack is filled downwards, so the "top" of the stack starts with `sp + * = stack + stack_size` and is decremented as the stack fills with data. + * See comment on "Invariants" below. + */ + StgPtr sp; StgWord stack[]; } StgStack; ===================================== libraries/base/GHC/Exts.hs ===================================== @@ -72,7 +72,7 @@ module GHC.Exts breakpoint, breakpointCond, -- * Ids with special behaviour - inline, noinline, lazy, oneShot, + inline, noinline, lazy, oneShot, SPEC (..), -- * Running 'RealWorld' state thread runRW#, ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -7,6 +7,9 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeInType #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE UnliftedFFITypes #-} {-| Module : GHC.Exts.Heap @@ -25,6 +28,7 @@ module GHC.Exts.Heap ( , ClosureType(..) , PrimType(..) , HasHeapRep(getClosureData) + , getClosureDataFromHeapRep -- * Info Table types , StgInfoTable(..) @@ -58,7 +62,7 @@ import GHC.Exts.Heap.Utils import Control.Monad import Data.Bits -import GHC.Arr +import Foreign import GHC.Exts import GHC.Int import GHC.Word @@ -66,13 +70,19 @@ import GHC.Word #include "ghcconfig.h" class HasHeapRep (a :: TYPE rep) where - getClosureData :: a -> IO Closure + + -- | Decode a closure to it's heap representation ('GenClosure'). + getClosureData + :: a + -- ^ Closure to decode. + -> IO Closure + -- ^ Heap representation of the closure. instance HasHeapRep (a :: TYPE 'LiftedRep) where - getClosureData = getClosure + getClosureData = getClosureDataFromHeapObject instance HasHeapRep (a :: TYPE 'UnliftedRep) where - getClosureData x = getClosure (unsafeCoerce# x) + getClosureData x = getClosureDataFromHeapObject (unsafeCoerce# x) instance Int# ~ a => HasHeapRep (a :: TYPE 'IntRep) where getClosureData x = return $ @@ -102,49 +112,84 @@ instance Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) where getClosureData x = return $ DoubleClosure { ptipe = PDouble, doubleVal = D# x } --- | This returns the raw representation of the given argument. The second --- component of the triple is the raw words of the closure on the heap, and the --- third component is those words that are actually pointers. Once back in the --- Haskell world, the raw words that hold pointers may be outdated after a --- garbage collector run, but the corresponding values in 'Box's will still --- point to the correct value. -getClosureRaw :: a -> IO (Ptr StgInfoTable, [Word], [Box]) -getClosureRaw x = do +-- | Get the heap representation of a closure _at this moment_, even if it is +-- unevaluated or an indirection or other exotic stuff. Beware when passing +-- something to this function, the same caveats as for +-- 'GHC.Exts.Heap.Closures.asBox' apply. +-- +-- For most use cases 'getClosureData' is an easier to use alternative. +-- +-- Currently TSO and STACK objects will return `UnsupportedClosure`. This is +-- because it is not memory safe to extract TSO and STACK objects (done via +-- `unpackClosure#`). Other threads may be mutating those objects and interleave +-- with reads in `unpackClosure#`. This is particularly problematic with STACKs +-- where pointer values may be overwritten by non-pointer values as the +-- corresponding haskell thread runs. +getClosureDataFromHeapObject + :: a + -- ^ Heap object to decode. + -> IO Closure + -- ^ Heap representation of the closure. +getClosureDataFromHeapObject x = do case unpackClosure# x of --- This is a hack to cover the bootstrap compiler using the old version of --- 'unpackClosure'. The new 'unpackClosure' return values are not merely --- a reordering, so using the old version would not work. - (# iptr, dat, pointers #) -> do - let nelems = (I# (sizeofByteArray# dat)) `div` wORD_SIZE - end = fromIntegral nelems - 1 - rawWds = [W# (indexWordArray# dat i) | I# i <- [0.. end] ] - pelems = I# (sizeofArray# pointers) - ptrList = amap' Box $ Array 0 (pelems - 1) pelems pointers - pure (Ptr iptr, rawWds, ptrList) - --- From GHC.Runtime.Heap.Inspect -amap' :: (t -> b) -> Array Int t -> [b] -amap' f (Array i0 i _ arr#) = map g [0 .. i - i0] - where g (I# i#) = case indexArray# arr# i# of - (# e #) -> f e - --- | This function returns a parsed heap representation of the argument _at --- this moment_, even if it is unevaluated or an indirection or other exotic --- stuff. Beware when passing something to this function, the same caveats as --- for 'asBox' apply. -getClosure :: a -> IO Closure -getClosure x = do - (iptr, wds, pts) <- getClosureRaw x - itbl <- peekItbl iptr - -- The remaining words after the header - let rawWds = drop (closureTypeHeaderSize (tipe itbl)) wds - -- For data args in a pointers then non-pointers closure - -- This is incorrect in non pointers-first setups - -- not sure if that happens - npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) wds +#if MIN_VERSION_ghc_prim(0,5,3) + (# infoTableAddr, heapRep, pointersArray #) -> do +#else + -- This is a hack to cover the bootstrap compiler using the old version + -- of 'unpackClosure'. The new 'unpackClosure' return values are not + -- merely a reordering, so using the old version would not work. + (# infoTableAddr, pointersArray, heapRep #) -> do +#endif + let infoTablePtr = Ptr infoTableAddr + ptrList = [case indexArray# pointersArray i of + (# ptr #) -> Box ptr + | I# i <- [0..(I# (sizeofArray# pointersArray)) - 1] + ] + + infoTable <- peekItbl infoTablePtr + case tipe infoTable of + TSO -> pure $ UnsupportedClosure infoTable + STACK -> pure $ UnsupportedClosure infoTable + _ -> getClosureDataFromHeapRep heapRep infoTablePtr ptrList + +-- | Convert an unpacked heap object, to a `GenClosure b`. The inputs to this +-- function can be generated from a heap object using `unpackClosure#`. +getClosureDataFromHeapRep + :: ByteArray# + -- ^ Heap representation of the closure as returned by `unpackClosure#`. + -- This includes all of the object including the header, info table + -- pointer, pointer data, and non-pointer data. The ByteArray# may be + -- pinned or unpinned. + -> Ptr StgInfoTable + -- ^ Pointer to the `StgInfoTable` of the closure, extracted from the heap + -- representation. The info table must not be movable by GC i.e. must be in + -- pinned or off-heap memory. + -> [b] + -- ^ Pointers in the payload of the closure, extracted from the heap + -- representation as returned by `collect_pointers()` in `Heap.c`. The type + -- `b` is some representation of a pointer e.g. `Any` or `Ptr Any`. + -> IO (GenClosure b) + -- ^ Heap representation of the closure. +getClosureDataFromHeapRep heapRep infoTablePtr pts = do + itbl <- peekItbl infoTablePtr + let -- heapRep as a list of words. + rawHeapWords :: [Word] + rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ] + where + nelems = (I# (sizeofByteArray# heapRep)) `div` wORD_SIZE + end = fromIntegral nelems - 1 + + -- Just the payload of rawHeapWords (no header). + payloadWords :: [Word] + payloadWords = drop (closureTypeHeaderSize (tipe itbl)) rawHeapWords + + -- The non-pointer words in the payload. Only valid for closures with a + -- "pointers first" layout. Not valid for bit field layout. + npts :: [Word] + npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) rawHeapWords case tipe itbl of t | t >= CONSTR && t <= CONSTR_NOCAF -> do - (p, m, n) <- dataConNames iptr + (p, m, n) <- dataConNames infoTablePtr if m == "GHC.ByteCode.Instr" && n == "BreakInfo" then pure $ UnsupportedClosure itbl else pure $ ConstrClosure itbl pts npts p m n @@ -164,9 +209,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to AP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 raw words to AP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ APClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -181,9 +226,9 @@ getClosure x = do unless (length pts >= 1) $ fail "Expected at least 1 ptr argument to PAP" -- We expect at least the arity, n_args, and fun fields - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail "Expected at least 2 raw words to PAP" - let splitWord = rawWds !! 0 + let splitWord = payloadWords !! 0 pure $ PAPClosure itbl #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -218,10 +263,10 @@ getClosure x = do unless (length pts >= 3) $ fail $ "Expected at least 3 ptr argument to BCO, found " ++ show (length pts) - unless (length rawWds >= 4) $ + unless (length payloadWords >= 4) $ fail $ "Expected at least 4 words to BCO, found " - ++ show (length rawWds) - let splitWord = rawWds !! 3 + ++ show (length payloadWords) + let splitWord = payloadWords !! 3 pure $ BCOClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) #if defined(WORDS_BIGENDIAN) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) @@ -230,27 +275,30 @@ getClosure x = do (fromIntegral splitWord) (fromIntegral $ shiftR splitWord (wORD_SIZE_IN_BITS `div` 2)) #endif - (drop 4 rawWds) + (drop 4 payloadWords) ARR_WORDS -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 words to ARR_WORDS, found " - ++ show (length rawWds) - pure $ ArrWordsClosure itbl (head rawWds) (tail rawWds) + ++ show (length payloadWords) + pure $ ArrWordsClosure itbl (head payloadWords) (tail payloadWords) t | t >= MUT_ARR_PTRS_CLEAN && t <= MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 2) $ + unless (length payloadWords >= 2) $ fail $ "Expected at least 2 words to MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ MutArrClosure itbl (rawWds !! 0) (rawWds !! 1) pts + ++ "found " ++ show (length payloadWords) + pure $ MutArrClosure itbl (payloadWords !! 0) (payloadWords !! 1) pts t | t >= SMALL_MUT_ARR_PTRS_CLEAN && t <= SMALL_MUT_ARR_PTRS_FROZEN_CLEAN -> do - unless (length rawWds >= 1) $ + unless (length payloadWords >= 1) $ fail $ "Expected at least 1 word to SMALL_MUT_ARR_PTRS_* " - ++ "found " ++ show (length rawWds) - pure $ SmallMutArrClosure itbl (rawWds !! 0) pts + ++ "found " ++ show (length payloadWords) + pure $ SmallMutArrClosure itbl (payloadWords !! 0) pts - t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> + t | t == MUT_VAR_CLEAN || t == MUT_VAR_DIRTY -> do + unless (length pts >= 1) $ + fail $ "Expected at least 1 words to MUT_VAR, found " + ++ show (length pts) pure $ MutVarClosure itbl (head pts) t | t == MVAR_CLEAN || t == MVAR_DIRTY -> do @@ -260,13 +308,12 @@ getClosure x = do pure $ MVarClosure itbl (pts !! 0) (pts !! 1) (pts !! 2) BLOCKING_QUEUE -> - pure $ OtherClosure itbl pts wds + pure $ OtherClosure itbl pts rawHeapWords -- pure $ BlockingQueueClosure itbl -- (pts !! 0) (pts !! 1) (pts !! 2) (pts !! 3) - -- pure $ OtherClosure itbl pts wds + -- pure $ OtherClosure itbl pts rawHeapWords -- - WEAK -> pure $ WeakClosure { info = itbl ===================================== rts/Heap.c ===================================== @@ -76,23 +76,12 @@ void heap_view_closure_ptrs_in_pap_payload(StgClosure *ptrs[], StgWord *nptrs } } -StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { - ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); - - StgWord size = heap_view_closureSize(closure); - StgWord nptrs = 0; - StgWord i; - - // First collect all pointers here, with the comfortable memory bound - // of the whole closure. Afterwards we know how many pointers are in - // the closure and then we can allocate space on the heap and copy them - // there - StgClosure *ptrs[size]; - +// See Heap.h +StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[size]) { StgClosure **end; - StgClosure **ptr; - const StgInfoTable *info = get_itbl(closure); + StgWord nptrs = 0; + StgWord i; switch (info->type) { case INVALID_OBJECT: @@ -101,6 +90,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { // No pointers case ARR_WORDS: + case STACK: break; // Default layout @@ -123,7 +113,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case FUN_0_2: case FUN_STATIC: end = closure->payload + info->layout.payload.ptrs; - for (ptr = closure->payload; ptr < end; ptr++) { + for (StgClosure **ptr = closure->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -136,7 +126,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { case THUNK_0_2: case THUNK_STATIC: end = ((StgThunk *)closure)->payload + info->layout.payload.ptrs; - for (ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { + for (StgClosure **ptr = ((StgThunk *)closure)->payload; ptr < end; ptr++) { ptrs[nptrs++] = *ptr; } break; @@ -228,6 +218,21 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { break; } + return nptrs; +} + +StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { + ASSERT(LOOKS_LIKE_CLOSURE_PTR(closure)); + + StgWord size = heap_view_closureSize(closure); + + // First collect all pointers here, with the comfortable memory bound + // of the whole closure. Afterwards we know how many pointers are in + // the closure and then we can allocate space on the heap and copy them + // there + StgClosure *ptrs[size]; + StgWord nptrs = collect_pointers(closure, size, ptrs); + size = nptrs + mutArrPtrsCardTableSize(nptrs); StgMutArrPtrs *arr = (StgMutArrPtrs *)allocate(cap, sizeofW(StgMutArrPtrs) + size); @@ -236,7 +241,7 @@ StgMutArrPtrs *heap_view_closurePtrs(Capability *cap, StgClosure *closure) { arr->ptrs = nptrs; arr->size = size; - for (i = 0; ipayload[i] = ptrs[i]; } ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } ===================================== testsuite/tests/typecheck/should_compile/T17186.hs ===================================== @@ -0,0 +1,17 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE TypeFamilyDependencies #-} +{-# LANGUAGE TypeOperators, AllowAmbiguousTypes #-} + +module T17186 where + +-- This test is significantly abbreviated from what was posted; see +-- #16512 for more context. + +type family Dim v + +type family v `OfDim` (n :: Dim v) = r | r -> n + +(!*^) :: Dim m `OfDim` j -> Dim m `OfDim` i +(!*^) = undefined ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,4 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) - +test('T17186', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ea6693a58c02f6d9c3aab795c100bb154c251681...759fb39e012e38903817f8bb860ef3f5ab623b66 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ea6693a58c02f6d9c3aab795c100bb154c251681...759fb39e012e38903817f8bb860ef3f5ab623b66 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 Wed Nov 11 21:46:16 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:46:16 -0500 Subject: [Git][ghc/ghc][wip/T18566] Introduce -fprof-callers flag Message-ID: <5fac5ba86cabf_10eefb1a4f4143902e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 6c9971ad by Ben Gamari at 2020-11-11T16:46:08-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 13 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,222 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = pattern + where + pattern = star <|> wildcard <|> char <|> end + star = PChar '*' <$ P.string "\\*" <*> pattern + wildcard = do + void $ P.char '*' + PWildcard <$> pattern + char = PChar <$> P.anyChar <*> pattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +157,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = gopt Opt_ProfCallerCcs dflags maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +224,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +377,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -216,6 +216,7 @@ data GeneralFlag -- profiling opts | Opt_AutoSccsOnIndividualCafs | Opt_ProfCountEntries + | Opt_ProfCallerCcs -- misc opts | Opt_Pp ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -700,6 +701,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1314,6 +1316,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2948,6 +2951,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -3468,6 +3475,7 @@ fFlagsDeps = [ flagSpec "print-typechecker-elaboration" Opt_PrintTypecheckerElaboration, flagSpec "prof-cafs" Opt_AutoSccsOnIndividualCafs, flagSpec "prof-count-entries" Opt_ProfCountEntries, + flagSpec "prof-callers" Opt_ProfCallerCcs, flagSpec "regs-graph" Opt_RegsGraph, flagSpec "regs-iterative" Opt_RegsIterative, depFlagSpec' "rewrite-rules" Opt_EnableRewriteRules @@ -3787,6 +3795,7 @@ defaultFlags settings Opt_OmitYields, Opt_PrintBindContents, Opt_ProfCountEntries, + Opt_ProfCallerCcs, Opt_SharedImplib, Opt_SimplPreInlining, Opt_VersionMacros @@ -4542,6 +4551,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-prof-callers=`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -358,6 +358,33 @@ Automatically placing cost-centres GHC has a number of flags for automatically inserting cost-centres into the compiled program. +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,7 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) + +test('CallerCc1', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.map']) +test('CallerCc2', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=*.map']) +test('CallerCc3', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.con*t']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6c9971ad2bed5daae38ba29d942efc2d65aedb47 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6c9971ad2bed5daae38ba29d942efc2d65aedb47 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 Wed Nov 11 21:53:27 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:53:27 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/lint-cache Message-ID: <5fac5d575795c_10ee3ffbd5991c2014401ac@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/lint-cache at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/lint-cache 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 Wed Nov 11 21:54:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:54:40 -0500 Subject: [Git][ghc/ghc][wip/lint-cache] gitlab-ci: Cache cabal store in linting job Message-ID: <5fac5da030120_10ee100d35081441760@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/lint-cache at Glasgow Haskell Compiler / GHC Commits: 2aacc7b4 by Ben Gamari at 2020-11-11T16:54:28-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -307,16 +307,20 @@ hadrian-ghc-in-ghci: - .gitlab/ci.sh setup - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache variables: GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache lint-base: extends: .lint-params script: - hadrian/build -c -j stage1:lib:base - hadrian/build -j lint:base - cache: - key: lint ############################################################ # Validation via Pipelines (make) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2aacc7b446557dfdd37ff46cd8c9154ffbe501a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2aacc7b446557dfdd37ff46cd8c9154ffbe501a6 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 Wed Nov 11 21:56:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 16:56:12 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Inline expandSynTyConApp_maybe Message-ID: <5fac5dfc490bc_10ee3ffbae050b601442390@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 093330fa by Ben Gamari at 2020-11-11T16:55:52-05:00 Inline expandSynTyConApp_maybe - - - - - 1 changed file: - compiler/GHC/Core/Type.hs Changes: ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -434,6 +434,9 @@ expandSynTyConApp_maybe tc tys rhs' = substTy (mkTvSubstPrs (tvs `zip` tys)) rhs | otherwise = Nothing +-- Without this INLINE the call to expandSynTyConApp_maybe in coreView +-- will result in an avoidable allocation. +{-# INLINE expandSynTyConApp_maybe #-} {-# INLINE coreFullView #-} coreFullView :: Type -> Type View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/093330fa202fc62fc0da860b97453b2ed0d7c612 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/093330fa202fc62fc0da860b97453b2ed0d7c612 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 Wed Nov 11 22:24:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 17:24:25 -0500 Subject: [Git][ghc/ghc][wip/fix-hadrian-ticky] 4 commits: hadrian: Introduce notion of flavour transformers Message-ID: <5fac64991c083_10ee3ffb8c5ca34c144505f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC Commits: 2c3d502e by Ben Gamari at 2020-11-11T17:17:37-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 99c25b06 by Ben Gamari at 2020-11-11T17:18:35-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - b0e563bf by Ben Gamari at 2020-11-11T17:21:34-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 12430702 by Ben Gamari at 2020-11-11T17:24:01-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 7 changed files: - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs Changes: ===================================== hadrian/doc/flavours.md ===================================== @@ -99,16 +99,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O -O2 - - prof - -O0
-H64m - -O0
-H64m - - -O - -O2 - -O - -O - bench -O
-H64m @@ -166,13 +156,66 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -### LLVM variants +## Flavour transformers -In addition to the above, there are LLVM variants for the flavours `quick`, -`prof`, `perf` and `bench`, available by appending a `-llvm` suffix (i.e., -`quick-llvm` for the LLVM variant of `quick`). These differ only in that there -is an additional `-fllvm` flag in `hsDefault` when the stage0 compiler is GHC. -See `src/Settings/Flavours/Llvm.hs` for details. +Each of the flavours described above is intended as a starting-point for +configuring your GHC build. In addition, Hadrian supports a number of "flavour +transformers" which modify the configuration in various ways. + +These can be appended to the flavour name passed via the `--flavour` +command-line flag, separated by the `+` character. For instance, + +``` +hadrian --flavour=perf+thread_sanitizer +``` + +The supported transformers are listed below: + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
Transformer nameEffect
werrorUse the `-Werror` flag for all stage1+ compilation.
debug_infoEnable production of native debugging information (via GHC/GCC's `-g3`) + during stage1+ compilations.
ticky_ghcCompile the GHC executable with Ticky-Ticky profiler support.
split_sectionsEnable section splitting for all libraries (except for the GHC + library due to the long linking times that this causes).
thread_sanitizerBuild the runtime system with ThreadSanitizer support
llvmUse GHC's LLVM backend (`-fllvm`) for all stage1+ compilation.
profiled_ghcBuild the GHC executable with cost-centre profiling support. + It is that you use this in conjunction with `no_dynamic_ghc` since + GHC does not It is support loading of profiled libraries with the + dynamically-linker.
no_dynamic_ghcLinked GHC against the statically-linked RTS. This causes GHC to + default to loading static rather than dynamic library when, + e.g., loading libraries during TemplateHaskell evaluations.
## Ways @@ -184,7 +227,6 @@ information. The following table lists ways that are built in different flavours Flavour Library ways RTS ways - Profiled GHC stage0 @@ -195,7 +237,7 @@ information. The following table lists ways that are built in different flavours stage1+ - default
perf
prof
devel1
devel2
perf-llvm
prof-llvm + default
perf
prof
devel1
devel2 vanilla vanilla
profiling
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -208,11 +250,9 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - Only in
prof
flavour - Only in
prof
flavour - quick
quick-llvm
quick-validate
quick-debug + quick
quick-validate
quick-debug vanilla vanilla
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -223,8 +263,6 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - No - No quickest
bench @@ -232,7 +270,5 @@ information. The following table lists ways that are built in different flavours vanilla vanilla
threaded vanilla
threaded - No - No ===================================== hadrian/hadrian.cabal ===================================== @@ -106,13 +106,10 @@ executable hadrian , Settings.Flavours.Benchmark , Settings.Flavours.Development , Settings.Flavours.GhcInGhci - , Settings.Flavours.Llvm , Settings.Flavours.Performance - , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.QuickCross , Settings.Flavours.Quickest - , Settings.Flavours.ThreadSanitizer , Settings.Flavours.Validate , Settings.Packages , Settings.Parser ===================================== hadrian/src/Flavour.hs ===================================== @@ -1,17 +1,28 @@ module Flavour ( Flavour (..), werror , DocTargets, DocTarget(..) + , parseFlavour -- * Flavour transformers + , flavourTransformers , addArgs , splitSections, splitSectionsIf , enableThreadSanitizer , enableDebugInfo, enableTickyGhc + , viaLlvmBackend + , enableProfiledGhc + , disableDynamicGhcPrograms ) where import Expression import Data.Set (Set) +import Data.Map (Map) +import qualified Data.Map as M import Packages +import Text.Parsec.Prim as P +import Text.Parsec.Combinator as P +import Text.Parsec.Char as P + -- Please update doc/{flavours.md, user-settings.md} when changing this file. -- | 'Flavour' is a collection of build settings that fully define a GHC build. -- Note the following type semantics: @@ -69,6 +80,49 @@ type DocTargets = Set DocTarget data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) +flavourTransformers :: Map String (Flavour -> Flavour) +flavourTransformers = M.fromList + [ "werror" =: werror + , "debug_info" =: enableDebugInfo + , "ticky_ghc" =: enableTickyGhc + , "split_sections" =: splitSections + , "thread_sanitizer" =: enableThreadSanitizer + , "llvm" =: viaLlvmBackend + , "profiled_ghc" =: enableProfiledGhc + , "no_dynamic_ghc" =: disableDynamicGhcPrograms + ] + where (=:) = (,) + +type Parser = Parsec String () + +parseFlavour :: [Flavour] -- ^ base flavours + -> Map String (Flavour -> Flavour) -- ^ modifiers + -> String + -> Either String Flavour +parseFlavour baseFlavours transformers str = + case P.runParser parser () "" str of + Left perr -> Left $ "error parsing flavour specifier: " ++ show perr + Right f -> Right f + where + parser :: Parser Flavour + parser = do + base <- baseFlavour + transs <- P.many flavourTrans + return $ foldr ($) base transs + + baseFlavour :: Parser Flavour + baseFlavour = + P.choice [ f <$ P.string (name f) + | f <- baseFlavours + ] + + flavourTrans :: Parser (Flavour -> Flavour) + flavourTrans = do + void $ P.char '+' + P.choice [ trans <$ P.string nm + | (nm, trans) <- M.toList transformers + ] + -- | Add arguments to the 'args' of a 'Flavour'. addArgs :: Args -> Flavour -> Flavour addArgs args' fl = fl { args = args fl <> args' } @@ -132,3 +186,17 @@ enableThreadSanitizer = addArgs $ mconcat , builder (Cabal Flags) ? arg "thread-sanitizer" , builder RunTest ? arg "--config=have_thread_sanitizer=True" ] + +-- | Use the LLVM backend in stages 1 and later. +viaLlvmBackend :: Flavour -> Flavour +viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm" + +-- | Build the GHC executable with profiling enabled. It is also recommended +-- that you use this with @'dynamicGhcPrograms' = False@ since GHC does not +-- support loading of profiled libraries with the dynamically-linker. +enableProfiledGhc :: Flavour -> Flavour +enableProfiledGhc flavour = flavour { ghcProfiled = True } + +-- | Disable 'dynamicGhcPrograms'. +disableDynamicGhcPrograms :: Flavour -> Flavour +disableDynamicGhcPrograms flavour = flavour { dynamicGhcPrograms = pure False } ===================================== hadrian/src/Settings.hs ===================================== @@ -15,13 +15,10 @@ import {-# SOURCE #-} Settings.Default import Settings.Flavours.Benchmark import Settings.Flavours.Development import Settings.Flavours.GhcInGhci -import Settings.Flavours.Llvm import Settings.Flavours.Performance -import Settings.Flavours.Profiled import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Flavours.QuickCross -import Settings.Flavours.ThreadSanitizer import Settings.Flavours.Validate import Control.Monad.Except @@ -75,11 +72,9 @@ flavour = do let flavours = hadrianFlavours ++ userFlavours (_settingErrs, tweak) = applySettings kvs - return $ - case filter (\fl -> name fl == flavourName) flavours of - [] -> error $ "Unknown build flavour: " ++ flavourName - [f] -> tweak f - _ -> error $ "Multiple build flavours named " ++ flavourName + case parseFlavour flavours flavourTransformers flavourName of + Left err -> fail err + Right f -> return $ tweak f -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. ===================================== hadrian/src/Settings/Flavours/Llvm.hs deleted ===================================== @@ -1,29 +0,0 @@ -module Settings.Flavours.Llvm ( - benchmarkLlvmFlavour, - performanceLlvmFlavour, - profiledLlvmFlavour, - quickLlvmFlavour, -) where - -import Expression -import Flavour - -import Settings.Flavours.Benchmark -import Settings.Flavours.Performance -import Settings.Flavours.Profiled -import Settings.Flavours.Quick - --- Please update doc/flavours.md when changing this file. -benchmarkLlvmFlavour, performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour :: Flavour -benchmarkLlvmFlavour = mkLlvmFlavour benchmarkFlavour -performanceLlvmFlavour = mkLlvmFlavour performanceFlavour -profiledLlvmFlavour = mkLlvmFlavour profiledFlavour -quickLlvmFlavour = mkLlvmFlavour quickFlavour - --- | Turn a flavour into an LLVM flavour -mkLlvmFlavour :: Flavour -> Flavour -mkLlvmFlavour flav = flav - { name = name flav ++ "-llvm" - , args = mconcat [ args flav - , builder Ghc ? arg "-fllvm" ] - } ===================================== hadrian/src/Settings/Flavours/Profiled.hs deleted ===================================== @@ -1,22 +0,0 @@ -module Settings.Flavours.Profiled (profiledFlavour) where - -import Expression -import Flavour -import {-# SOURCE #-} Settings.Default - --- Please update doc/flavours.md when changing this file. -profiledFlavour :: Flavour -profiledFlavour = defaultFlavour - { name = "prof" - , args = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs - , ghcProfiled = True - , dynamicGhcPrograms = pure False } - -profiledArgs :: Args -profiledArgs = sourceArgs SourceArgs - { hsDefault = mconcat - [ pure ["-O0", "-H64m"] - ] - , hsLibrary = notStage0 ? arg "-O" - , hsCompiler = mconcat [stage0 ? arg "-O2", notStage0 ? arg "-O"] - , hsGhc = arg "-O" } ===================================== hadrian/src/Settings/Flavours/ThreadSanitizer.hs deleted ===================================== @@ -1,9 +0,0 @@ -module Settings.Flavours.ThreadSanitizer (threadSanitizerFlavour) where - -import Flavour -import Settings.Flavours.Validate - -threadSanitizerFlavour :: Flavour -threadSanitizerFlavour = - enableThreadSanitizer (validateFlavour - { name = "thread-sanitizer" }) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/759fb39e012e38903817f8bb860ef3f5ab623b66...1243070298a33adcb3d53987c57c0d93c0148c5d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/759fb39e012e38903817f8bb860ef3f5ab623b66...1243070298a33adcb3d53987c57c0d93c0148c5d 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 Wed Nov 11 22:27:21 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 17:27:21 -0500 Subject: [Git][ghc/ghc][wip/T18566] Introduce -fprof-callers flag Message-ID: <5fac6549a03e_10eefc8b50414458fa@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 5b3dd47f by Ben Gamari at 2020-11-11T17:27:12-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 13 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,222 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = pattern + where + pattern = star <|> wildcard <|> char <|> end + star = PChar '*' <$ P.string "\\*" <*> pattern + wildcard = do + void $ P.char '*' + PWildcard <$> pattern + char = PChar <$> P.anyChar <*> pattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +157,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = gopt Opt_ProfCallerCcs dflags maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +224,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +377,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. @@ -510,6 +518,9 @@ doCorePass CoreDoSpecialising = {-# SCC "Specialise" #-} doCorePass CoreDoSpecConstr = {-# SCC "SpecConstr" #-} specConstrProgram +doCorePass CoreAddCallerCcs = {-# SCC "AddCallerCcs" #-} + addCallerCostCentres + doCorePass CoreDoPrintCore = observe printCore doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat doCorePass CoreDoNothing = return ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -216,6 +216,7 @@ data GeneralFlag -- profiling opts | Opt_AutoSccsOnIndividualCafs | Opt_ProfCountEntries + | Opt_ProfCallerCcs -- misc opts | Opt_Pp ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -700,6 +701,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1314,6 +1316,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2948,6 +2951,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -3468,6 +3475,7 @@ fFlagsDeps = [ flagSpec "print-typechecker-elaboration" Opt_PrintTypecheckerElaboration, flagSpec "prof-cafs" Opt_AutoSccsOnIndividualCafs, flagSpec "prof-count-entries" Opt_ProfCountEntries, + flagSpec "prof-callers" Opt_ProfCallerCcs, flagSpec "regs-graph" Opt_RegsGraph, flagSpec "regs-iterative" Opt_RegsIterative, depFlagSpec' "rewrite-rules" Opt_EnableRewriteRules @@ -3787,6 +3795,7 @@ defaultFlags settings Opt_OmitYields, Opt_PrintBindContents, Opt_ProfCountEntries, + Opt_ProfCallerCcs, Opt_SharedImplib, Opt_SimplPreInlining, Opt_VersionMacros @@ -4542,6 +4551,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-prof-callers=`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -358,6 +358,33 @@ Automatically placing cost-centres GHC has a number of flags for automatically inserting cost-centres into the compiled program. +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,7 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) + +test('CallerCc1', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.map']) +test('CallerCc2', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=*.map']) +test('CallerCc3', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.con*t']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5b3dd47ff32cc33bfae101dd3a6e372e07768e1a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5b3dd47ff32cc33bfae101dd3a6e372e07768e1a 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 Wed Nov 11 22:33:22 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 17:33:22 -0500 Subject: [Git][ghc/ghc][wip/fix-hadrian-ticky] hadrian: Drop redundant flavour definitions Message-ID: <5fac66b2ac004_10ee3ffbad1f122c14479f6@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC Commits: 2f5c8f47 by Ben Gamari at 2020-11-11T17:33:16-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 6 changed files: - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs Changes: ===================================== hadrian/doc/flavours.md ===================================== @@ -99,16 +99,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O -O2 - - prof - -O0
-H64m - -O0
-H64m - - -O - -O2 - -O - -O - bench -O
-H64m @@ -166,14 +156,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -### LLVM variants - -In addition to the above, there are LLVM variants for the flavours `quick`, -`prof`, `perf` and `bench`, available by appending a `-llvm` suffix (i.e., -`quick-llvm` for the LLVM variant of `quick`). These differ only in that there -is an additional `-fllvm` flag in `hsDefault` when the stage0 compiler is GHC. -See `src/Settings/Flavours/Llvm.hs` for details. - ## Flavour transformers Each of the flavours described above is intended as a starting-point for @@ -245,7 +227,6 @@ information. The following table lists ways that are built in different flavours Flavour Library ways RTS ways - Profiled GHC stage0 @@ -256,7 +237,7 @@ information. The following table lists ways that are built in different flavours stage1+ - default
perf
prof
devel1
devel2
perf-llvm
prof-llvm + default
perf
prof
devel1
devel2 vanilla vanilla
profiling
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -269,11 +250,9 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - Only in
prof
flavour - Only in
prof
flavour - quick
quick-llvm
quick-validate
quick-debug + quick
quick-validate
quick-debug vanilla vanilla
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -284,8 +263,6 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - No - No quickest
bench @@ -293,7 +270,5 @@ information. The following table lists ways that are built in different flavours vanilla vanilla
threaded vanilla
threaded - No - No ===================================== hadrian/hadrian.cabal ===================================== @@ -106,13 +106,10 @@ executable hadrian , Settings.Flavours.Benchmark , Settings.Flavours.Development , Settings.Flavours.GhcInGhci - , Settings.Flavours.Llvm , Settings.Flavours.Performance - , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.QuickCross , Settings.Flavours.Quickest - , Settings.Flavours.ThreadSanitizer , Settings.Flavours.Validate , Settings.Packages , Settings.Parser ===================================== hadrian/src/Settings.hs ===================================== @@ -15,13 +15,10 @@ import {-# SOURCE #-} Settings.Default import Settings.Flavours.Benchmark import Settings.Flavours.Development import Settings.Flavours.GhcInGhci -import Settings.Flavours.Llvm import Settings.Flavours.Performance -import Settings.Flavours.Profiled import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Flavours.QuickCross -import Settings.Flavours.ThreadSanitizer import Settings.Flavours.Validate import Control.Monad.Except @@ -54,13 +51,11 @@ stagePackages stage = do hadrianFlavours :: [Flavour] hadrianFlavours = [ benchmarkFlavour, defaultFlavour, developmentFlavour Stage1 - , developmentFlavour Stage2, performanceFlavour, profiledFlavour + , developmentFlavour Stage2, performanceFlavour , quickFlavour, quickValidateFlavour, quickDebugFlavour , quickestFlavour - , quickCrossFlavour, benchmarkLlvmFlavour - , performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour - , ghcInGhciFlavour, validateFlavour, slowValidateFlavour - , threadSanitizerFlavour ] + , quickCrossFlavour, + , ghcInGhciFlavour, validateFlavour, slowValidateFlavour ] -- | This action looks up a flavour with the name given on the -- command line with @--flavour@, defaulting to 'userDefaultFlavour' ===================================== hadrian/src/Settings/Flavours/Llvm.hs deleted ===================================== @@ -1,25 +0,0 @@ -module Settings.Flavours.Llvm ( - benchmarkLlvmFlavour, - performanceLlvmFlavour, - profiledLlvmFlavour, - quickLlvmFlavour, -) where - -import Flavour - -import Settings.Flavours.Benchmark -import Settings.Flavours.Performance -import Settings.Flavours.Profiled -import Settings.Flavours.Quick - --- Please update doc/flavours.md when changing this file. -benchmarkLlvmFlavour, performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour :: Flavour -benchmarkLlvmFlavour = mkLlvmFlavour benchmarkFlavour -performanceLlvmFlavour = mkLlvmFlavour performanceFlavour -profiledLlvmFlavour = mkLlvmFlavour profiledFlavour -quickLlvmFlavour = mkLlvmFlavour quickFlavour - --- | Turn a flavour into an LLVM flavour -mkLlvmFlavour :: Flavour -> Flavour -mkLlvmFlavour flav = viaLlvmBackend $ flav - { name = name flav ++ "-llvm" } ===================================== hadrian/src/Settings/Flavours/Profiled.hs deleted ===================================== @@ -1,22 +0,0 @@ -module Settings.Flavours.Profiled (profiledFlavour) where - -import Expression -import Flavour -import {-# SOURCE #-} Settings.Default - --- Please update doc/flavours.md when changing this file. -profiledFlavour :: Flavour -profiledFlavour = defaultFlavour - { name = "prof" - , args = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs - , ghcProfiled = True - , dynamicGhcPrograms = pure False } - -profiledArgs :: Args -profiledArgs = sourceArgs SourceArgs - { hsDefault = mconcat - [ pure ["-O0", "-H64m"] - ] - , hsLibrary = notStage0 ? arg "-O" - , hsCompiler = mconcat [stage0 ? arg "-O2", notStage0 ? arg "-O"] - , hsGhc = arg "-O" } ===================================== hadrian/src/Settings/Flavours/ThreadSanitizer.hs deleted ===================================== @@ -1,9 +0,0 @@ -module Settings.Flavours.ThreadSanitizer (threadSanitizerFlavour) where - -import Flavour -import Settings.Flavours.Validate - -threadSanitizerFlavour :: Flavour -threadSanitizerFlavour = - enableThreadSanitizer (validateFlavour - { name = "thread-sanitizer" }) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2f5c8f47a9bf6070b008ab44104f178dbe768662 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2f5c8f47a9bf6070b008ab44104f178dbe768662 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 Wed Nov 11 22:49:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 17:49:40 -0500 Subject: [Git][ghc/ghc][wip/fix-hadrian-ticky] hadrian: Drop redundant flavour definitions Message-ID: <5fac6a8430ac4_10ee3ffb97acfda014491b5@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC Commits: 7a107185 by Ben Gamari at 2020-11-11T17:49:33-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 6 changed files: - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs Changes: ===================================== hadrian/doc/flavours.md ===================================== @@ -99,16 +99,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O -O2 - - prof - -O0
-H64m - -O0
-H64m - - -O - -O2 - -O - -O - bench -O
-H64m @@ -166,14 +156,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -### LLVM variants - -In addition to the above, there are LLVM variants for the flavours `quick`, -`prof`, `perf` and `bench`, available by appending a `-llvm` suffix (i.e., -`quick-llvm` for the LLVM variant of `quick`). These differ only in that there -is an additional `-fllvm` flag in `hsDefault` when the stage0 compiler is GHC. -See `src/Settings/Flavours/Llvm.hs` for details. - ## Flavour transformers Each of the flavours described above is intended as a starting-point for @@ -245,7 +227,6 @@ information. The following table lists ways that are built in different flavours Flavour Library ways RTS ways - Profiled GHC stage0 @@ -256,7 +237,7 @@ information. The following table lists ways that are built in different flavours stage1+ - default
perf
prof
devel1
devel2
perf-llvm
prof-llvm + default
perf
prof
devel1
devel2 vanilla vanilla
profiling
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -269,11 +250,9 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - Only in
prof
flavour - Only in
prof
flavour - quick
quick-llvm
quick-validate
quick-debug + quick
quick-validate
quick-debug vanilla vanilla
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -284,8 +263,6 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - No - No quickest
bench @@ -293,7 +270,5 @@ information. The following table lists ways that are built in different flavours vanilla vanilla
threaded vanilla
threaded - No - No ===================================== hadrian/hadrian.cabal ===================================== @@ -106,13 +106,10 @@ executable hadrian , Settings.Flavours.Benchmark , Settings.Flavours.Development , Settings.Flavours.GhcInGhci - , Settings.Flavours.Llvm , Settings.Flavours.Performance - , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.QuickCross , Settings.Flavours.Quickest - , Settings.Flavours.ThreadSanitizer , Settings.Flavours.Validate , Settings.Packages , Settings.Parser ===================================== hadrian/src/Settings.hs ===================================== @@ -15,13 +15,10 @@ import {-# SOURCE #-} Settings.Default import Settings.Flavours.Benchmark import Settings.Flavours.Development import Settings.Flavours.GhcInGhci -import Settings.Flavours.Llvm import Settings.Flavours.Performance -import Settings.Flavours.Profiled import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Flavours.QuickCross -import Settings.Flavours.ThreadSanitizer import Settings.Flavours.Validate import Control.Monad.Except @@ -54,13 +51,11 @@ stagePackages stage = do hadrianFlavours :: [Flavour] hadrianFlavours = [ benchmarkFlavour, defaultFlavour, developmentFlavour Stage1 - , developmentFlavour Stage2, performanceFlavour, profiledFlavour + , developmentFlavour Stage2, performanceFlavour , quickFlavour, quickValidateFlavour, quickDebugFlavour , quickestFlavour - , quickCrossFlavour, benchmarkLlvmFlavour - , performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour - , ghcInGhciFlavour, validateFlavour, slowValidateFlavour - , threadSanitizerFlavour ] + , quickCrossFlavour + , ghcInGhciFlavour, validateFlavour, slowValidateFlavour ] -- | This action looks up a flavour with the name given on the -- command line with @--flavour@, defaulting to 'userDefaultFlavour' ===================================== hadrian/src/Settings/Flavours/Llvm.hs deleted ===================================== @@ -1,25 +0,0 @@ -module Settings.Flavours.Llvm ( - benchmarkLlvmFlavour, - performanceLlvmFlavour, - profiledLlvmFlavour, - quickLlvmFlavour, -) where - -import Flavour - -import Settings.Flavours.Benchmark -import Settings.Flavours.Performance -import Settings.Flavours.Profiled -import Settings.Flavours.Quick - --- Please update doc/flavours.md when changing this file. -benchmarkLlvmFlavour, performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour :: Flavour -benchmarkLlvmFlavour = mkLlvmFlavour benchmarkFlavour -performanceLlvmFlavour = mkLlvmFlavour performanceFlavour -profiledLlvmFlavour = mkLlvmFlavour profiledFlavour -quickLlvmFlavour = mkLlvmFlavour quickFlavour - --- | Turn a flavour into an LLVM flavour -mkLlvmFlavour :: Flavour -> Flavour -mkLlvmFlavour flav = viaLlvmBackend $ flav - { name = name flav ++ "-llvm" } ===================================== hadrian/src/Settings/Flavours/Profiled.hs deleted ===================================== @@ -1,22 +0,0 @@ -module Settings.Flavours.Profiled (profiledFlavour) where - -import Expression -import Flavour -import {-# SOURCE #-} Settings.Default - --- Please update doc/flavours.md when changing this file. -profiledFlavour :: Flavour -profiledFlavour = defaultFlavour - { name = "prof" - , args = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs - , ghcProfiled = True - , dynamicGhcPrograms = pure False } - -profiledArgs :: Args -profiledArgs = sourceArgs SourceArgs - { hsDefault = mconcat - [ pure ["-O0", "-H64m"] - ] - , hsLibrary = notStage0 ? arg "-O" - , hsCompiler = mconcat [stage0 ? arg "-O2", notStage0 ? arg "-O"] - , hsGhc = arg "-O" } ===================================== hadrian/src/Settings/Flavours/ThreadSanitizer.hs deleted ===================================== @@ -1,9 +0,0 @@ -module Settings.Flavours.ThreadSanitizer (threadSanitizerFlavour) where - -import Flavour -import Settings.Flavours.Validate - -threadSanitizerFlavour :: Flavour -threadSanitizerFlavour = - enableThreadSanitizer (validateFlavour - { name = "thread-sanitizer" }) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7a1071855094b4578917a1eb53f7b4417ef0a2c3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7a1071855094b4578917a1eb53f7b4417ef0a2c3 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 Wed Nov 11 23:08:28 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 18:08:28 -0500 Subject: [Git][ghc/ghc][wip/T18566] Fix it Message-ID: <5fac6eec5f6db_10ee3ffbae01abc814517ac@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: eefb84cc by GHC GitLab CI at 2020-11-11T23:05:27+00:00 Fix it - - - - - 9 changed files: - compiler/GHC/Core/Opt/CallerCC.hs - docs/users_guide/profiling.rst - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout - testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -72,7 +72,8 @@ doExpr :: Env -> CoreExpr -> M CoreExpr doExpr env e@(Var v) | needsCallSiteCostCentre env v = do let nameDoc :: SDoc - nameDoc = hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + nameDoc = withUserStyle alwaysQualify DefaultDepth $ + hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) ccName :: CcName ccName = mkFastString $ showSDoc (dflags env) nameDoc ===================================== docs/users_guide/profiling.rst ===================================== @@ -364,6 +364,11 @@ compiled program. :category: Automatically enclose all occurrences of the named function in an ``SCC``. + Note that these cost-centres are added late in compilation (after + simplification) and consequently the names may be slightly different than + they appear in the source program (e.g. a call to ``f`` may inlined with + its wrapper, resulting in an occurrence of its worker, ``$wf``). + In addition to plain module-qualified names (e.g. ``Data.List.map``), ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard symbol: ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample ===================================== @@ -0,0 +1,79 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc1 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (58 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +clause.clause' Main Main.hs:(63,12)-(65,57) 29.3 37.5 +insert Main Main.hs:(108,1)-(112,8) 27.6 1.7 +disin Main Main.hs:(74,1)-(83,11) 22.4 49.5 +disin.dp Main Main.hs:80:3-14 5.2 0.0 +conjunct Main Main.hs:(70,1)-(71,18) 5.2 0.0 +unicl Main Main.hs:(176,1)-(180,36) 3.4 1.1 +tautclause Main Main.hs:173:1-49 3.4 3.7 +disin.dq Main Main.hs:81:3-14 3.4 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 0.0 2.6 +split.split' Main Main.hs:(165,11)-(166,28) 0.0 2.3 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 22.4 49.5 36.2 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 5.2 0.0 5.2 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 5.2 0.0 5.2 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 3.4 0.0 3.4 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 0.0 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 0.0 2.3 0.0 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 3.4 1.1 63.8 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 0.0 2.6 60.3 46.9 + tautclause Main Main.hs:173:1-49 295 37422 3.4 3.7 3.4 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 56.9 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 56.9 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 29.3 37.5 56.9 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 27.6 1.7 27.6 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample ===================================== @@ -0,0 +1,78 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc2 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (59 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 32.2 49.5 +insert Main Main.hs:(108,1)-(112,8) 27.1 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 25.4 37.5 +tautclause Main Main.hs:173:1-49 3.4 3.7 +split.split' Main Main.hs:(165,11)-(166,28) 3.4 2.3 +disin.dq Main Main.hs:81:3-14 3.4 0.0 +conjunct Main Main.hs:(70,1)-(71,18) 3.4 0.0 +clause Main Main.hs:(61,1)-(65,57) 1.7 1.4 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 0.0 2.6 +unicl Main Main.hs:(176,1)-(180,36) 0.0 1.1 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 32.2 49.5 39.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 3.4 0.0 3.4 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 0.0 0.0 0.0 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 3.4 0.0 3.4 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.4 2.3 3.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 0.0 1.1 57.6 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 0.0 2.6 57.6 46.9 + tautclause Main Main.hs:173:1-49 295 37422 3.4 3.7 3.4 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 54.2 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 1.7 1.4 54.2 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 25.4 37.5 52.5 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 27.1 1.7 27.1 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample ===================================== @@ -0,0 +1,79 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc3 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (55 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 27.3 49.5 +insert Main Main.hs:(108,1)-(112,8) 25.5 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 18.2 37.5 +conjunct Main Main.hs:(70,1)-(71,18) 10.9 0.0 +tautclause Main Main.hs:173:1-49 9.1 3.7 +unicl.unicl'.cp Main Main.hs:180:24-36 1.8 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 1.8 2.6 +unicl Main Main.hs:(176,1)-(180,36) 1.8 1.1 +split.split' Main Main.hs:(165,11)-(166,28) 1.8 2.3 +disin.dq Main Main.hs:81:3-14 1.8 0.0 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 27.3 49.5 40.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 10.9 0.0 10.9 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 0.0 0.0 0.0 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 1.8 0.0 1.8 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 1.8 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 1.8 2.3 1.8 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 1.8 1.1 58.2 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 1.8 2.6 56.4 46.9 + tautclause Main Main.hs:173:1-49 295 37422 9.1 3.7 9.1 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 1.8 0.0 45.5 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 43.6 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 18.2 37.5 43.6 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 25.5 1.7 25.5 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -1,7 +1,19 @@ setTestOpts(req_profiling) setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) setTestOpts(only_ways(prof_ways)) +setTestOpts(extra_files(['Main.hs'])) +setTestOpts(extra_run_opts('7')) -test('CallerCc1', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.map']) -test('CallerCc2', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=*.map']) -test('CallerCc3', extra_files(['Main.hs']), compile_and_run, ['-fprof-callers=Data.List.con*t']) +# N.B. Main.hs is stolen from heapprof001. + +test('CallerCc1', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=*.concat -O0']) + +test('CallerCc2', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.concat -O0']) + +test('CallerCc3', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.con*at -O0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eefb84cc147a291cfeb15b7011d90e883200dd09 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eefb84cc147a291cfeb15b7011d90e883200dd09 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 Wed Nov 11 23:09:12 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 11 Nov 2020 18:09:12 -0500 Subject: =?UTF-8?Q?[Git][ghc/ghc][wip/cfuneqcan-refactor]_2_commits:_Addres?= =?UTF-8?Q?s_points_from_H=C3=A9cate.?= Message-ID: <5fac6f18ee7d8_10ee3ffbae01abc81452748@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: b90a27ce by Richard Eisenberg at 2020-11-11T13:00:33-05:00 Address points from Hécate. - - - - - 78425e2e by Richard Eisenberg at 2020-11-11T18:01:57-05:00 Reviews on GitLab - - - - - 14 changed files: - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/Solver/Interact.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -2659,7 +2659,8 @@ FamInstEnv, and so lives here. Note [simplifyArgsWorker] ~~~~~~~~~~~~~~~~~~~~~~~~~ -Invariant (F2) of Note [Flattening] says that flattening is homogeneous. +Invariant (F2) of Note [Flattening] in GHC.Tc.Solver.Flatten says that +flattening is homogeneous. This causes some trouble when flattening a function applied to a telescope of arguments, perhaps with dependency. For example, suppose ===================================== compiler/GHC/Core/FamInstEnv.hs ===================================== @@ -428,7 +428,8 @@ Here is how we do it: apart(target, pattern) = not (unify(flatten(target), pattern)) where flatten (implemented in flattenTys, below) converts all type-family -applications into fresh variables. (See Note [Flattening] in GHC.Core.Unify.) +applications into fresh variables. (See +Note [Flattening type-family applications when matching instances] in GHC.Core.Unify.) Note [Compatibility] ~~~~~~~~~~~~~~~~~~~~ @@ -1176,7 +1177,8 @@ findBranch branches target_tys , cab_incomps = incomps }) = branch in_scope = mkInScopeSet (unionVarSets $ map (tyCoVarsOfTypes . coAxBranchLHS) incomps) - -- See Note [Flattening] in GHC.Core.Unify + -- See Note [Flattening type-family applications when matching instances] + -- in GHC.Core.Unify flattened_target = flattenTys in_scope target_tys in case tcMatchTys tpl_lhs target_tys of Just subst -- matching worked. now, check for apartness. @@ -1193,11 +1195,11 @@ findBranch branches target_tys -- (POPL '14). This should be used when determining if an equation -- ('CoAxBranch') of a closed type family can be used to reduce a certain target -- type family application. -apartnessCheck :: [Type] -- ^ /flattened/ target arguments. Make sure - -- they're flattened! See Note [Flattening] - -- in GHC.Core.Unify - -- (NB: This "flat" is a different - -- "flat" than is used in GHC.Tc.Solver.Flatten.) +apartnessCheck :: [Type] + -- ^ /flattened/ target arguments. Make sure they're flattened! See + -- Note [Flattening type-family applications when matching instances] + -- in GHC.Core.Unify. (NB: This "flat" is a different + -- "flat" than is used in GHC.Tc.Solver.Flatten.) -> CoAxBranch -- ^ the candidate equation we wish to use -- Precondition: this matches the target -> Bool -- ^ True <=> equation can fire ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -840,6 +840,8 @@ lookupInstEnv' ie vis_mods cls tys flattened_tys = flattenTys in_scope tys in -- NB: important to flatten here. Otherwise, it looks like -- instance C Int cannot match a target [W] C (F Bool). + -- See Note [Flattening type-family applications when matching instances] + -- in GHC.Core.Unify. case tcUnifyTysFG instanceBindFun tpl_tys flattened_tys of SurelyApart -> find ms us rest _ -> find ms (item:us) rest @@ -1029,20 +1031,26 @@ When looking up in the instance environment, or family-instance environment, we are careful about multiple matches, as described above in Note [Overlapping instances] -The key_tys can contain skolem constants, and we can guarantee that those +The target tys can contain skolem constants. For existentials and instance variables, +we can guarantee that those are never going to be instantiated to anything, so we should not involve -them in the unification test. Example: +them in the unification test. These are called "super skolems". Example: class Foo a where { op :: a -> Int } instance Foo a => Foo [a] -- NB overlap instance Foo [Int] -- NB overlap data T = forall a. Foo a => MkT a f :: T -> Int f (MkT x) = op [x,x] -The op [x,x] means we need (Foo [a]). Without the filterVarSet we'd -complain, saying that the choice of instance depended on the instantiation -of 'a'; but of course it isn't *going* to be instantiated. - -We do this only for isOverlappableTyVar skolems. For example we reject +The op [x,x] means we need (Foo [a]). This `a` will never be instantiated, and +so it is a super skolem. (See the use of tcInstSuperSkolTyVarsX in +GHC.Tc.Gen.Pat.tcDataConPat.) Super skolems respond True to +isOverlappableTyVar, and the use of Skolem in instanceBindFun, above, means +that these will be treated as fresh constants in the unification algorithm +during instance lookup. Without this treatment, GHC would complain, saying +that the choice of instance depended on the instantiation of 'a'; but of +course it isn't *going* to be instantiated. + +We do this only for super skolems. For example we reject g :: forall a => [a] -> Int g x = op x on the grounds that the correct instance depends on the instantiation of 'a' ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -821,8 +821,11 @@ data TyCon -- any type synonym families (data families -- are fine), again after expanding any -- nested synonyms - synIsForgetful :: Bool -- True <=> at least one argument is not mentioned - -- in the RHS + synIsForgetful :: Bool -- True <= at least one argument is not mentioned + -- in the RHS (or is mentioned only under + -- forgetful synonyms) + -- Test is conservative, so True does not guarantee + -- forgetfulness. } -- | Represents families (both type and data) @@ -2056,7 +2059,11 @@ isFamFreeTyCon (SynonymTyCon { synIsFamFree = fam_free }) = fam_free isFamFreeTyCon (FamilyTyCon { famTcFlav = flav }) = isDataFamFlav flav isFamFreeTyCon _ = True --- | Is this a forgetful type synonym? +-- | Is this a forgetful type synonym? If this is a type synonym whose +-- RHS does not mention one (or more) of its bound variables, returns +-- True. Thus, False means that all bound variables appear on the RHS; +-- True may not mean anything, as the test to set this flag is +-- conservative. isForgetfulSynTyCon :: TyCon -> Bool isForgetfulSynTyCon (SynonymTyCon { synIsForgetful = forget }) = forget isForgetfulSynTyCon _ = False ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -719,8 +719,9 @@ unifier It does /not/ work up to ~. The algorithm implemented here is rather delicate, and we depend on it to uphold certain properties. This is a summary of these required properties. Any reference to "flattening" refers to the flattening -algorithm in GHC.Core.FamInstEnv (See Note [Flattening] in GHC.Core.Unify), not -the flattening algorithm in the solver. +algorithm in GHC.Core.Unify (See +Note [Flattening type-family applications when matching instances] in GHC.Core.Unify), +not the flattening algorithm in the solver. Notation: θ,φ substitutions @@ -1648,8 +1649,8 @@ pushRefl co = * * ************************************************************************ -Note [Flattening] -~~~~~~~~~~~~~~~~~ +Note [Flattening type-family applications when matching instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ As described in "Closed type families with overlapping equations" http://research.microsoft.com/en-us/um/people/simonpj/papers/ext-f/axioms-extended.pdf we need to flatten core types before unifying them, when checking for "surely-apart" @@ -1678,6 +1679,15 @@ can see that (F x x) can reduce to Double. So, it had better be the case that (F blah blah) can reduce to Double, no matter what (blah) is! Flattening as done below ensures this. +We also use this flattening operation to check for class instances. +If we have + instance C (Maybe b) + instance {-# OVERLAPPING #-} C (Maybe Bool) + [W] C (Maybe (F a)) +we want to know that the second instance might match later. So we +flatten the (F a) in the target before trying to unify with instances. +(This is done in GHC.Core.InstEnv.lookupInstEnv'.) + The algorithm works by building up a TypeMap TyVar, mapping type family applications to fresh variables. This mapping must be threaded through all the function calls, as any entry in @@ -1794,7 +1804,7 @@ data FlattenEnv -- domain: exactly-saturated type family applications -- range: (fresh variable, type family tycon, args) , fe_in_scope :: InScopeSet } - -- See Note [Flattening] + -- See Note [Flattening type-family applications when matching instances] emptyFlattenEnv :: InScopeSet -> FlattenEnv emptyFlattenEnv in_scope @@ -1805,11 +1815,11 @@ updateInScopeSet :: FlattenEnv -> (InScopeSet -> InScopeSet) -> FlattenEnv updateInScopeSet env upd = env { fe_in_scope = upd (fe_in_scope env) } flattenTys :: InScopeSet -> [Type] -> [Type] --- See Note [Flattening] +-- See Note [Flattening type-family applications when matching instances] flattenTys in_scope tys = fst (flattenTysX in_scope tys) flattenTysX :: InScopeSet -> [Type] -> ([Type], TyVarEnv (TyCon, [Type])) --- See Note [Flattening] +-- See Note [Flattening type-family applications when matching instances] -- NB: the returned types mention the fresh type variables -- in the domain of the returned env, whose range includes -- the original type family applications. Building a substitution @@ -1889,7 +1899,7 @@ coreFlattenCo subst env co (env1, kind') = coreFlattenTy subst env (coercionType co) covar = mkFlattenFreshCoVar (fe_in_scope env1) kind' -- Add the covar to the FlattenEnv's in-scope set. - -- See Note [Flattening], wrinkle 2A. + -- See Note [Flattening type-family applications when matching instances], wrinkle 2A. env2 = updateInScopeSet env1 (flip extendInScopeSet covar) coreFlattenVarBndr :: TvSubstEnv -> FlattenEnv @@ -1897,7 +1907,7 @@ coreFlattenVarBndr :: TvSubstEnv -> FlattenEnv coreFlattenVarBndr subst env tv = (env2, subst', tv') where - -- See Note [Flattening], wrinkle 2B. + -- See Note [Flattening type-family applications when matching instances], wrinkle 2B. kind = varType tv (env1, kind') = coreFlattenTy subst env kind tv' = uniqAway (fe_in_scope env1) (setVarType tv kind') @@ -1927,11 +1937,13 @@ coreFlattenTyFamApp tv_subst env fam_tc fam_args (sat_fam_args, leftover_args) = ASSERT( arity <= length fam_args ) splitAt arity fam_args -- Apply the substitution before looking up an application in the - -- environment. See Note [Flattening], wrinkle 1. + -- environment. See Note [Flattening type-family applications when matching instances], + -- wrinkle 1. -- NB: substTys short-cuts the common case when the substitution is empty. sat_fam_args' = substTys tcv_subst sat_fam_args (env', leftover_args') = coreFlattenTys tv_subst env leftover_args - -- `fam_tc` may be over-applied to `fam_args` (see Note [Flattening], + -- `fam_tc` may be over-applied to `fam_args` (see + -- Note [Flattening type-family applications when matching instances] -- wrinkle 3), so we split it into the arguments needed to saturate it -- (sat_fam_args') and the rest (leftover_args') fam_ty = mkTyConApp fam_tc sat_fam_args' ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1189,6 +1189,11 @@ tc_hs_type _ rn_ty@(HsTyLit _ (HsStrTy _ s)) exp_kind = do { checkWiredInTyCon typeSymbolKindCon ; checkExpectedKind rn_ty (mkStrLitTy s) typeSymbolKind exp_kind } +--------- Wildcards + +tc_hs_type mode ty@(HsWildCardTy _) ek + = tcAnonWildCardOcc NoExtraConstraint mode ty ek + --------- Potentially kind-polymorphic types: call the "up" checker -- See Note [Future-proofing the type checker] tc_hs_type mode ty@(HsTyVar {}) ek = tc_infer_hs_type_ek mode ty ek @@ -1198,9 +1203,6 @@ tc_hs_type mode ty@(HsOpTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsKindSig {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(XHsType (NHsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek -tc_hs_type mode ty@(HsWildCardTy _) ek - = tcAnonWildCardOcc NoExtraConstraint mode ty ek - {- Note [Variable Specificity and Forall Visibility] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/Gen/Pat.hs ===================================== @@ -898,6 +898,8 @@ tcDataConPat penv (L con_span con_name) data_con pat_ty_scaled ; (tenv, ex_tvs') <- tcInstSuperSkolTyVarsX tenv ex_tvs -- Get location from monad, not from ex_tvs -- This freshens: See Note [Freshen existentials] + -- Why "super"? See Note [Binding when lookup up instances] + -- in GHC.Core.InstEnv. ; let -- pat_ty' = mkTyConApp tycon ctxt_res_tys -- pat_ty' is type of the actual constructor application ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -1019,29 +1019,21 @@ can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1@(LitTy l1) _ (LitTy l2) _ -- Decompose FunTy: (s -> t) and (c => t) -- NB: don't decompose (Int -> blah) ~ (Show a => blah) can_eq_nc' _flat _rdr_env _envs ev eq_rel - (FunTy { ft_mult = am1, ft_af = af1, ft_arg = ty1a, ft_res = ty1b }) ps_ty1 - (FunTy { ft_mult = am2, ft_af = af2, ft_arg = ty2a, ft_res = ty2b }) ps_ty2 - | Just ty1a_rep <- getRuntimeRep_maybe ty1a -- getRutimeRep_maybe: + (FunTy { ft_mult = am1, ft_af = af1, ft_arg = ty1a, ft_res = ty1b }) _ps_ty1 + (FunTy { ft_mult = am2, ft_af = af2, ft_arg = ty2a, ft_res = ty2b }) _ps_ty2 + | af1 == af2 -- Don't decompose (Int -> blah) ~ (Show a => blah) + , Just ty1a_rep <- getRuntimeRep_maybe ty1a -- getRutimeRep_maybe: , Just ty1b_rep <- getRuntimeRep_maybe ty1b -- see Note [Decomposing FunTy] , Just ty2a_rep <- getRuntimeRep_maybe ty2a , Just ty2b_rep <- getRuntimeRep_maybe ty2b - = if af1 == af2 -- Don't decompose (Int -> blah) ~ (Show a => blah) - then canDecomposableTyConAppOK ev eq_rel funTyCon + = canDecomposableTyConAppOK ev eq_rel funTyCon [am1, ty1a_rep, ty1b_rep, ty1a, ty1b] [am2, ty2a_rep, ty2b_rep, ty2a, ty2b] - else canEqHardFailure ev ps_ty1 ps_ty2 - -- in the "else" case, we don't want to fall through, because the TyConApp - -- case may trigger, giving a worse error -- Decompose type constructor applications -- NB: we have expanded type synonyms already --- We still have to handle the FunTy case separately, just to avoid decomposing --- (Int -> blah) and (Show a => blah). -can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1 _ ty2 _ - -- use tcSplit to avoid splitting (Eq a => Bool) - | Just (tc1, tys1) <- tcSplitTyConApp_maybe ty1 - , Just (tc2, tys2) <- tcSplitTyConApp_maybe ty2 - , not (isTypeFamilyTyCon tc1) +can_eq_nc' _flat _rdr_env _envs ev eq_rel (TyConApp tc1 tys1) _ (TyConApp tc2 tys2) _ + | not (isTypeFamilyTyCon tc1) , not (isTypeFamilyTyCon tc2) = canTyConApp ev eq_rel tc1 tys1 tc2 tys2 @@ -2040,7 +2032,7 @@ See also #10715, which induced this addition. Note [Put touchable variables on the left] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -#10009, a very nasty example: +Ticket #10009, a very nasty example: f :: (UnF (F b) ~ b) => F b -> () @@ -2085,7 +2077,7 @@ in a Given. On the other hand, the original LHS mentioned only variables that appear in Givens. We thus choose to put variables that can appear in Wanteds on the left. -#12526 is another good example of this in action. +Ticket #12526 is another good example of this in action. -} @@ -2476,18 +2468,18 @@ canEqOK dflags eq_rel lhs rhs -- are not generally insoluble where - good_rhs = kinds_match && not bad_newtype + good_rhs = kinds_match && not bad_newtype - lhs_kind = canEqLHSKind lhs - rhs_kind = tcTypeKind rhs + lhs_kind = canEqLHSKind lhs + rhs_kind = tcTypeKind rhs - kinds_match = lhs_kind `tcEqType` rhs_kind + kinds_match = lhs_kind `tcEqType` rhs_kind - bad_newtype | ReprEq <- eq_rel - , Just tc <- tyConAppTyCon_maybe rhs - = isNewTyCon tc - | otherwise - = False + bad_newtype | ReprEq <- eq_rel + , Just tc <- tyConAppTyCon_maybe rhs + = isNewTyCon tc + | otherwise + = False {- Note [Equalities with incompatible kinds] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2530,17 +2522,18 @@ Wrinkles: tales of destruction. So, we have an invariant on CEqCan (TyEq:H) that the RHS does not have - any coercion holes. This is checked in metaTyVarUpdateOK. We also + any coercion holes. This is checked in checkTypeEq. Any equalities that + have such an RHS are turned in CIrredCans with a BlockedCIS status. We also must be sure to kick out any constraints that mention coercion holes - when those holes get filled in. + when those holes get filled in, so that the unification step can now proceed. (2a) We must now absolutely make sure to kick out any constraints that - mention a newly-filled-in coercion hole. This is done in - kickOutAfterFillingCoercionHole. But we only kick out when the - filling coercion contains no coercion holes. This extra check - avoids needless work when rewriting evidence (which fills coercion - holes) and aids efficiency. It also can avoid a loop in the solver - that would otherwise arise in this case: + mention a newly-filled-in coercion hole -- if there are no more + remaining coercion holes. This is done in + kickOutAfterFillingCoercionHole. The extra check that there are no + more remaining holes avoids needless work when rewriting evidence + (which fills coercion holes) and aids efficiency. It also can avoid + a loop in the solver that would otherwise arise in this case: [W] w1 :: (ty1 :: F a) ~ (ty2 :: s) After canonicalisation, we discover that this equality is heterogeneous. So we emit @@ -2551,11 +2544,14 @@ Wrinkles: and forth, as it goes through canEqTyVarFunEq. We thus get co_abc := sym co_abd, and then co_abd := sym co_abe, with [W] co_abe :: F a ~ s - right back where we started. But all this filling in would, - naively, cause kicking w2 out. Which, when it got processed, + right back where we started. (At this point, we're in canEqCanLHSFinish, + so we're not looping.) But all this filling in would, + naively, cause w2 to be kicked out. Which, when it got processed, would get this whole chain going again. The solution is to kick out a blocked constraint only when the result of filling in the blocking coercion involves no further blocking coercions. + Alternatively, we could be careful not to do unnecessary swaps during + canonicalisation, but that seems hard to do, in general. (2b) Consider this case: [G] co_given :: k1 ~ k2 @@ -2592,8 +2588,8 @@ Wrinkles: cast appears opposite a tyvar. This is implemented in the cast case of can_eq_nc'. - (4) Reporting an error for a constraint that is blocked only because - of wrinkle (2) is hard: what would we say to users? And we don't + (4) Reporting an error for a constraint that is blocked with status BlockedCIS + is hard: what would we say to users? And we don't really need to report, because if a constraint is blocked, then there is unsolved wanted blocking it; that unsolved wanted will be reported. We thus push such errors to the bottom of the queue @@ -2671,7 +2667,25 @@ In order to solve the Wanted, we must use the Given to rewrite `a` to Maybe (F a). But note that the Given has an occurs-check failure, and so we can't straightforwardly add the Given to the inert set. -Instead, we detect this scenario by the following characteristics: +The key idea is to replace the (F a) in the RHS of the Given with a +fresh variable, which we'll call a CycleBreakerTv, or cbv. Then, emit +a new Given to connect cbv with F a. So our situation becomes + + instance C (Maybe b) + [G] a ~ Maybe cbv + [G] F a ~ cbv + [W] C a + +Note the orientation of the second Given. The type family ends up +on the left; see commentary on canEqTyVarFunEq, which decides how to +orient such cases. No special treatment for CycleBreakerTvs is +necessary. This scenario is now easily soluble, by using the first +Given to rewrite the Wanted, which can now be solved. + +(The first Given actually also rewrites the second one. This causes +no trouble.) + +More generally, we detect this scenario by the following characteristics: - a Given CEqCan constraint - with a tyvar on its LHS - with a soluble occurs-check failure @@ -2689,16 +2703,24 @@ after we're done running the solver (in nestImplicTcS and runTcSWithEvBinds). This is done by restoreTyVarCycles, which uses the inert_cycle_breakers field in InertSet, which contains the pairings invented in breakTyVarCycle. -In our example, we start with - - [G] a ~ Maybe (F a) - -We then change this to become - - [G] a ~ Maybe cbv - [G] F a ~ cbv - -and set cbv := F a after we're done solving. +That is: + +We transform + [G] g : a ~ ...(F a)... +to + [G] (Refl a) : F a ~ cbv -- CEqCan + [G] g : a ~ ...cbv... -- CEqCan + +Note that +* `cbv` is a fresh cycle breaker variable. +* `cbv` is a is a meta-tyvar, but it is completely untouchable. +* We track the cycle-breaker variables in inert_cycle_breakers in InertSet +* We eventually fill in the cycle-breakers, with `cbv := F a`. + No one else fills in cycle-breakers! +* This fill-in is done when solving is complete, by restoreTyVarCycles + in nestImplicTcS and runTcSWithEvBinds. +* The evidence for the new `F a ~ cbv` constraint is Refl, because we know this fill-in is + ultimately going to happen. There are drawbacks of this approach: @@ -2749,14 +2771,26 @@ Details: The temporary ill-kinded type hurts no one, and avoiding this would be quite painfully difficult. + Specifically, this detail does not contravene the Purely Kinded Type Invariant + (Note [The Purely Kinded Type Invariant (PKTI)] in GHC.Tc.Gen.HsType). + The PKTI says that we can call typeKind on any type, without failure. + It would be violated if we, say, replaced a kind (a -> b) with a kind c, + because an arrow kind might be consulted in piResultTys. Here, we are + replacing one opaque type like (F a b c) with another, cbv (opaque in + that we never assume anything about its structure, like that it has a + result type or a RuntimeRep argument). + (4) The evidence for the produced Givens is all just reflexive, because we will eventually set the cycle-breaker variable to be the type family, and then, after the zonk, all will be well. (5) The approach here is inefficient. For instance, we could choose to - affect only type family applications that mention the offending variable. - We could try to detect cases like a ~ (F a, F a) and use the same - tyvar to replace F a. (Cf. Note [Flattening] in GHC.Core.Unify, which + affect only type family applications that mention the offending variable: + in a ~ (F b, G a), we need to replace only G a, not F b. Furthermore, + we could try to detect cases like a ~ (F a, F a) and use the same + tyvar to replace F a. (Cf. + Note [Flattening type-family applications when matching instances] + in GHC.Core.Unify, which goes to this extra effort.) There may be other opportunities for improvement. However, this is really a very small corner case, always tickled by a user-written Given. The investment to craft a clever, @@ -2768,7 +2802,9 @@ Details: evidence itself. As in Detail (4), we don't need to change the evidence term (as in e.g. rewriteEqEvidence) because the cycle breaker variables are all zonked away by the time we examine the - evidence. + evidence. That is, we must set the ctev_pred of the ctEvidence. + This is implemented in canEqCanLHSFinish, with a reference to + this detail. (7) We don't wish to apply this magic to CycleBreakerTvs themselves. Consider this, from typecheck/should_compile/ContextStack2: @@ -2801,7 +2837,11 @@ Details: unchecked, this will end up breaking cycles again, looping ad infinitum (and resulting in a context-stack reduction error, not an outright loop). The solution is easy: don't break cycles - if the var is already a CycleBreakerTv. This makes sense, because + if the var is already a CycleBreakerTv. Instead, we mark this + final Given as a CIrredCan with an OtherCIS status (it's not + insoluble). + + Not breaking cycles fursther makes sense, because we only want to break cycles for user-written loopy Givens, and a CycleBreakerTv certainly isn't user-written. ===================================== compiler/GHC/Tc/Solver/Flatten.hs ===================================== @@ -362,7 +362,7 @@ If we need to make this yet more performant, a possible way forward is to duplicate the flattener code for the nominal case, and make that case faster. This doesn't seem quite worth it, yet. -Note [flatten_exact_fam_app_fully performance] +Note [flatten_exact_fam_app performance] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Once we've got a flat rhs, we extend the famapp-cache to record the result. Doing so can save lots of work when the same redex shows up more @@ -727,15 +727,22 @@ keeps types smaller. But we need to take care. Suppose type Syn a = Int type instance F Bool = Syn (F Bool) + [G] F Bool ~ Syn (F Bool) -If we don't expand the synonym, we'll fall into an unnecessary loop. +If we don't expand the synonym, we'll get a spurious occurs-check +failure. This is normally what occCheckExpand takes care of, but +the LHS is a type family application, and occCheckExpand (already +complex enough as it is) does not know how to expand to avoid +a type family application. In addition, expanding the forgetful synonym like this -will generally yield a *smaller* type. We thus expand forgetful +will generally yield a *smaller* type. To wit, if we spot +S ( ... F tys ... ), where S is forgetful, we don't want to bother +doing hard work simplifying (F tys). We thus expand forgetful synonyms, but not others. -One nice consequence is that we never have to occCheckExpand flattened -types, as any forgetful synonyms are already expanded. +isForgetfulSynTyCon returns True more often than it needs to, so +we err on the side of more expansion. We also, of course, must expand type synonyms that mention type families, so those families can get reduced. @@ -745,11 +752,63 @@ so those families can get reduced. Flattening a type-family application * * ************************************************************************ + +Note [How to normalise a family application] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Given an exactly saturated family application, how should we normalise it? +This Note spells out the algorithm and its reasoning. + +STEP 1. Try the famapp-cache. If we get a cache hit, jump to FINISH. + +STEP 2. Try top-level instances. Note that we haven't simplified the arguments + yet. Example: + type instance F (Maybe a) = Int + target: F (Maybe (G Bool)) + Instead of first trying to simplify (G Bool), we use the instance first. This + avoids the work of simplifying G Bool. + + If an instance is found, jump to FINISH. + +STEP 3. Flatten all arguments. This might expose more information so that we + can use a top-level instance. + + Continue to the next step. + +STEP 4. Try the inerts. Note that we try the inerts *after* flattening the + arguments, because the inerts will have flattened LHSs. + + If an inert is found, jump to FINISH. + +STEP 5. Try the famapp-cache again. Now that we've revealed more information + in the arguments, the cache might be helpful. + + If we get a cache hit, jump to FINISH. + +STEP 6. Try top-level instances, which might trigger now that we know more + about the argumnents. + + If an instance is found, jump to FINISH. + +STEP 7. No progress to be made. Return what we have. (Do not do FINISH.) + +FINISH 1. We've made a reduction, but the new type may still have more + work to do. So flatten the new type. + +FINISH 2. Add the result to the famapp-cache, connecting the type we started + with to the one we ended with. + +Because STEP 1/2 and STEP 5/6 happen the same way, they are abstracted into +try_to_reduce. + +FINISH is naturally implemented in `finish`. But, Note [flatten_exact_fam_app performance] +tells us that we should not add to the famapp-cache after STEP 1/2. So `finish` +is inlined in that case, and only FINISH 1 is performed. + -} flatten_fam_app :: TyCon -> [TcType] -> FlatM (Xi, Coercion) -- flatten_fam_app can be over-saturated - -- flatten_exact_fam_app_fully lifts out the application to top level + -- flatten_exact_fam_app lifts out the application to top level -- Postcondition: Coercion :: Xi ~ F tys flatten_fam_app tc tys -- Can be over-saturated = ASSERT2( tys `lengthAtLeast` tyConArity tc @@ -760,26 +819,27 @@ flatten_fam_app tc tys -- Can be over-saturated -- in which case the remaining arguments should -- be dealt with by AppTys do { let (tys1, tys_rest) = splitAt (tyConArity tc) tys - ; (xi1, co1) <- flatten_exact_fam_app_fully tc tys1 + ; (xi1, co1) <- flatten_exact_fam_app tc tys1 -- co1 :: xi1 ~ F tys1 ; flatten_app_ty_args xi1 co1 tys_rest } -- the [TcType] exactly saturate the TyCon -flatten_exact_fam_app_fully :: TyCon -> [TcType] -> FlatM (Xi, Coercion) -flatten_exact_fam_app_fully tc tys +-- See Note [How to normalise a family application] +flatten_exact_fam_app :: TyCon -> [TcType] -> FlatM (Xi, Coercion) +flatten_exact_fam_app tc tys = do { checkStackDepth (mkTyConApp tc tys) - -- Step 1. Try to reduce without reducing arguments first. + -- STEP 1/2. Try to reduce without reducing arguments first. ; result1 <- try_to_reduce tc tys ; case result1 of -- Don't use `finish`; - -- See Note [flatten_exact_fam_app_fully performance] + -- See Note [flatten_exact_fam_app performance] { Just (co, xi) -> do { (xi2, co2) <- bumpDepth $ flatten_one xi ; return (xi2, co2 `mkTcTransCo` co) } ; Nothing -> - -- That didn't work. So reduce the arguments. + -- That didn't work. So reduce the arguments, in STEP 3. do { (xis, cos, kind_co) <- flatten_args_tc tc (repeat Nominal) tys -- kind_co :: tcTypeKind(F xis) ~N tcTypeKind(F tys) @@ -795,6 +855,7 @@ flatten_exact_fam_app_fully tc tys -- and co' :: xi' ~r F tys, which is homogeneous homogenise xi co = homogenise_result xi (co `mkTcTransCo` args_co) role kind_co + -- STEP 4: try the inerts ; result2 <- liftTcS $ lookupFamAppInert tc xis ; flavour <- getFlavour ; case result2 of @@ -813,11 +874,11 @@ flatten_exact_fam_app_fully tc tys ; _ -> - -- inert didn't work. Try to reduce again + -- inert didn't work. Try to reduce again, in STEP 5/6. do { result3 <- try_to_reduce tc xis ; case result3 of Just (co, xi) -> finish (homogenise xi co) - Nothing -> -- we have made no progress at all + Nothing -> -- we have made no progress at all: STEP 7. return (homogenise reduced (mkTcReflCo role reduced)) where reduced = mkTyConApp tc xis }}}}} @@ -825,10 +886,13 @@ flatten_exact_fam_app_fully tc tys -- call this if the above attempts made progress. -- This recursively flattens the result and then adds to the cache finish :: (Xi, Coercion) -> FlatM (Xi, Coercion) - finish (xi, co) = do { (fully, fully_co) <- bumpDepth $ flatten_one xi + finish (xi, co) = do { -- flatten the result: FINISH 1 + (fully, fully_co) <- bumpDepth $ flatten_one xi ; let final_co = fully_co `mkTcTransCo` co ; eq_rel <- getEqRel ; flavour <- getFlavour + + -- extend the cache: FINISH 2 ; when (eq_rel == NomEq && flavour /= Derived) $ -- the cache only wants Nominal eqs -- and Wanteds can rewrite Deriveds; the cache @@ -837,12 +901,15 @@ flatten_exact_fam_app_fully tc tys ; return (fully, final_co) } -- Returned coercion is output ~r input, where r is the role in the FlatM monad +-- See Note [How to normalise a family application] try_to_reduce :: TyCon -> [TcType] -> FlatM (Maybe (TcCoercion, TcType)) try_to_reduce tc tys - = do { result <- liftTcS $ firstJustsM [ lookupFamAppCache tc tys - , matchFam tc tys ] + = do { result <- liftTcS $ firstJustsM [ lookupFamAppCache tc tys -- STEP 5 + , matchFam tc tys ] -- STEP 6 ; downgrade result } where + -- The result above is always Nominal. We might want a Representational + -- coercion; this downgrades (and prints, out of convenience). downgrade :: Maybe (TcCoercionN, TcType) -> FlatM (Maybe (TcCoercion, TcType)) downgrade Nothing = return Nothing downgrade result@(Just (co, xi)) @@ -991,8 +1058,6 @@ split_pi_tys' ty = split ty ty split orig_ty _ = ([], orig_ty, False) {-# INLINE split_pi_tys' #-} - - -- | Like 'tyConBindersTyCoBinders' but you also get a 'Bool' which is true iff -- there is at least one named binder. ty_con_binders_ty_binders' :: [TyConBinder] -> ([TyCoBinder], Bool) ===================================== compiler/GHC/Tc/Solver/Interact.hs ===================================== @@ -2096,7 +2096,7 @@ The partial solution is that: The end effect is that, much as we do for overlapping instances, we delay choosing a class instance if there is a possibility of another instance OR a given to match our constraint later on. This fixes -#4981 and #5002. +tickets #4981 and #5002. Other notes: ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -802,6 +802,7 @@ Proof. By property (R2), with f1=f2 Definition [Generalised substitution] A "generalised substitution" S is a set of triples (t0 -f-> t), where t0 is a type variable or an exactly-saturated type family application + (that is, t0 is a CanEqLHS) t is a type f is a flavour such that @@ -876,7 +877,7 @@ Main Theorem [Stability under extension] AND (K3) See Note [K3: completeness of solving] { (K3a) If the role of fs is nominal: s /= t0 (K3b) If the role of fs is representational: - s is not of form (a t1 .. tn) } } + s is not of form (t0 t1 .. tn) } } Conditions (T1-T3) are established by the canonicaliser @@ -1149,6 +1150,9 @@ Additional notes: * inert_dicts is a finite map keyed by the type; it's inconvenient for it to map to TWO constraints +Another example requiring Deriveds is in +Note [Put touchable variables on the left] in GHC.Tc.Solver.Canonical. + Note [Splitting WD constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We are about to add a [WD] constraint to the inert set; and we @@ -1774,7 +1778,7 @@ kick_out_rewritable new_fr new_lhs && fr_can_rewrite_ty eq_rel rhs_ty -- (K2d) -- (K2c) is guaranteed by the first guard of keep_eq - kick_out_for_completeness + kick_out_for_completeness -- (K3) and Note [K3: completeness of solving] = case (eq_rel, new_lhs) of (NomEq, _) -> rhs_ty `eqType` canEqLHSType new_lhs (ReprEq, TyVarLHS new_tv) -> isTyVarHead new_tv rhs_ty @@ -1815,6 +1819,8 @@ kickOutAfterFillingCoercionHole hole filled_co ; setInertCans ics' } where + holes_of_co = coercionHolesOfCo filled_co + kick_out :: InertCans -> (WorkList, InertCans) kick_out ics@(IC { inert_irreds = irreds }) = let (to_kick, to_keep) = partitionBagWith kick_ct irreds @@ -1830,7 +1836,7 @@ kickOutAfterFillingCoercionHole hole filled_co kick_ct ct@(CIrredCan { cc_status = BlockedCIS holes }) | hole `elementOfUniqSet` holes = let new_holes = holes `delOneFromUniqSet` hole - `unionUniqSets` coercionHolesOfCo filled_co + `unionUniqSets` holes_of_co updated_ct = ct { cc_status = BlockedCIS new_holes } in if isEmptyUniqSet new_holes @@ -2238,14 +2244,15 @@ We must determine whether a Given might later match a Wanted. We definitely need to account for the possibility that any metavariable in the Wanted might be arbitrarily instantiated. We do *not* want to allow skolems in the Given to be instantiated. But what about -type family applications? +type family applications? (Examples are below the explanation.) To allow flexibility in how type family applications unify we use -the Core flattener. See Note [Flattening] in GHC.Core.Unify. +the Core flattener. See +Note [Flattening type-family applications when matching instances] in GHC.Core.Unify. This is *distinct* from the flattener in GHC.Tc.Solver.Flatten. The Core flattener replaces all type family applications with fresh variables. The next question: should we allow these fresh -variables in the domian of a unifying substitution? +variables in the domain of a unifying substitution? A type family application that mentions only skolems is settled: any skolems would have been rewritten w.r.t. Givens by now. These type @@ -2256,6 +2263,30 @@ we use BindMe to tell the unifier to allow it in the substitution. On the other hand, a type family application with only skolems is considered rigid. +Examples: + [G] C a + [W] C alpha + This easily might match later. + + [G] C a + [W] C (F alpha) + This might match later, too, but we need to flatten the (F alpha) + to a fresh variable so that the unifier can connect the two. + + [G] C (F alpha) + [W] C a + This also might match later. Again, we will need to flatten to + find this out. (Surprised about a metavariable in a Given? See + #18929.) + + [G] C (F a) + [W] C a + This won't match later. We're not going to get new Givens that + can inform the F a, and so this is a no-go. + +This treatment fixes #18910 and is tested in +typecheck/should_compile/InstanceGivenOverlap{,2} + Note [When does an implication have given equalities?] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider an implication @@ -3599,7 +3630,7 @@ breakTyVarCycle loc = go go ty@(Rep.ForAllTy {}) = return ty -- See Detail (1) of Note go ty@(Rep.CoercionTy {}) = return ty -- See Detail (2) of Note --- | Filli in CycleBreakerTvs with the variables they stand for. +-- | Fill in CycleBreakerTvs with the variables they stand for. -- See Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical. restoreTyVarCycles :: InertSet -> TcM () restoreTyVarCycles is @@ -3609,6 +3640,7 @@ restoreTyVarCycles is -- Unwrap a type synonym only when either: -- The type synonym is forgetful, or -- the type synonym mentions a type family in its expansion +-- See Note [Flattening synonyms] in GHC.Tc.Solver.Flatten. flattenView :: TcType -> Maybe TcType flattenView ty@(Rep.TyConApp tc _) | isForgetfulSynTyCon tc || (isTypeSynonymTyCon tc && not (isFamFreeTyCon tc)) ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -113,6 +113,36 @@ import qualified Data.Semigroup ( (<>) ) * These are the constraints the low-level simplifier works with * * * ************************************************************************ + +Note [CEqCan occurs check] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A CEqCan relates a CanEqLHS (a type variable or type family applications) on +its left to an arbitrary type on its right. It is used for rewriting, in the +flattener. Because it is used for rewriting, it would be disastrous if the RHS +were to mention the LHS: this would cause a loop in rewriting. + +We thus perform an occurs-check. There is, of course, some subtlety: + +* For type variables, the occurs-check looks deeply. This is because + a CEqCan over a meta-variable is also used to inform unification, + in GHC.Tc.Solver.Interact.solveByUnification. If the LHS appears + anywhere, at all, in the RHS, unification will create an infinite + structure, which is bad. + +* For type family applications, the occurs-check is shallow; it looks + only in places where we might rewrite. (Specifically, it does not + look in kinds or coercions.) An occurrence of the LHS in, say, an + RHS coercion is OK, as we do not rewrite in coercions. No loop to + be found. + + You might also worry about the possibility that a type family + application LHS doesn't exactly appear in the RHS, but something + that reduces to the LHS does. Yet that can't happen: the RHS is + already inert, with all type family redexes reduced. So a simple + syntactic check is just fine. + +The occurs check is performed in GHC.Tc.Utils.Unify.checkTypeEq. + -} -- | A 'Xi'-type is one that has been fully rewritten with respect @@ -157,8 +187,7 @@ data Ct -- * See Note [inert_eqs: the inert equalities] in GHC.Tc.Solver.Monad -- * Many are checked in checkTypeEq in GHC.Tc.Utils.Unify -- * (TyEq:OC) lhs does not occur in rhs (occurs check) - -- (skips coercions if the lhs is a type family application, because - -- we don't rewrite type families in coercions) + -- Note [CEqCan occurs check] -- * (TyEq:F) rhs has no foralls -- (this avoids substituting a forall for the tyvar in other types) -- * (TyEq:K) tcTypeKind lhs `tcEqKind` tcTypeKind rhs; Note [Ct kind invariant] @@ -243,6 +272,8 @@ data HoleSort = ExprHole Id -- ^ A hole in a type (PartialTypeSignatures) | ConstraintHole -- ^ A hole in a constraint, like @f :: (_, Eq a) => ... + -- Differentiated from TypeHole because a ConstraintHole + -- is simplified differently. See GHC.Tc.Solver.simplifyHoles. instance Outputable Hole where ppr (Hole { hole_sort = ExprHole id @@ -1141,8 +1172,9 @@ data ImplicStatus | IC_Unsolved -- Neither of the above; might go either way -- | Does this implication have Given equalities? --- See Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad --- and Note [Suppress redundant givens during error reporting] in GHC.Tc.Errors +-- See Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad, +-- which also explains why we need three options here. Also, see +-- Note [Suppress redundant givens during error reporting] in GHC.Tc.Errors data HasGivenEqs = NoGivenEqs -- definitely no given equalities | LocalGivenEqs -- might have Given equalities that affect only local skolems ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -2169,7 +2169,8 @@ Why?, for example: - For CIrredCan we want to see if a constraint is insoluble with insolubleWC On the other hand, we change CEqCan to CNonCanonical, because of all of -CEqCan's invariants, which can break during zonking. Besides, the constraint +CEqCan's invariants, which can break during zonking. (Example: a ~R alpha, where +we have alpha := N Int, where N is a newtype.) Besides, the constraint will be canonicalised again, so there is little benefit in keeping the CEqCan structure. ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -1976,7 +1976,8 @@ checkTyFamEq dflags fun_tc fun_args ty = inline checkTypeEq dflags YesTypeFamilies (TyFamLHS fun_tc fun_args) ty -- inline checkTypeEq so that the `case`s over the CanEqLHS get blasted away -checkTypeEq :: DynFlags -> AreTypeFamiliesOK -> CanEqLHS -> TcType -> MetaTyVarUpdateResult () +checkTypeEq :: DynFlags -> AreTypeFamiliesOK -> CanEqLHS -> TcType + -> MetaTyVarUpdateResult () -- Checks the invariants for CEqCan. In particular: -- (a) a forall type (forall a. blah) -- (b) a predicate type (c => ty) @@ -1987,13 +1988,7 @@ checkTypeEq :: DynFlags -> AreTypeFamiliesOK -> CanEqLHS -> TcType -> MetaTyVarU -- For (a), (b), and (c) we check only the top level of the type, NOT -- inside the kinds of variables it mentions. For (d) we look deeply -- in coercions when the LHS is a tyvar (but skip coercions for type family --- LHSs), and for (e) we do look in the kinds of course. --- --- Why skip coercions for type families? Because we don't rewrite type family --- applications in coercions, so there's no point in looking there. On the --- other hand, we must check for type variables, lest we mutably create an --- infinite structure during unification. - +-- LHSs), and for (e) see Note [CEqCan occurs check] in GHC.Tc.Types.Constraint. checkTypeEq dflags ty_fam_ok lhs ty = go ty where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef7479323a85c965b50fb2dfd71f537872cedab1...78425e2e6d50575111568a2e6f9d8e7f7e8bae22 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ef7479323a85c965b50fb2dfd71f537872cedab1...78425e2e6d50575111568a2e6f9d8e7f7e8bae22 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 Wed Nov 11 23:40:28 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 18:40:28 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Optimise nullary type constructor usage Message-ID: <5fac766ca1695_10ee3ffba936d0dc1456082@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 12d3c9b3 by Ben Gamari at 2020-11-11T18:40:18-05:00 Optimise nullary type constructor usage During the compilation of programs GHC very frequently deals with the `Type` type, which is a synonym of `TYPE 'LiftedRep`. This patch teaches GHC to avoid expanding the `Type` synonym (and other nullary type synonyms) during type comparisons, saving a good amount of work. This optimisation is described in `Note [Comparing nullary type synonyms]`. To maximize the impact of this optimisation, we introduce a few special-cases to reduce `TYPE 'LiftedRep` to `Type`. See `Note [Prefer Type over TYPE 'LiftedPtrRep]`. Closes #17958. Metric Decrease: T18698b T1969 T12227 T12545 T12707 T14683 T3064 T5631 T5642 T9020 T9872a T13035 haddock.Cabal haddock.base - - - - - 22 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - + compiler/GHC/Builtin/Types/Prim.hs-boot - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/printer/T18052a.stderr - testsuite/tests/simplCore/should_compile/T13143.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -170,6 +170,7 @@ import GHC.Types.Var (VarBndr (Bndr)) import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE, mAX_SUM_SIZE ) import GHC.Unit.Module ( Module ) import GHC.Core.Type +import qualified GHC.Core.TyCo.Rep as TyCoRep (Type(TyConApp)) import GHC.Types.RepType import GHC.Core.DataCon import GHC.Core.ConLike @@ -691,7 +692,7 @@ constraintKindTyCon :: TyCon constraintKindTyCon = pcTyCon constraintKindTyConName Nothing [] [] liftedTypeKind, typeToTypeKind, constraintKind :: Kind -liftedTypeKind = tYPE liftedRepTy +liftedTypeKind = TyCoRep.TyConApp liftedTypeKindTyCon [] typeToTypeKind = liftedTypeKind `mkVisFunTyMany` liftedTypeKind constraintKind = mkTyConApp constraintKindTyCon [] @@ -1415,8 +1416,8 @@ runtimeRepTy = mkTyConTy runtimeRepTyCon -- type Type = tYPE 'LiftedRep liftedTypeKindTyCon :: TyCon liftedTypeKindTyCon = buildSynTyCon liftedTypeKindTyConName - [] liftedTypeKind [] - (tYPE liftedRepTy) + [] liftedTypeKind [] rhs + where rhs = TyCoRep.TyConApp tYPETyCon [liftedRepTy] runtimeRepTyCon :: TyCon runtimeRepTyCon = pcTyCon runtimeRepTyConName Nothing [] ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -551,10 +551,6 @@ mkPrimTcName built_in_syntax occ key tycon = mkWiredInName gHC_PRIM (mkTcOccFS occ) key (mkATyCon tycon) built_in_syntax ----------------------------- --- | Given a RuntimeRep, applies TYPE to it. --- see Note [TYPE and RuntimeRep] -tYPE :: Type -> Type -tYPE rr = TyConApp tYPETyCon [rr] -- Given a Multiplicity, applies FUN to it. functionWithMultiplicity :: Type -> Type ===================================== compiler/GHC/Builtin/Types/Prim.hs-boot ===================================== @@ -0,0 +1,5 @@ +module GHC.Builtin.Types.Prim where + +import GHC.Core.TyCon + +tYPETyCon :: TyCon ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -52,6 +52,7 @@ module GHC.Core.TyCo.Rep ( mkVisFunTyMany, mkVisFunTysMany, mkInvisFunTyMany, mkInvisFunTysMany, mkTyConApp, + tYPE, -- * Functions over binders TyCoBinder(..), TyCoVarBinder, TyBinder, @@ -90,8 +91,9 @@ import GHC.Core.TyCon import GHC.Core.Coercion.Axiom -- others -import GHC.Builtin.Names ( liftedTypeKindTyConKey, manyDataConKey ) -import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, manyDataConTy ) +import GHC.Builtin.Names ( liftedTypeKindTyConKey, liftedRepDataConKey, manyDataConKey, tYPETyConKey ) +import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, liftedTypeKind, manyDataConTy ) +import {-# SOURCE #-} GHC.Builtin.Types.Prim ( tYPETyCon ) import GHC.Types.Basic ( LeftOrRight(..), pickLR ) import GHC.Types.Unique ( hasKey ) import GHC.Utils.Outputable @@ -1018,9 +1020,47 @@ mkTyConApp tycon tys -- avoid reboxing every time `mkTyConApp` is called. = ASSERT2( null tys, ppr tycon $$ ppr tys ) manyDataConTy + -- See Note [Prefer Type over TYPE 'LiftedRep]. + | tycon `hasKey` tYPETyConKey + , [rep] <- tys + = tYPE rep + -- The catch-all case | otherwise = TyConApp tycon tys +-- Note [Prefer Type over TYPE 'LiftedRep] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- The Core of nearly any program will have numerous occurrences of +-- @TYPE 'LiftedRep@ floating about. Consequently, we try hard to ensure +-- that operations on such types are efficient: +-- +-- * Instead of representing the lifted kind as +-- @TyConApp tYPETyCon [liftedRepDataCon]@ we rather prefer to +-- use the 'GHC.Types.Type' type synonym (available in GHC as +-- 'TysPrim.liftedTypeKind'). Note only is this a smaller AST but it also +-- guarantees sharing on the heap. +-- +-- * To avoid allocating 'TyConApp' constructors 'TysPrim.tYPE' +-- catches the lifted case and uses `liftedTypeKind` instead of building an +-- application. +-- +-- * Similarly, 'Type.mkTyConApp' catches applications of TYPE and +-- handles them using 'TysPrim.tYPE', ensuring that it benefits from the +-- optimisation described above. +-- +-- * Since 'liftedTypeKind' is a nullary type synonym application, +-- it benefits from the optimisation described in Note [Comparing nullary +-- type synonyms] in "GHC.Core.Type". + +-- | Given a RuntimeRep, applies TYPE to it. +-- see Note [TYPE and RuntimeRep] +tYPE :: Type -> Type +tYPE (TyConApp tc []) + -- See Note [Prefer Type of TYPE 'LiftedRep] + | tc `hasKey` liftedRepDataConKey = liftedTypeKind -- TYPE 'LiftedRep +tYPE rr = TyConApp tYPETyCon [rr] + -- This is a single, global definition of the type `Type` -- Defined here so it is only allocated once. -- See Note [mkTyConApp and Type] ===================================== compiler/GHC/Core/TyCo/Subst.hs ===================================== @@ -424,6 +424,7 @@ zipTCvSubst tcvs tys -- | Generates the in-scope set for the 'TCvSubst' from the types in the -- incoming environment. No CoVars, please! mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst +mkTvSubstPrs [] = emptyTCvSubst mkTvSubstPrs prs = ASSERT2( onlyTyVarsAndNoCoercionTy, text "prs" <+> ppr prs ) mkTvSubst in_scope tenv ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2310,12 +2310,14 @@ expandSynTyCon_maybe -- ^ Expand a type synonym application, if any expandSynTyCon_maybe tc tys | SynonymTyCon { tyConTyVars = tvs, synTcRhs = rhs, tyConArity = arity } <- tc - = case tys `listLengthCmp` arity of - GT -> Just (tvs `zip` tys, rhs, drop arity tys) - EQ -> Just (tvs `zip` tys, rhs, []) - LT -> Nothing - | otherwise - = Nothing + = case tys of + [] -> Just ([], rhs, []) -- Avoid a bit of work in the case of nullary synonyms + _ -> case tys `listLengthCmp` arity of + GT -> Just (tvs `zip` tys, rhs, drop arity tys) + EQ -> Just (tvs `zip` tys, rhs, []) + LT -> Nothing + | otherwise + = Nothing ---------------- ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -382,15 +382,16 @@ how roles in kinds might work out. -} -- | Gives the typechecker view of a type. This unwraps synonyms but --- leaves 'Constraint' alone. c.f. coreView, which turns Constraint into --- TYPE LiftedRep. Returns Nothing if no unwrapping happens. +-- leaves 'Constraint' alone. c.f. 'coreView', which turns 'Constraint' into +-- @TYPE LiftedRep at . Returns 'Nothing' if no unwrapping happens. -- See also Note [coreView vs tcView] {-# INLINE tcView #-} tcView :: Type -> Maybe Type -tcView (TyConApp tc tys) | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') +tcView (TyConApp tc tys) + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- The free vars of 'rhs' should all be bound by 'tenv', so it's - -- ok to use 'substTy' here. + -- ok to use 'substTy' here (which is what expandSynTyConApp_maybe does). -- See also Note [The substitution invariant] in GHC.Core.TyCo.Subst. -- Its important to use mkAppTys, rather than (foldl AppTy), -- because the function part might well return a @@ -399,17 +400,16 @@ tcView _ = Nothing {-# INLINE coreView #-} coreView :: Type -> Maybe Type --- ^ This function Strips off the /top layer only/ of a type synonym +-- ^ This function strips off the /top layer only/ of a type synonym -- application (if any) its underlying representation type. --- Returns Nothing if there is nothing to look through. +-- Returns 'Nothing' if there is nothing to look through. -- This function considers 'Constraint' to be a synonym of @TYPE LiftedRep at . -- -- By being non-recursive and inlined, this case analysis gets efficiently -- joined onto the case analysis that the caller is already doing coreView ty@(TyConApp tc tys) - | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') - -- This equation is exactly like tcView + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- At the Core level, Constraint = Type -- See Note [coreView vs tcView] @@ -419,6 +419,25 @@ coreView ty@(TyConApp tc tys) coreView _ = Nothing +----------------------------------------------- +expandSynTyConApp_maybe :: TyCon -> [Type] -> Maybe Type +expandSynTyConApp_maybe tc tys + | Just (tvs, rhs) <- synTyConDefn_maybe tc + = case tys of + [] -> Just (mkAppTys rhs tys) + _ -> case tys `listLengthCmp` arity of + GT -> Just (mkAppTys rhs' (drop arity tys)) + EQ -> Just rhs' + LT -> Nothing + where + arity = tyConArity tc + rhs' = substTy (mkTvSubstPrs (tvs `zip` tys)) rhs + | otherwise + = Nothing +-- Without this INLINE the call to expandSynTyConApp_maybe in coreView +-- will result in an avoidable allocation. +{-# INLINE expandSynTyConApp_maybe #-} + {-# INLINE coreFullView #-} coreFullView :: Type -> Type -- ^ Iterates 'coreView' until there is no more to synonym to expand. @@ -2194,6 +2213,36 @@ But the left is an AppTy while the right is a TyConApp. The solution is to use repSplitAppTy_maybe to break up the TyConApp into its pieces and then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * TcCanonical.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See [Prefer Type over TYPE 'LiftedRep] in +GHC.Core.TyCo.Rep for details. + -} eqType :: Type -> Type -> Bool @@ -2305,6 +2354,10 @@ nonDetCmpTypeX env orig_t1 orig_t2 = -- Returns both the resulting ordering relation between the two types -- and whether either contains a cast. go :: RnEnv2 -> Type -> Type -> TypeOrdering + -- See Note [Comparing nullary type synonyms]. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = TEQ go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 | Just t2' <- coreView t2 = go env t1 t2' ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -957,7 +957,12 @@ unify_ty :: UMEnv -- Respects newtypes, PredTypes unify_ty env ty1 ty2 kco - -- Use tcView, not coreView. See Note [coreView vs tcView] in GHC.Core.Type. + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + | TyConApp tc1 [] <- ty1 + , TyConApp tc2 [] <- ty2 + , tc1 == tc2 = return () + + -- TODO: More commentary needed here | Just ty1' <- tcView ty1 = unify_ty env ty1' ty2 kco | Just ty2' <- tcView ty2 = unify_ty env ty1 ty2' kco | CastTy ty1' co <- ty1 = if um_unif env ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -961,6 +961,11 @@ can_eq_nc' -> Type -> Type -- RHS, after and before type-synonym expansion, resp -> TcS (StopOrContinue Ct) +-- See Note [Comparing nullary type synonyms] in GHC.Core.Type. +can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1@(TyConApp tc1 []) _ps_ty1 (TyConApp tc2 []) _ps_ty2 + | tc1 == tc2 + = canEqReflexive ev eq_rel ty1 + -- Expand synonyms first; see Note [Type synonyms and canonicalization] can_eq_nc' flat rdr_env envs ev eq_rel ty1 ps_ty1 ty2 ps_ty2 | Just ty1' <- tcView ty1 = can_eq_nc' flat rdr_env envs ev eq_rel ty1' ps_ty1 ty2 ps_ty2 ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -120,7 +120,6 @@ import GHC.Types.Id as Id import GHC.Types.Name import GHC.Types.Var.Set import GHC.Builtin.Types -import GHC.Builtin.Types.Prim import GHC.Types.Var.Env import GHC.Types.Name.Env import GHC.Utils.Misc ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -1545,6 +1545,11 @@ tc_eq_type keep_syns vis_only orig_ty1 orig_ty2 = go orig_env orig_ty1 orig_ty2 where go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = True + go env t1 t2 | not keep_syns, Just t1' <- tcView t1 = go env t1' t2 go env t1 t2 | not keep_syns, Just t2' <- tcView t2 = go env t1 t2' ===================================== testsuite/tests/deSugar/should_compile/T2431.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 63, types: 43, coercions: 1, joins: 0/0} + = {terms: 63, types: 39, coercions: 1, joins: 0/0} --- RHS size: {terms: 2, types: 4, coercions: 1, joins: 0/0} +-- RHS size: {terms: 2, types: 3, coercions: 1, joins: 0/0} T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a [GblId[DataConWrapper], Caf=NoCafRefs, @@ -15,7 +15,7 @@ T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a T2431.$WRefl = \ (@a) -> T2431.Refl @a @a @~(
_N :: a GHC.Prim.~# a) --- RHS size: {terms: 4, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 7, coercions: 0, joins: 0/0} absurd :: forall a. (Int :~: Bool) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] absurd = \ (@a) (x :: Int :~: Bool) -> case x of { } ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -16,13 +16,12 @@ Derived class instances: = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(T14578.Wat f g a -> T14578.Wat f g a -> T14578.Wat f g a) ((GHC.Base.<>) @(T14578.App (Data.Functor.Compose.Compose f g) a)) GHC.Base.sconcat = GHC.Prim.coerce - @(GHC.Base.NonEmpty - (T14578.App (Data.Functor.Compose.Compose f g) a) + @(GHC.Base.NonEmpty (T14578.App (Data.Functor.Compose.Compose f g) a) -> T14578.App (Data.Functor.Compose.Compose f g) a) @(GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a) (GHC.Base.sconcat @@ -31,7 +30,7 @@ Derived class instances: = GHC.Prim.coerce @(b -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(b -> T14578.Wat f g a -> T14578.Wat f g a) (GHC.Base.stimes @(T14578.App (Data.Functor.Compose.Compose f g) a)) ===================================== testsuite/tests/plugins/plugins09.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/plugins10.stdout ===================================== @@ -6,7 +6,6 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: Language.Haskell.TH.Syntax typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat parsePlugin(a) ===================================== testsuite/tests/plugins/plugins11.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/static-plugins.stdout ===================================== @@ -5,11 +5,11 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: System.IO typeCheckPlugin (rn) -interfacePlugin: GHC.Prim -interfacePlugin: GHC.Show interfacePlugin: GHC.Types +interfacePlugin: GHC.Show interfacePlugin: GHC.TopHandler typeCheckPlugin (tc) +interfacePlugin: GHC.Prim interfacePlugin: GHC.CString interfacePlugin: GHC.Num.BigNat ==pure.1 ===================================== testsuite/tests/printer/T18052a.stderr ===================================== @@ -10,9 +10,9 @@ Dependent packages: [base-4.16.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 24, types: 61, coercions: 0, joins: 0/0} + = {terms: 24, types: 52, coercions: 0, joins: 0/0} --- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} T18052a.$b:||: :: forall {a} {b}. a -> b -> (a, b) [GblId, Arity=2, Unf=OtherCon []] T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) @@ -22,7 +22,7 @@ T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) [GblId] (+++) = ++ --- RHS size: {terms: 13, types: 20, coercions: 0, joins: 0/0} +-- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/0} T18052a.$m:||: :: forall {rep :: GHC.Types.RuntimeRep} {r :: TYPE rep} {a} {b}. (a, b) -> (a -> b -> r) -> ((# #) -> r) -> r ===================================== testsuite/tests/simplCore/should_compile/T13143.stderr ===================================== @@ -1,17 +1,17 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 71, types: 44, coercions: 0, joins: 0/0} + = {terms: 71, types: 40, coercions: 0, joins: 0/0} Rec { --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} T13143.$wf [InlPrag=NOINLINE, Occ=LoopBreaker] :: forall {a}. (# #) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] T13143.$wf = \ (@a) _ [Occ=Dead] -> T13143.$wf @a GHC.Prim.(##) end Rec } --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} f [InlPrag=[final]] :: forall a. Int -> a [GblId, Arity=1, ===================================== testsuite/tests/simplCore/should_compile/T18013.stderr ===================================== @@ -129,9 +129,9 @@ Rule fired: Class op fmap (BUILTIN) ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 52, types: 106, coercions: 17, joins: 0/1} + = {terms: 52, types: 101, coercions: 17, joins: 0/1} --- RHS size: {terms: 37, types: 87, coercions: 17, joins: 0/1} +-- RHS size: {terms: 37, types: 84, coercions: 17, joins: 0/1} mapMaybeRule :: forall a b. Rule IO a b -> Rule IO (Maybe a) (Maybe b) [GblId, ===================================== testsuite/tests/simplCore/should_compile/T7360.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 106, types: 47, coercions: 0, joins: 0/0} + = {terms: 106, types: 45, 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 @@ -31,7 +31,7 @@ T7360.fun4 :: () WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 20 0}] T7360.fun4 = fun1 T7360.Foo1 --- RHS size: {terms: 11, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 11, types: 7, coercions: 0, joins: 0/0} fun2 :: forall {a}. [a] -> ((), Int) [GblId, Arity=1, ===================================== testsuite/tests/typecheck/should_compile/T13032.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Desugar (after optimization) ==================== Result size of Desugar (after optimization) - = {terms: 13, types: 24, coercions: 0, joins: 0/0} + = {terms: 13, types: 18, coercions: 0, joins: 0/0} --- RHS size: {terms: 6, types: 11, coercions: 0, joins: 0/0} +-- RHS size: {terms: 6, types: 8, coercions: 0, joins: 0/0} f :: forall a b. (a ~ b) => a -> b -> Bool [LclIdX, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/12d3c9b3e3af0f264275085bd1f81031dddba919 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/12d3c9b3e3af0f264275085bd1f81031dddba919 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 Wed Nov 11 23:47:10 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 18:47:10 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Optimise nullary type constructor usage Message-ID: <5fac77feaa24_10ee3ffb94d1c6d8146009e@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 4ce6aeff by Ben Gamari at 2020-11-11T18:46:58-05:00 Optimise nullary type constructor usage During the compilation of programs GHC very frequently deals with the `Type` type, which is a synonym of `TYPE 'LiftedRep`. This patch teaches GHC to avoid expanding the `Type` synonym (and other nullary type synonyms) during type comparisons, saving a good amount of work. This optimisation is described in `Note [Comparing nullary type synonyms]`. To maximize the impact of this optimisation, we introduce a few special-cases to reduce `TYPE 'LiftedRep` to `Type`. See `Note [Prefer Type over TYPE 'LiftedPtrRep]`. Closes #17958. Metric Decrease: T18698b T1969 T12227 T12545 T12707 T14683 T3064 T5631 T5642 T9020 T9872a T13035 haddock.Cabal haddock.base - - - - - 22 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - + compiler/GHC/Builtin/Types/Prim.hs-boot - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/printer/T18052a.stderr - testsuite/tests/simplCore/should_compile/T13143.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -170,6 +170,7 @@ import GHC.Types.Var (VarBndr (Bndr)) import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE, mAX_SUM_SIZE ) import GHC.Unit.Module ( Module ) import GHC.Core.Type +import qualified GHC.Core.TyCo.Rep as TyCoRep (Type(TyConApp)) import GHC.Types.RepType import GHC.Core.DataCon import GHC.Core.ConLike @@ -691,7 +692,7 @@ constraintKindTyCon :: TyCon constraintKindTyCon = pcTyCon constraintKindTyConName Nothing [] [] liftedTypeKind, typeToTypeKind, constraintKind :: Kind -liftedTypeKind = tYPE liftedRepTy +liftedTypeKind = TyCoRep.TyConApp liftedTypeKindTyCon [] typeToTypeKind = liftedTypeKind `mkVisFunTyMany` liftedTypeKind constraintKind = mkTyConApp constraintKindTyCon [] @@ -1415,8 +1416,8 @@ runtimeRepTy = mkTyConTy runtimeRepTyCon -- type Type = tYPE 'LiftedRep liftedTypeKindTyCon :: TyCon liftedTypeKindTyCon = buildSynTyCon liftedTypeKindTyConName - [] liftedTypeKind [] - (tYPE liftedRepTy) + [] liftedTypeKind [] rhs + where rhs = TyCoRep.TyConApp tYPETyCon [liftedRepTy] runtimeRepTyCon :: TyCon runtimeRepTyCon = pcTyCon runtimeRepTyConName Nothing [] ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -551,10 +551,6 @@ mkPrimTcName built_in_syntax occ key tycon = mkWiredInName gHC_PRIM (mkTcOccFS occ) key (mkATyCon tycon) built_in_syntax ----------------------------- --- | Given a RuntimeRep, applies TYPE to it. --- see Note [TYPE and RuntimeRep] -tYPE :: Type -> Type -tYPE rr = TyConApp tYPETyCon [rr] -- Given a Multiplicity, applies FUN to it. functionWithMultiplicity :: Type -> Type ===================================== compiler/GHC/Builtin/Types/Prim.hs-boot ===================================== @@ -0,0 +1,5 @@ +module GHC.Builtin.Types.Prim where + +import GHC.Core.TyCon + +tYPETyCon :: TyCon ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -52,6 +52,7 @@ module GHC.Core.TyCo.Rep ( mkVisFunTyMany, mkVisFunTysMany, mkInvisFunTyMany, mkInvisFunTysMany, mkTyConApp, + tYPE, -- * Functions over binders TyCoBinder(..), TyCoVarBinder, TyBinder, @@ -90,8 +91,9 @@ import GHC.Core.TyCon import GHC.Core.Coercion.Axiom -- others -import GHC.Builtin.Names ( liftedTypeKindTyConKey, manyDataConKey ) -import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, manyDataConTy ) +import GHC.Builtin.Names ( liftedTypeKindTyConKey, liftedRepDataConKey, manyDataConKey, tYPETyConKey ) +import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, liftedTypeKind, manyDataConTy ) +import {-# SOURCE #-} GHC.Builtin.Types.Prim ( tYPETyCon ) import GHC.Types.Basic ( LeftOrRight(..), pickLR ) import GHC.Types.Unique ( hasKey ) import GHC.Utils.Outputable @@ -1018,12 +1020,50 @@ mkTyConApp tycon tys -- avoid reboxing every time `mkTyConApp` is called. = ASSERT2( null tys, ppr tycon $$ ppr tys ) manyDataConTy + -- See Note [Prefer Type over TYPE 'LiftedRep]. + | tycon `hasKey` tYPETyConKey + , [rep] <- tys + = tYPE rep + -- The catch-all case | otherwise = TyConApp tycon tys +-- Note [Prefer Type over TYPE 'LiftedRep] +-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +-- +-- The Core of nearly any program will have numerous occurrences of +-- @TYPE 'LiftedRep@ floating about. Consequently, we try hard to ensure +-- that operations on such types are efficient: +-- +-- * Instead of representing the lifted kind as +-- @TyConApp tYPETyCon [liftedRepDataCon]@ we rather prefer to +-- use the 'GHC.Types.Type' type synonym (available in GHC as +-- 'GHC.Builtin.Types.Prim.liftedTypeKind'). Note only is this a +-- smaller AST but it also guarantees sharing on the heap. +-- +-- * To avoid allocating 'TyConApp' constructors +-- 'GHC.Builtin.Types.Prim.tYPE' catches the lifted case and uses +-- `liftedTypeKind` instead of building an application. +-- +-- * Similarly, 'Type.mkTyConApp' catches applications of TYPE and +-- handles them using 'GHC.Builtin.Types.Prim.tYPE', ensuring +-- that it benefits from the optimisation described above. +-- +-- * Since 'liftedTypeKind' is a nullary type synonym application, +-- it benefits from the optimisation described in Note [Comparing +-- nullary type synonyms] in "GHC.Core.Type". + +-- | Given a RuntimeRep, applies TYPE to it. +-- See Note [TYPE and RuntimeRep] in GHC.Builtin.Types.Prim. +tYPE :: Type -> Type +tYPE (TyConApp tc []) + -- See Note [Prefer Type of TYPE 'LiftedRep] + | tc `hasKey` liftedRepDataConKey = liftedTypeKind -- TYPE 'LiftedRep +tYPE rr = TyConApp tYPETyCon [rr] + -- This is a single, global definition of the type `Type` -- Defined here so it is only allocated once. --- See Note [mkTyConApp and Type] +-- See Note [mkTyConApp and Type] in this module. liftedTypeKindTyConApp :: Type liftedTypeKindTyConApp = TyConApp liftedTypeKindTyCon [] ===================================== compiler/GHC/Core/TyCo/Subst.hs ===================================== @@ -424,6 +424,7 @@ zipTCvSubst tcvs tys -- | Generates the in-scope set for the 'TCvSubst' from the types in the -- incoming environment. No CoVars, please! mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst +mkTvSubstPrs [] = emptyTCvSubst mkTvSubstPrs prs = ASSERT2( onlyTyVarsAndNoCoercionTy, text "prs" <+> ppr prs ) mkTvSubst in_scope tenv ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2310,12 +2310,14 @@ expandSynTyCon_maybe -- ^ Expand a type synonym application, if any expandSynTyCon_maybe tc tys | SynonymTyCon { tyConTyVars = tvs, synTcRhs = rhs, tyConArity = arity } <- tc - = case tys `listLengthCmp` arity of - GT -> Just (tvs `zip` tys, rhs, drop arity tys) - EQ -> Just (tvs `zip` tys, rhs, []) - LT -> Nothing - | otherwise - = Nothing + = case tys of + [] -> Just ([], rhs, []) -- Avoid a bit of work in the case of nullary synonyms + _ -> case tys `listLengthCmp` arity of + GT -> Just (tvs `zip` tys, rhs, drop arity tys) + EQ -> Just (tvs `zip` tys, rhs, []) + LT -> Nothing + | otherwise + = Nothing ---------------- ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -382,15 +382,16 @@ how roles in kinds might work out. -} -- | Gives the typechecker view of a type. This unwraps synonyms but --- leaves 'Constraint' alone. c.f. coreView, which turns Constraint into --- TYPE LiftedRep. Returns Nothing if no unwrapping happens. +-- leaves 'Constraint' alone. c.f. 'coreView', which turns 'Constraint' into +-- @TYPE LiftedRep at . Returns 'Nothing' if no unwrapping happens. -- See also Note [coreView vs tcView] {-# INLINE tcView #-} tcView :: Type -> Maybe Type -tcView (TyConApp tc tys) | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') +tcView (TyConApp tc tys) + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- The free vars of 'rhs' should all be bound by 'tenv', so it's - -- ok to use 'substTy' here. + -- ok to use 'substTy' here (which is what expandSynTyConApp_maybe does). -- See also Note [The substitution invariant] in GHC.Core.TyCo.Subst. -- Its important to use mkAppTys, rather than (foldl AppTy), -- because the function part might well return a @@ -399,17 +400,16 @@ tcView _ = Nothing {-# INLINE coreView #-} coreView :: Type -> Maybe Type --- ^ This function Strips off the /top layer only/ of a type synonym +-- ^ This function strips off the /top layer only/ of a type synonym -- application (if any) its underlying representation type. --- Returns Nothing if there is nothing to look through. +-- Returns 'Nothing' if there is nothing to look through. -- This function considers 'Constraint' to be a synonym of @TYPE LiftedRep at . -- -- By being non-recursive and inlined, this case analysis gets efficiently -- joined onto the case analysis that the caller is already doing coreView ty@(TyConApp tc tys) - | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') - -- This equation is exactly like tcView + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- At the Core level, Constraint = Type -- See Note [coreView vs tcView] @@ -419,6 +419,25 @@ coreView ty@(TyConApp tc tys) coreView _ = Nothing +----------------------------------------------- +expandSynTyConApp_maybe :: TyCon -> [Type] -> Maybe Type +expandSynTyConApp_maybe tc tys + | Just (tvs, rhs) <- synTyConDefn_maybe tc + = case tys of + [] -> Just (mkAppTys rhs tys) + _ -> case tys `listLengthCmp` arity of + GT -> Just (mkAppTys rhs' (drop arity tys)) + EQ -> Just rhs' + LT -> Nothing + where + arity = tyConArity tc + rhs' = substTy (mkTvSubstPrs (tvs `zip` tys)) rhs + | otherwise + = Nothing +-- Without this INLINE the call to expandSynTyConApp_maybe in coreView +-- will result in an avoidable allocation. +{-# INLINE expandSynTyConApp_maybe #-} + {-# INLINE coreFullView #-} coreFullView :: Type -> Type -- ^ Iterates 'coreView' until there is no more to synonym to expand. @@ -2194,6 +2213,36 @@ But the left is an AppTy while the right is a TyConApp. The solution is to use repSplitAppTy_maybe to break up the TyConApp into its pieces and then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * TcCanonical.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See [Prefer Type over TYPE 'LiftedRep] in +GHC.Core.TyCo.Rep for details. + -} eqType :: Type -> Type -> Bool @@ -2305,6 +2354,10 @@ nonDetCmpTypeX env orig_t1 orig_t2 = -- Returns both the resulting ordering relation between the two types -- and whether either contains a cast. go :: RnEnv2 -> Type -> Type -> TypeOrdering + -- See Note [Comparing nullary type synonyms]. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = TEQ go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 | Just t2' <- coreView t2 = go env t1 t2' ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -957,7 +957,12 @@ unify_ty :: UMEnv -- Respects newtypes, PredTypes unify_ty env ty1 ty2 kco - -- Use tcView, not coreView. See Note [coreView vs tcView] in GHC.Core.Type. + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + | TyConApp tc1 [] <- ty1 + , TyConApp tc2 [] <- ty2 + , tc1 == tc2 = return () + + -- TODO: More commentary needed here | Just ty1' <- tcView ty1 = unify_ty env ty1' ty2 kco | Just ty2' <- tcView ty2 = unify_ty env ty1 ty2' kco | CastTy ty1' co <- ty1 = if um_unif env ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -961,6 +961,11 @@ can_eq_nc' -> Type -> Type -- RHS, after and before type-synonym expansion, resp -> TcS (StopOrContinue Ct) +-- See Note [Comparing nullary type synonyms] in GHC.Core.Type. +can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1@(TyConApp tc1 []) _ps_ty1 (TyConApp tc2 []) _ps_ty2 + | tc1 == tc2 + = canEqReflexive ev eq_rel ty1 + -- Expand synonyms first; see Note [Type synonyms and canonicalization] can_eq_nc' flat rdr_env envs ev eq_rel ty1 ps_ty1 ty2 ps_ty2 | Just ty1' <- tcView ty1 = can_eq_nc' flat rdr_env envs ev eq_rel ty1' ps_ty1 ty2 ps_ty2 ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -120,7 +120,6 @@ import GHC.Types.Id as Id import GHC.Types.Name import GHC.Types.Var.Set import GHC.Builtin.Types -import GHC.Builtin.Types.Prim import GHC.Types.Var.Env import GHC.Types.Name.Env import GHC.Utils.Misc ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -1545,6 +1545,11 @@ tc_eq_type keep_syns vis_only orig_ty1 orig_ty2 = go orig_env orig_ty1 orig_ty2 where go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = True + go env t1 t2 | not keep_syns, Just t1' <- tcView t1 = go env t1' t2 go env t1 t2 | not keep_syns, Just t2' <- tcView t2 = go env t1 t2' ===================================== testsuite/tests/deSugar/should_compile/T2431.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 63, types: 43, coercions: 1, joins: 0/0} + = {terms: 63, types: 39, coercions: 1, joins: 0/0} --- RHS size: {terms: 2, types: 4, coercions: 1, joins: 0/0} +-- RHS size: {terms: 2, types: 3, coercions: 1, joins: 0/0} T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a [GblId[DataConWrapper], Caf=NoCafRefs, @@ -15,7 +15,7 @@ T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a T2431.$WRefl = \ (@a) -> T2431.Refl @a @a @~(_N :: a GHC.Prim.~# a) --- RHS size: {terms: 4, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 7, coercions: 0, joins: 0/0} absurd :: forall a. (Int :~: Bool) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] absurd = \ (@a) (x :: Int :~: Bool) -> case x of { } ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -16,13 +16,12 @@ Derived class instances: = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(T14578.Wat f g a -> T14578.Wat f g a -> T14578.Wat f g a) ((GHC.Base.<>) @(T14578.App (Data.Functor.Compose.Compose f g) a)) GHC.Base.sconcat = GHC.Prim.coerce - @(GHC.Base.NonEmpty - (T14578.App (Data.Functor.Compose.Compose f g) a) + @(GHC.Base.NonEmpty (T14578.App (Data.Functor.Compose.Compose f g) a) -> T14578.App (Data.Functor.Compose.Compose f g) a) @(GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a) (GHC.Base.sconcat @@ -31,7 +30,7 @@ Derived class instances: = GHC.Prim.coerce @(b -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(b -> T14578.Wat f g a -> T14578.Wat f g a) (GHC.Base.stimes @(T14578.App (Data.Functor.Compose.Compose f g) a)) ===================================== testsuite/tests/plugins/plugins09.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/plugins10.stdout ===================================== @@ -6,7 +6,6 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: Language.Haskell.TH.Syntax typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat parsePlugin(a) ===================================== testsuite/tests/plugins/plugins11.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/static-plugins.stdout ===================================== @@ -5,11 +5,11 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: System.IO typeCheckPlugin (rn) -interfacePlugin: GHC.Prim -interfacePlugin: GHC.Show interfacePlugin: GHC.Types +interfacePlugin: GHC.Show interfacePlugin: GHC.TopHandler typeCheckPlugin (tc) +interfacePlugin: GHC.Prim interfacePlugin: GHC.CString interfacePlugin: GHC.Num.BigNat ==pure.1 ===================================== testsuite/tests/printer/T18052a.stderr ===================================== @@ -10,9 +10,9 @@ Dependent packages: [base-4.16.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 24, types: 61, coercions: 0, joins: 0/0} + = {terms: 24, types: 52, coercions: 0, joins: 0/0} --- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} T18052a.$b:||: :: forall {a} {b}. a -> b -> (a, b) [GblId, Arity=2, Unf=OtherCon []] T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) @@ -22,7 +22,7 @@ T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) [GblId] (+++) = ++ --- RHS size: {terms: 13, types: 20, coercions: 0, joins: 0/0} +-- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/0} T18052a.$m:||: :: forall {rep :: GHC.Types.RuntimeRep} {r :: TYPE rep} {a} {b}. (a, b) -> (a -> b -> r) -> ((# #) -> r) -> r ===================================== testsuite/tests/simplCore/should_compile/T13143.stderr ===================================== @@ -1,17 +1,17 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 71, types: 44, coercions: 0, joins: 0/0} + = {terms: 71, types: 40, coercions: 0, joins: 0/0} Rec { --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} T13143.$wf [InlPrag=NOINLINE, Occ=LoopBreaker] :: forall {a}. (# #) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] T13143.$wf = \ (@a) _ [Occ=Dead] -> T13143.$wf @a GHC.Prim.(##) end Rec } --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} f [InlPrag=[final]] :: forall a. Int -> a [GblId, Arity=1, ===================================== testsuite/tests/simplCore/should_compile/T18013.stderr ===================================== @@ -129,9 +129,9 @@ Rule fired: Class op fmap (BUILTIN) ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 52, types: 106, coercions: 17, joins: 0/1} + = {terms: 52, types: 101, coercions: 17, joins: 0/1} --- RHS size: {terms: 37, types: 87, coercions: 17, joins: 0/1} +-- RHS size: {terms: 37, types: 84, coercions: 17, joins: 0/1} mapMaybeRule :: forall a b. Rule IO a b -> Rule IO (Maybe a) (Maybe b) [GblId, ===================================== testsuite/tests/simplCore/should_compile/T7360.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 106, types: 47, coercions: 0, joins: 0/0} + = {terms: 106, types: 45, 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 @@ -31,7 +31,7 @@ T7360.fun4 :: () WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 20 0}] T7360.fun4 = fun1 T7360.Foo1 --- RHS size: {terms: 11, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 11, types: 7, coercions: 0, joins: 0/0} fun2 :: forall {a}. [a] -> ((), Int) [GblId, Arity=1, ===================================== testsuite/tests/typecheck/should_compile/T13032.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Desugar (after optimization) ==================== Result size of Desugar (after optimization) - = {terms: 13, types: 24, coercions: 0, joins: 0/0} + = {terms: 13, types: 18, coercions: 0, joins: 0/0} --- RHS size: {terms: 6, types: 11, coercions: 0, joins: 0/0} +-- RHS size: {terms: 6, types: 8, coercions: 0, joins: 0/0} f :: forall a b. (a ~ b) => a -> b -> Bool [LclIdX, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ce6aeff033d63d5ffe7f68ac8915f1721c0ddf0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4ce6aeff033d63d5ffe7f68ac8915f1721c0ddf0 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 Nov 12 00:48:06 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 19:48:06 -0500 Subject: [Git][ghc/ghc][wip/T18566] Fix docs Message-ID: <5fac864692d1b_10eeed3410014688a2@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 52ba5f9d by Ben Gamari at 2020-11-11T19:47:58-05:00 Fix docs - - - - - 2 changed files: - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst Changes: ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -51,7 +51,7 @@ Compiler Code using ``Void#`` now has to enable :extension:`UnboxedTuples`. ``ghc`` library -~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~ - The ``con_args`` field of ``ConDeclGADT`` has been renamed to ``con_g_args``. This is because the type of ``con_g_args`` is now different from the type of ===================================== docs/users_guide/profiling.rst ===================================== @@ -373,7 +373,7 @@ compiled program. ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard symbol: - .. code-block:: + .. code-block:: none pattern := '.' module := '*' View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/52ba5f9dd3b137836f9a9518694385de75c032f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/52ba5f9dd3b137836f9a9518694385de75c032f8 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 Nov 12 01:21:51 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 20:21:51 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/boxed-rep Message-ID: <5fac8e2f3c07b_43133fa6a819329458458@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/boxed-rep at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/boxed-rep 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 Nov 12 01:32:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 20:32:26 -0500 Subject: [Git][ghc/ghc][wip/boxed-rep] Implement BoxedRep proposal Message-ID: <5fac90aa7fc09_43133fa6a81663c06638d@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/boxed-rep at Glasgow Haskell Compiler / GHC Commits: c77ae1fb by Andrew Martin at 2020-11-11T20:30:29-05:00 Implement BoxedRep proposal This implements the BoxedRep proposal, refacoring the `RuntimeRep` hierarchy from: ```haskell data RuntimeRep = LiftedPtrRep | UnliftedPtrRep | ... ``` to ```haskell data RuntimeRep = BoxedRep Levity | ... data Levity = Lifted | Unlifted ``` Closes #17526. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/Enum.hs - libraries/base/GHC/Exts.hs - libraries/base/GHC/Show.hs - libraries/base/Unsafe/Coerce.hs - libraries/base/tests/T11334a.hs - libraries/base/tests/T11334a.stdout - libraries/binary - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/tests/ClosureSizeUtils.hs - libraries/ghc-prim/GHC/Types.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - testsuite/tests/backpack/should_run/T13955.bkp - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_fail/T17131.stderr - testsuite/tests/deriving/should_compile/T13154b.hs - testsuite/tests/deriving/should_fail/T12512.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c77ae1fbbe58614409765fb5f40f82a364dfc9c0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c77ae1fbbe58614409765fb5f40f82a364dfc9c0 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 Nov 12 02:12:51 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 21:12:51 -0500 Subject: [Git][ghc/ghc][wip/boxed-rep] Implement BoxedRep proposal Message-ID: <5fac9a2391b52_43133fa699c32ec073034@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/boxed-rep at Glasgow Haskell Compiler / GHC Commits: fa16578b by Andrew Martin at 2020-11-11T21:12:41-05:00 Implement BoxedRep proposal This implements the BoxedRep proposal, refacoring the `RuntimeRep` hierarchy from: ```haskell data RuntimeRep = LiftedPtrRep | UnliftedPtrRep | ... ``` to ```haskell data RuntimeRep = BoxedRep Levity | ... data Levity = Lifted | Unlifted ``` Closes #17526. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/Enum.hs - libraries/base/GHC/Exts.hs - libraries/base/GHC/Show.hs - libraries/base/Unsafe/Coerce.hs - libraries/base/tests/T11334a.hs - libraries/base/tests/T11334a.stdout - libraries/binary - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/tests/ClosureSizeUtils.hs - libraries/ghc-prim/GHC/Types.hs - libraries/template-haskell/Language/Haskell/TH/Syntax.hs - testsuite/tests/backpack/should_run/T13955.bkp - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_fail/T17131.stderr - testsuite/tests/deriving/should_compile/T13154b.hs - testsuite/tests/deriving/should_fail/T12512.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa16578b606480c7782c6bcb0845bae93840d376 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa16578b606480c7782c6bcb0845bae93840d376 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 Nov 12 02:22:03 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 21:22:03 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11 Message-ID: <5fac9c4b278a9_43133fa69863a320738d8@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: 8271dde5 by Ben Gamari at 2020-11-11T21:21:51-05:00 Bump time submodule to 1.11 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 9 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/Main.hs - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 179911e246516868ebd8b4d030a3780054d572f6 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit b609dabd2b79ecb2a52d28c3cce38f2c2c4c9840 ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit af5d89ccb44b4615898cdb547d35fe5cd62f5793 ===================================== utils/ghc-cabal/Main.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -28,6 +29,7 @@ import Distribution.Verbosity import qualified Distribution.InstalledPackageInfo as Installed import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Utils.ShortText (fromShortText) +import Distribution.Utils.Path (getSymbolicPath) import Control.Exception (bracket) import Control.Monad @@ -433,7 +435,7 @@ generate directory distdir config_args variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd), - variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), + variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8271dde51d7f5311bd8a09a8f9292db86b908f65 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8271dde51d7f5311bd8a09a8f9292db86b908f65 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 Nov 12 02:37:58 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 21:37:58 -0500 Subject: [Git][ghc/ghc][wip/T18566] 11 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags Message-ID: <5faca00664940_43133fa68f3640c87475@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 40a4f83a by Ben Gamari at 2020-11-11T21:37:52-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 73b71342 by Ben Gamari at 2020-11-11T21:37:53-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Types/Var.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - docs/users_guide/profiling.rst - includes/rts/Linker.h - includes/rts/storage/GC.h - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52ba5f9dd3b137836f9a9518694385de75c032f8...73b71342e1a7c7e3efdc251710b2d0ac26a078e5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52ba5f9dd3b137836f9a9518694385de75c032f8...73b71342e1a7c7e3efdc251710b2d0ac26a078e5 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 Nov 12 04:07:13 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 11 Nov 2020 23:07:13 -0500 Subject: [Git][ghc/ghc][wip/T18566] Introduce -fprof-callers flag Message-ID: <5facb4f1c051d_43133fa68b5ab920805cb@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 54160a2e by Ben Gamari at 2020-11-11T23:07:06-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 19 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,223 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = withUserStyle alwaysQualify DefaultDepth $ + hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = pattern + where + pattern = star <|> wildcard <|> char <|> end + star = PChar '*' <$ P.string "\\*" <*> pattern + wildcard = do + void $ P.char '*' + PWildcard <$> pattern + char = PChar <$> P.anyChar <*> pattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +157,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = gopt Opt_ProfCallerCcs dflags maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +224,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +377,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. @@ -510,6 +518,9 @@ doCorePass CoreDoSpecialising = {-# SCC "Specialise" #-} doCorePass CoreDoSpecConstr = {-# SCC "SpecConstr" #-} specConstrProgram +doCorePass CoreAddCallerCcs = {-# SCC "AddCallerCcs" #-} + addCallerCostCentres + doCorePass CoreDoPrintCore = observe printCore doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat doCorePass CoreDoNothing = return ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -216,6 +216,7 @@ data GeneralFlag -- profiling opts | Opt_AutoSccsOnIndividualCafs | Opt_ProfCountEntries + | Opt_ProfCallerCcs -- misc opts | Opt_Pp ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -699,6 +700,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1313,6 +1315,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2947,6 +2950,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -3468,6 +3475,7 @@ fFlagsDeps = [ flagSpec "print-typechecker-elaboration" Opt_PrintTypecheckerElaboration, flagSpec "prof-cafs" Opt_AutoSccsOnIndividualCafs, flagSpec "prof-count-entries" Opt_ProfCountEntries, + flagSpec "prof-callers" Opt_ProfCallerCcs, flagSpec "regs-graph" Opt_RegsGraph, flagSpec "regs-iterative" Opt_RegsIterative, depFlagSpec' "rewrite-rules" Opt_EnableRewriteRules @@ -3787,6 +3795,7 @@ defaultFlags settings Opt_OmitYields, Opt_PrintBindContents, Opt_ProfCountEntries, + Opt_ProfCallerCcs, Opt_SharedImplib, Opt_SimplPreInlining, Opt_VersionMacros @@ -4548,6 +4557,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-fprof-callers=⟨name⟩`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ @@ -47,7 +51,7 @@ Compiler Code using ``Void#`` now has to enable :extension:`UnboxedTuples`. ``ghc`` library -~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~ - The ``con_args`` field of ``ConDeclGADT`` has been renamed to ``con_g_args``. This is because the type of ``con_g_args`` is now different from the type of ===================================== docs/users_guide/profiling.rst ===================================== @@ -358,6 +358,38 @@ Automatically placing cost-centres GHC has a number of flags for automatically inserting cost-centres into the compiled program. +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + Note that these cost-centres are added late in compilation (after + simplification) and consequently the names may be slightly different than + they appear in the source program (e.g. a call to ``f`` may inlined with + its wrapper, resulting in an occurrence of its worker, ``$wf``). + + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: none + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample ===================================== @@ -0,0 +1,79 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc1 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (58 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +clause.clause' Main Main.hs:(63,12)-(65,57) 29.3 37.5 +insert Main Main.hs:(108,1)-(112,8) 27.6 1.7 +disin Main Main.hs:(74,1)-(83,11) 22.4 49.5 +disin.dp Main Main.hs:80:3-14 5.2 0.0 +conjunct Main Main.hs:(70,1)-(71,18) 5.2 0.0 +unicl Main Main.hs:(176,1)-(180,36) 3.4 1.1 +tautclause Main Main.hs:173:1-49 3.4 3.7 +disin.dq Main Main.hs:81:3-14 3.4 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 0.0 2.6 +split.split' Main Main.hs:(165,11)-(166,28) 0.0 2.3 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 22.4 49.5 36.2 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 5.2 0.0 5.2 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 5.2 0.0 5.2 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 3.4 0.0 3.4 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 0.0 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 0.0 2.3 0.0 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 3.4 1.1 63.8 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 0.0 2.6 60.3 46.9 + tautclause Main Main.hs:173:1-49 295 37422 3.4 3.7 3.4 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 56.9 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 56.9 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 29.3 37.5 56.9 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 27.6 1.7 27.6 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample ===================================== @@ -0,0 +1,78 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc2 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (59 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 32.2 49.5 +insert Main Main.hs:(108,1)-(112,8) 27.1 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 25.4 37.5 +tautclause Main Main.hs:173:1-49 3.4 3.7 +split.split' Main Main.hs:(165,11)-(166,28) 3.4 2.3 +disin.dq Main Main.hs:81:3-14 3.4 0.0 +conjunct Main Main.hs:(70,1)-(71,18) 3.4 0.0 +clause Main Main.hs:(61,1)-(65,57) 1.7 1.4 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 0.0 2.6 +unicl Main Main.hs:(176,1)-(180,36) 0.0 1.1 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 32.2 49.5 39.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 3.4 0.0 3.4 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 0.0 0.0 0.0 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 3.4 0.0 3.4 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.4 2.3 3.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 0.0 1.1 57.6 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 0.0 2.6 57.6 46.9 + tautclause Main Main.hs:173:1-49 295 37422 3.4 3.7 3.4 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 54.2 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 1.7 1.4 54.2 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 25.4 37.5 52.5 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 27.1 1.7 27.1 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample ===================================== @@ -0,0 +1,79 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc3 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (55 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 27.3 49.5 +insert Main Main.hs:(108,1)-(112,8) 25.5 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 18.2 37.5 +conjunct Main Main.hs:(70,1)-(71,18) 10.9 0.0 +tautclause Main Main.hs:173:1-49 9.1 3.7 +unicl.unicl'.cp Main Main.hs:180:24-36 1.8 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 1.8 2.6 +unicl Main Main.hs:(176,1)-(180,36) 1.8 1.1 +split.split' Main Main.hs:(165,11)-(166,28) 1.8 2.3 +disin.dq Main Main.hs:81:3-14 1.8 0.0 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 27.3 49.5 40.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 10.9 0.0 10.9 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 0.0 0.0 0.0 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 1.8 0.0 1.8 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 1.8 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 1.8 2.3 1.8 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 1.8 1.1 58.2 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 1.8 2.6 56.4 46.9 + tautclause Main Main.hs:173:1-49 295 37422 9.1 3.7 9.1 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 1.8 0.0 45.5 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 43.6 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 18.2 37.5 43.6 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 25.5 1.7 25.5 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,19 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) +setTestOpts(extra_files(['Main.hs'])) +setTestOpts(extra_run_opts('7')) + +# N.B. Main.hs is stolen from heapprof001. + +test('CallerCc1', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=*.concat -O0']) + +test('CallerCc2', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.concat -O0']) + +test('CallerCc3', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.con*at -O0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54160a2ebf84de74aac4d09cbbb5afd711aab44c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54160a2ebf84de74aac4d09cbbb5afd711aab44c 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 Nov 12 04:27:03 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 11 Nov 2020 23:27:03 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags Message-ID: <5facb997c720c_43133fa6b83d49d0906b@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 882c3716 by Ben Gamari at 2020-11-11T23:26:55-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - acda600c by Sebastian Graf at 2020-11-11T23:26:56-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 7628ed61 by Sebastian Graf at 2020-11-11T23:26:56-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - 3620c087 by Ben Gamari at 2020-11-11T23:26:56-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Types/Var.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - includes/RtsAPI.h - includes/rts/EventLogWriter.h - includes/rts/Linker.h - includes/rts/storage/GC.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa6c717c66fd545edb37f952064268f0622d89b0...3620c0877e5c753b05f9e0a3fbf710f91de967e9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aa6c717c66fd545edb37f952064268f0622d89b0...3620c0877e5c753b05f9e0a3fbf710f91de967e9 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 Nov 12 05:57:35 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 00:57:35 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5faccecff2850_43133fa6a9210e3c984d@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 19b84b8f by Moritz Angermann at 2020-11-12T05:57:21+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring - libraries/ghc-bignum/ghc-bignum.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19b84b8f1fbe3e443e7e5288d306a4ae724297b1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19b84b8f1fbe3e443e7e5288d306a4ae724297b1 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 Nov 12 06:18:59 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 01:18:59 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5facd3d3b8424_43133fa68ef1c3941005f6@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 8b244f90 by Moritz Angermann at 2020-11-12T06:18:33+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring - libraries/ghc-bignum/ghc-bignum.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b244f90b8ff9f05c815c4f8914912f7b06a021f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8b244f90b8ff9f05c815c4f8914912f7b06a021f 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 Nov 12 06:19:20 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 01:19:20 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-ncg] 125 commits: [Sized Cmm] properly retain sizes. Message-ID: <5facd3e88573b_43133fa699d7ee3c101896@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC Commits: 19b84b8f by Moritz Angermann at 2020-11-12T05:57:21+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 0a64be45 by Moritz Angermann at 2020-11-12T06:17:22+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - d17ec357 by Moritz Angermann at 2020-11-12T06:17:22+00:00 Initial NCG - - - - - 6bf3c5bc by Moritz Angermann at 2020-11-12T06:17:22+00:00 Address Takenobu's comments - - - - - ede58bf3 by Moritz Angermann at 2020-11-12T06:17:22+00:00 Fix floating points handling of NaNs - - - - - 154219d3 by Moritz Angermann at 2020-11-12T06:17:22+00:00 Add basic Graph Coloring support - - - - - e503a4c7 by Moritz Angermann at 2020-11-12T06:17:22+00:00 Drop debug - - - - - 9cdee43a by Moritz Angermann at 2020-11-12T06:17:22+00:00 Add primops_match.cmm testsuite - - - - - b8f071d8 by Moritz Angermann at 2020-11-12T06:17:22+00:00 Fix -NaN for real this time. - - - - - 61d7367f by Moritz Angermann at 2020-11-12T06:17:22+00:00 Adds nan test. - - - - - c13fd20f by Moritz Angermann at 2020-11-12T06:17:23+00:00 no show - - - - - 710f281b by Moritz Angermann at 2020-11-12T06:17:23+00:00 Some notes on PIC - - - - - 9e65d7bc by Moritz Angermann at 2020-11-12T06:17:23+00:00 Properly load W32 with bit 31 set. - - - - - d6f8d3e2 by Moritz Angermann at 2020-11-12T06:17:23+00:00 better relocation logging - - - - - 19b9576e by Moritz Angermann at 2020-11-12T06:17:23+00:00 Add AsmOpt Flags - - - - - 18608958 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Adds ANN instruction. I wish I had a `pad n` function for SDoc, that would interact with the layout, and just pad what ever was printed so far to `n` chars. - - - - - 5c6d98e6 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Drop dead 32bit logic. - - - - - 6102a2ca by Moritz Angermann at 2020-11-12T06:17:23+00:00 Add Show CmmExpr instances. Why would we want this, when we have Outputtable CmmExpr? Quite often when working on Code Generators, we want to structurally match on a Cmm Expression. Having to recover the Cmm Expression from its Outputtable text is not always trivial, and requires substantial effort. By having a Show instance, we can almost copy the definition to match on. - - - - - af8fb4e7 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Drop duplicate show instance for CLabel now. - - - - - aa4a1e8f by Moritz Angermann at 2020-11-12T06:17:23+00:00 Add link, lest I keep forgetting it. - - - - - 24eb3ab8 by Moritz Angermann at 2020-11-12T06:17:23+00:00 inline comments with // - - - - - 641c10b2 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Some optimizations; not yet sure if safe or not. - - - - - 67fb8a0e by Moritz Angermann at 2020-11-12T06:17:23+00:00 Add latest opt changes. - - - - - b0f111b1 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Address Takenobu Tani's comments. Thanks! - - - - - b5e703b7 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Fix gcd :blush: - - - - - cdd3b8f4 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Overflow guard - - - - - 9a10675d by Moritz Angermann at 2020-11-12T06:17:23+00:00 More annotations. - - - - - 0c0244d9 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Revert "Overflow guard" They are Integers not Ints. This reverts commit 3ef94e593a2848cf2bdc4251f5be34536642675f. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 7533571a by Moritz Angermann at 2020-11-12T06:17:23+00:00 Add CmmAssign and CmmStore comments - - - - - f6579037 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Minor address mode changes - - - - - 66dca21d by Moritz Angermann at 2020-11-12T06:17:23+00:00 More Amode optimizations - - - - - 247f2573 by Moritz Angermann at 2020-11-12T06:17:23+00:00 I think this shoudl work for all Registers, not just CmmGlobal - - - - - 03f88c81 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Opt <<, >> - - - - - 927e7715 by Moritz Angermann at 2020-11-12T06:17:23+00:00 Opt &&, || - - - - - 99af19db by Moritz Angermann at 2020-11-12T06:17:23+00:00 Add branch ANNotations. - - - - - f336ac89 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Disable Opt &&, ||, due to mask immediate - - - - - 7fe06b7b by Moritz Angermann at 2020-11-12T06:17:24+00:00 Opt: Adds CBZ, CBNZ - - - - - f3a634aa by Moritz Angermann at 2020-11-12T06:17:24+00:00 More generic CBZ, CBNZ - - - - - add007c0 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Fixup - - - - - 66834310 by Moritz Angermann at 2020-11-12T06:17:24+00:00 very rudimentary bitmask support. - - - - - 38c94f28 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Add some more bitmasks - - - - - a86131db by Moritz Angermann at 2020-11-12T06:17:24+00:00 Opt STR - - - - - d6cd96e7 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Fixup - - - - - a6b5010d by Moritz Angermann at 2020-11-12T06:17:24+00:00 Fix MO_SF_Conv - - - - - 0c574b98 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Add Comment re MO_Memcpy - - - - - c1f70267 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Always PIC via GOT - - - - - 3b6c3ae2 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Fix up generated assembly. Don't generate identity moves e.g. mov x18, x18 - - - - - 590db641 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Drop superfulous alignment generation. - - - - - 20450cd3 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Hadrian :fire: - - - - - 09ee538e by Moritz Angermann at 2020-11-12T06:17:24+00:00 Address Tekenobus comments. Thanks! - - - - - 3c15a0c4 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Adds J to distinguish jumps from B. Maybe this would be better handled with a phantom type? - - - - - 9bd54729 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Make sp an Operand - - - - - 1060261f by Moritz Angermann at 2020-11-12T06:17:24+00:00 allocMoreStack This is still broken, as we can't spill into arbitrary ranges. Hence while we can allocate extra space, we can't really spill past 4096 offsets due to the immediat having to be encoded. This leaves us with a max of 512 spill slots. We *can* work around this if we change the sp though. - - - - - dba041d4 by Moritz Angermann at 2020-11-12T06:17:24+00:00 [Spill/Reload] Spill Around :fire: - - - - - f7a0b2ed by Moritz Angermann at 2020-11-12T06:17:24+00:00 Address Takenobus observations! Thanks! - - - - - 6649fa32 by Moritz Angermann at 2020-11-12T06:17:24+00:00 :sob: - - - - - 8b4d3125 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Revert the Spill/Reload fix; undo :got: loads. This breaks dynamic, however we can build a working stage2 compiler with the following mk/build.mk BuildFlavour = quick ifneq "$(BuildFlavour)" "" include mk/flavours/$(BuildFlavour).mk endif STRIP_CMD = : DYNAMIC_BY_DEFAULT = NO DYNAMIC_GHC_PROGRAMS = NO - - - - - f0585086 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Disable trivial deadlock detection - - - - - 014e56e6 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Adds some annotations - - - - - 47e049e6 by Moritz Angermann at 2020-11-12T06:17:24+00:00 Trying to get PIC right. - - - - - 56dc2be2 by Moritz Angermann at 2020-11-12T06:17:25+00:00 [aarch64] Fix spill/reload - - - - - 482dc4a4 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Try to get PIC right. - - - - - 8e116adc by Moritz Angermann at 2020-11-12T06:17:25+00:00 Spill/Reload only need a smaller window - - - - - b64f7d45 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Drop bad/useless optimisation This was due to not handling PIC symbols correctly and injecting CmmLoad as we do on other platforms, but this doesn't translate to aarch64's got lookups. - - - - - dededbb4 by Moritz Angermann at 2020-11-12T06:17:25+00:00 B is b - - - - - 1231cd43 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Fix CCall |Now mark used registers properly for the Register Allocator. - - - - - d5ec8b63 by Moritz Angermann at 2020-11-12T06:17:25+00:00 :sob: - - - - - 2fee7c85 by Moritz Angermann at 2020-11-12T06:17:25+00:00 :sob: :sob: - - - - - 0b25d139 by Moritz Angermann at 2020-11-12T06:17:25+00:00 :sob: Segfault no 3. This showed up in T4114 - - - - - dea38aec by Moritz Angermann at 2020-11-12T06:17:25+00:00 Add mkComment to `Instruction` - - - - - 80e947bc by Moritz Angermann at 2020-11-12T06:17:25+00:00 Use mkComment for debugging - - - - - 3a8337f9 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Fix T4114 crashes T4114 causes this codepath to show up. - - - - - 976f6161 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Cleanup some compiler warnings - - - - - 5d6ec913 by Moritz Angermann at 2020-11-12T06:17:25+00:00 [Aarch64] No div-by-zero; disable test. - - - - - 979a410f by Moritz Angermann at 2020-11-12T06:17:25+00:00 Simplify aarch64 StgRun We don't need to do the callee save register dance. The compiler will do this for us already: 0000000000000000 <StgRun>: 0: a9b653f3 stp x19, x20, [sp, #-160]! 4: a9015bf5 stp x21, x22, [sp, #16] 8: a90263f7 stp x23, x24, [sp, #32] c: a9036bf9 stp x25, x26, [sp, #48] 10: a90473fb stp x27, x28, [sp, #64] 14: f9002bfe str x30, [sp, #80] 18: 6d0627e8 stp d8, d9, [sp, #96] 1c: 6d072fea stp d10, d11, [sp, #112] 20: 6d0837ec stp d12, d13, [sp, #128] 24: 6d093fee stp d14, d15, [sp, #144] 28: a9bf47f0 stp x16, x17, [sp, #-16]! 2c: d14013ff sub sp, sp, #0x4, lsl #12 30: aa0103f3 mov x19, x1 34: d61f0000 br x0 0000000000000038 <StgReturn>: 38: 914013ff add sp, sp, #0x4, lsl #12 3c: aa1603e0 mov x0, x22 40: a8c147f0 ldp x16, x17, [sp], #16 44: a9415bf5 ldp x21, x22, [sp, #16] 48: a94263f7 ldp x23, x24, [sp, #32] 4c: a9436bf9 ldp x25, x26, [sp, #48] 50: a94473fb ldp x27, x28, [sp, #64] 54: f9402bfe ldr x30, [sp, #80] 58: 6d4627e8 ldp d8, d9, [sp, #96] 5c: 6d472fea ldp d10, d11, [sp, #112] 60: 6d4837ec ldp d12, d13, [sp, #128] 64: 6d493fee ldp d14, d15, [sp, #144] 68: a8ca53f3 ldp x19, x20, [sp], #160 6c: d65f03c0 ret - - - - - c8dd4ec2 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Use ip0 for spills/reloads - - - - - 84520236 by Moritz Angermann at 2020-11-12T06:17:25+00:00 :broom: Cleanup - - - - - 54b453fb by Moritz Angermann at 2020-11-12T06:17:25+00:00 Adds LLVM (AArch64) CI Job - - - - - fa3b1cd2 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Add validate as well. - - - - - 01e2c160 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Revert "Simplify aarch64 StgRun" This reverts commit f27472c0483db2382344f4a8f4c1b2a192d98725. - - - - - 4798ef1c by Moritz Angermann at 2020-11-12T06:17:25+00:00 Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md - - - - - 6d27405c by Moritz Angermann at 2020-11-12T06:17:25+00:00 Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md - - - - - 390b103f by Moritz Angermann at 2020-11-12T06:17:25+00:00 [macOS] support for arm64 Adding basic changes to support arm64-apple-darwin - - - - - 5a126fd8 by Moritz Angermann at 2020-11-12T06:17:25+00:00 Add CLabel logic - - - - - a2a0e07a by Moritz Angermann at 2020-11-12T06:17:26+00:00 [configure] make arm64-apple-darwin an LLVM Target This is required as the llvm toolchain doesn't like aarch64-apple-darwin, and only accepts arm64-apple-darwin. - - - - - 410a1509 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [configure] disable subsections_via_symbols on arm64/macOS LLVM's clang will not emit relocation entries for assembly local (L prefixed) symbols. In the presence of subsections_via_symbols, the linker is free to strip dead symbols from the object code, however due to the lack of relocations for assembly local symbols, branches will be invalidated through this dead stripping. As such we must not permit subsections_via_symbols on arm64/macho-o. - - - - - 0714c8ca by Moritz Angermann at 2020-11-12T06:17:26+00:00 [arm64/mach-o] adrp/ldr symbol names This will break elf. We need to find a better solution for this symbol naming is platform dependent here. :got: / @gotpage :got_lo12: / @gotpageoff :lo12: / @pageoff - - - - - 101c3a2c by Moritz Angermann at 2020-11-12T06:17:26+00:00 [WIP] symbol garbage Naming is hard. Supporting assembler and linker even harder. L is the assembly local prefix l is the linker local prefix L is not relocated at all. l is relocated, but fails to for conditional branches. Send help! - - - - - 7812209d by Moritz Angermann at 2020-11-12T06:17:26+00:00 [MachO] cleanup compiler warnings - - - - - ea24f4f9 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [macOS/arm64] do not use read_only_relocs on arm64 The linker simply doesn't support it and will complain loudly. - - - - - 5617c112 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [Storage/Adjustor] Drop size check in allocExec This is violated by ghci, in InfoTable.hsc we call _allocateExec with a size that does not guarantee to be of ffi_closure size. Other allocateExec implementations do not have this check either; I highly doubt it's sensible to have this check in the presence of ghci's allocateExec calls. - - - - - 32739907 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [linker/elf] better errors (with error message) - - - - - 7a01dfbe by Moritz Angermann at 2020-11-12T06:17:26+00:00 [darwin] always pic, ios AND mac AND tv AND ... - - - - - 9c3f0f8b by Moritz Angermann at 2020-11-12T06:17:26+00:00 [aarch64/codegen] pack ccall arguments on darwin This is annoying, but the darwinpcs does not match the default aapcs :facepalm: - - - - - 8ee9c135 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [linker:MachO] split PLT logic out. Why was this missing in the first place? It's now a bit more aligned to the elf plt logic. - - - - - 6db8fbd7 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [configure] fix LLVMTarget when native uname -p return "arm", hence we can't work with target_cpu, but need to match on the target triple. - - - - - 71c75c71 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [testsuite] fix subsections_via_symbols test - - - - - 2e9532ee by Moritz Angermann at 2020-11-12T06:17:26+00:00 [testsuite] FixT11649 - - - - - 71dde819 by Moritz Angermann at 2020-11-12T06:17:26+00:00 Fix conc059 test - - - - - 7a75bbf7 by Moritz Angermann at 2020-11-12T06:17:26+00:00 WIP: fix ghci adjustors on aarch64/arm (infotables) - - - - - 376d8a86 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [DWARF] Enable only on elf platforms - - - - - 71ab682f by Moritz Angermann at 2020-11-12T06:17:26+00:00 [Testsuite/LLVM] Fix T5681, T7571, T8131b - - - - - b256abba by Moritz Angermann at 2020-11-12T06:17:26+00:00 [testsuite/darwin] fix tests ghcilink003, ghcilink006 - - - - - adf82185 by Moritz Angermann at 2020-11-12T06:17:26+00:00 Fix linker_error2 - - - - - 6ca34c8f by Moritz Angermann at 2020-11-12T06:17:26+00:00 Sized Hints - - - - - 94ee3730 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [Testsuite/arm64] Fix test derefnull - - - - - 543a1925 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [testsuite/arm64] fix section_alignment - - - - - c9b4ff39 by Moritz Angermann at 2020-11-12T06:17:26+00:00 [macOS/arm64] darwinpcs :facepalm: - - - - - c79e9c2b by Moritz Angermann at 2020-11-12T06:17:26+00:00 [aarch64/darwin] ifdef for got lables. This should ideally be some runtime flag, but it would need access to the platform. - - - - - 93fc3390 by Moritz Angermann at 2020-11-12T06:17:27+00:00 [aarch64/rts] fix missing prototypes - - - - - 54654813 by Moritz Angermann at 2020-11-12T06:17:27+00:00 Int has Word size in Haskell. - - - - - d0a59675 by Moritz Angermann at 2020-11-12T06:17:27+00:00 [debug only] warn on hint/arg mismatch - - - - - ee2d541f by Moritz Angermann at 2020-11-12T06:17:27+00:00 [AArch64 NCG] User argument format rather than hint. - - - - - 9579a4ed by Moritz Angermann at 2020-11-12T06:17:27+00:00 [Debug] Fix CmmFloat warnings. - - - - - 21ecdb1e by Moritz Angermann at 2020-11-12T06:17:27+00:00 [aarch64/elf] fixup elf symbols - - - - - 43011dbd by Moritz Angermann at 2020-11-12T06:17:27+00:00 :facepalm: - - - - - 7f1c3754 by Moritz Angermann at 2020-11-12T06:17:27+00:00 :facepalm: - - - - - 4e663448 by Moritz Angermann at 2020-11-12T06:17:27+00:00 [Adjustors] Proper allocator handling. - - - - - 0f2cd07a by Moritz Angermann at 2020-11-12T06:17:27+00:00 Revert "[AArch64] Aarch64 Always PIC" This reverts commit 921276592218211f441fcf011fc52441e3a2f0a6. - - - - - 92dbdb4c by Moritz Angermann at 2020-11-12T06:17:27+00:00 Revert "[Storage/Adjustor] Drop size check in allocExec" This reverts commit 37a62ae956a25e5832fbe125a4d8ee556fd11042. - - - - - 27caf3f3 by Moritz Angermann at 2020-11-12T06:17:27+00:00 [Storage] Reinstate check; add comment. - - - - - 17365a82 by Moritz Angermann at 2020-11-12T06:17:27+00:00 [AArch64] Aarch64 Always PIC - - - - - 8cf9749e by Moritz Angermann at 2020-11-12T06:17:27+00:00 [testsuite] static001 is not broken anymore. - - - - - 8abe5f30 by Moritz Angermann at 2020-11-12T06:17:27+00:00 Revert "Sized Hints" This reverts commit 65cbfcc10e7ad32dd04ebce011860f5b557eacac. - - - - - 0cc7cdb3 by Moritz Angermann at 2020-11-12T06:17:27+00:00 fix up rebase - - - - - 17 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Type.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm.hs - + compiler/GHC/CmmToAsm/AArch64.hs - + compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - + compiler/GHC/CmmToAsm/AArch64/Cond.hs - + compiler/GHC/CmmToAsm/AArch64/Instr.hs - + compiler/GHC/CmmToAsm/AArch64/LLVM Test Results.md The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a110435790495f25b750d0ef65aab6e0813ade11...0cc7cdb3645892e98daddfafc56ad1c0b597688c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a110435790495f25b750d0ef65aab6e0813ade11...0cc7cdb3645892e98daddfafc56ad1c0b597688c 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 Nov 12 09:10:48 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 04:10:48 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5facfc18d66f7_4313a4d7e8411792a@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 5697ee50 by Moritz Angermann at 2020-11-12T09:10:36+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring - libraries/ghc-bignum/ghc-bignum.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5697ee50b8d6fb865cf08df03e282459ebb2d5fe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5697ee50b8d6fb865cf08df03e282459ebb2d5fe 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 Nov 12 09:57:26 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 12 Nov 2020 04:57:26 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fad07068ae1b_43133fa6a9121e901406e4@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: f5071724 by Ben Gamari at 2020-11-12T04:57:13-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 0dbded64 by Sebastian Graf at 2020-11-12T04:57:13-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - fdc795f6 by Sebastian Graf at 2020-11-12T04:57:14-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - 101d8904 by Ben Gamari at 2020-11-12T04:57:14-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 18 changed files: - .gitlab-ci.yml - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T Changes: ===================================== .gitlab-ci.yml ===================================== @@ -307,16 +307,20 @@ hadrian-ghc-in-ghci: - .gitlab/ci.sh setup - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache variables: GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache lint-base: extends: .lint-params script: - hadrian/build -c -j stage1:lib:base - hadrian/build -j lint:base - cache: - key: lint ############################################################ # Validation via Pipelines (make) ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity at@(AT oss _) ar + | oss `lengthAtMost` ar = at + | otherwise = AT (take ar oss) topDiv + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== includes/RtsAPI.h ===================================== @@ -17,7 +17,6 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" -#include "rts/EventLogWriter.h" /* * Running the scheduler @@ -58,6 +57,9 @@ typedef struct CapabilityPublic_ { StgRegTable r; } CapabilityPublic; +/* N.B. this needs the Capability declaration above. */ +#include "rts/EventLogWriter.h" + /* ---------------------------------------------------------------------------- RTS configuration settings, for passing to hs_init_ghc() ------------------------------------------------------------------------- */ ===================================== includes/rts/EventLogWriter.h ===================================== @@ -68,3 +68,8 @@ bool startEventLogging(const EventLogWriter *writer); * Stop event logging and destroy the current EventLogWriter. */ void endEventLogging(void); + +/* + * Flush the eventlog. cap can be NULL if one is not held. + */ +void flushEventLog(Capability **cap); ===================================== libraries/base/Debug/Trace.hs ===================================== @@ -37,6 +37,7 @@ module Debug.Trace ( -- $eventlog_tracing traceEvent, traceEventIO, + flushEventLog, -- * Execution phase markers -- $markers @@ -319,3 +320,11 @@ traceMarkerIO :: String -> IO () traceMarkerIO msg = GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> case traceMarker# p s of s' -> (# s', () #) + +-- | Immediately flush the event log, if enabled. +-- +-- @since 4.15.0.0 +flushEventLog :: IO () +flushEventLog = c_flushEventLog nullPtr + +foreign import ccall "flushEventLog" c_flushEventLog :: Ptr () -> IO () ===================================== rts/Capability.c ===================================== @@ -23,6 +23,7 @@ #include "Schedule.h" #include "Sparks.h" #include "Trace.h" +#include "eventlog/EventLog.h" // for flushLocalEventsBuf #include "sm/GC.h" // for gcWorkerThread() #include "STM.h" #include "RtsUtils.h" @@ -982,6 +983,10 @@ yieldCapability debugTrace(DEBUG_nonmoving_gc, "Flushing update remembered set blocks..."); break; + case SYNC_FLUSH_EVENT_LOG: + flushLocalEventsBuf(cap); + break; + default: break; } ===================================== rts/Capability.h ===================================== @@ -267,7 +267,8 @@ typedef enum { SYNC_OTHER, SYNC_GC_SEQ, SYNC_GC_PAR, - SYNC_FLUSH_UPD_REM_SET + SYNC_FLUSH_UPD_REM_SET, + SYNC_FLUSH_EVENT_LOG } SyncType; // ===================================== rts/RtsSymbols.c ===================================== @@ -594,6 +594,7 @@ SymI_HasProto(__word_encodeFloat) \ SymI_HasProto(stg_atomicallyzh) \ SymI_HasProto(barf) \ + SymI_HasProto(flushEventLog) \ SymI_HasProto(deRefStablePtr) \ SymI_HasProto(debugBelch) \ SymI_HasProto(errorBelch) \ ===================================== rts/Schedule.c ===================================== @@ -2070,7 +2070,7 @@ forkProcess(HsStablePtr *entry stopTimer(); // See #4074 #if defined(TRACING) - flushEventLog(); // so that child won't inherit dirty file buffers + flushAllCapsEventsBufs(); // so that child won't inherit dirty file buffers #endif pid = fork(); ===================================== rts/Trace.c ===================================== @@ -118,10 +118,10 @@ void resetTracing (void) restartEventLogging(); } -void flushTrace (void) +void flushTrace () { if (eventlog_enabled) { - flushEventLog(); + flushEventLog(NULL); } } ===================================== rts/Trace.h ===================================== @@ -319,7 +319,6 @@ void traceConcSweepEnd(void); void traceConcUpdRemSetFlush(Capability *cap); void traceNonmovingHeapCensus(uint32_t log_blk_size, const struct NonmovingAllocCensus *census); - void flushTrace(void); #else /* !TRACING */ ===================================== rts/eventlog/EventLog.c ===================================== @@ -16,6 +16,7 @@ #include "RtsUtils.h" #include "Stats.h" #include "EventLog.h" +#include "Schedule.h" #include #include @@ -270,8 +271,8 @@ stopEventLogWriter(void) } } -void -flushEventLog(void) +static void +flushEventLogWriter(void) { if (event_log_writer != NULL && event_log_writer->flushEventLog != NULL) { @@ -1484,7 +1485,7 @@ void printAndClearEventBuf (EventsBuf *ebuf) "printAndClearEventLog: could not flush event log\n" ); resetEventsBuf(ebuf); - flushEventLog(); + flushEventLogWriter(); return; } @@ -1566,6 +1567,40 @@ void postEventType(EventsBuf *eb, EventType *et) postInt32(eb, EVENT_ET_END); } +void flushLocalEventsBuf(Capability *cap) +{ + EventsBuf *eb = &capEventBuf[cap->no]; + printAndClearEventBuf(eb); +} + +// Flush all capabilities' event buffers when we already hold all capabilities. +// Used during forkProcess. +void flushAllCapsEventsBufs() +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + + for (unsigned int i=0; i < n_capabilities; i++) { + flushLocalEventsBuf(capabilities[i]); + } + flushEventLogWriter(); +} + +void flushEventLog(Capability **cap USED_IF_THREADS) +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + +#if defined(THREADED_RTS) + Task *task = getTask(); + stopAllCapabilitiesWith(cap, task, SYNC_FLUSH_EVENT_LOG); + releaseAllCapabilities(n_capabilities, cap ? *cap : NULL, task); +#endif + flushEventLogWriter(); +} + #else enum EventLogStatus eventLogStatus(void) @@ -1579,4 +1614,6 @@ bool startEventLogging(const EventLogWriter *writer STG_UNUSED) { void endEventLogging(void) {} +void flushEventLog(Capability **cap STG_UNUSED) {} + #endif /* TRACING */ ===================================== rts/eventlog/EventLog.h ===================================== @@ -28,8 +28,10 @@ void initEventLogging(void); void restartEventLogging(void); void freeEventLogging(void); void abortEventLogging(void); // #4512 - after fork child needs to abort -void flushEventLog(void); // event log inherited from parent void moreCapEventBufs (uint32_t from, uint32_t to); +void flushLocalEventsBuf(Capability *cap); +void flushAllCapsEventsBufs(void); +void flushAllEventsBufs(Capability *cap); /* * Post a scheduler event to the capability's event buffer (an event @@ -175,6 +177,9 @@ void postNonmovingHeapCensus(int log_blk_size, #else /* !TRACING */ +INLINE_HEADER void flushLocalEventsBuf(Capability *cap STG_UNUSED) +{ /* nothing */ } + INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, EventTypeNum tag STG_UNUSED, StgThreadID id STG_UNUSED, ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3620c0877e5c753b05f9e0a3fbf710f91de967e9...101d89040d2889559a9bfe3a43541d3fd0a72f1d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3620c0877e5c753b05f9e0a3fbf710f91de967e9...101d89040d2889559a9bfe3a43541d3fd0a72f1d 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 Nov 12 11:52:54 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Thu, 12 Nov 2020 06:52:54 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fad2216347fb_43133fa68e11f5981529d@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: a0aa594e by Daniel Rogozin at 2020-11-12T14:52:29+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0aa594e5fba43586a336e78f879ca078dd5b9e6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0aa594e5fba43586a336e78f879ca078dd5b9e6 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 Nov 12 13:09:52 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 08:09:52 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 15 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fad34205b1a_4313d7f779c159255@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - e0989e1c by Moritz Angermann at 2020-11-12T08:09:50-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5697ee50b8d6fb865cf08df03e282459ebb2d5fe...e0989e1c4c4e4249fbc1bf4e920625585f191689 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5697ee50b8d6fb865cf08df03e282459ebb2d5fe...e0989e1c4c4e4249fbc1bf4e920625585f191689 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 Nov 12 14:24:24 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Thu, 12 Nov 2020 09:24:24 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] 15 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fad4598dce2a_43133fa68f32a45417106@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 16943de3 by Daniel Rogozin at 2020-11-12T17:23:50+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a0aa594e5fba43586a336e78f879ca078dd5b9e6...16943de3607c68d593a5680ff5d66fa4897b4d1d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a0aa594e5fba43586a336e78f879ca078dd5b9e6...16943de3607c68d593a5680ff5d66fa4897b4d1d 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 Nov 12 14:45:15 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Thu, 12 Nov 2020 09:45:15 -0500 Subject: [Git][ghc/ghc][wip/con-info-ghc-debug] Info table rather than closure Message-ID: <5fad4a7b498db_43133fa6cddab8cc1767b2@gitlab.haskell.org.mail> Matthew Pickering pushed to branch wip/con-info-ghc-debug at Glasgow Haskell Compiler / GHC Commits: d7068676 by Matthew Pickering at 2020-11-06T17:02:05+00:00 Info table rather than closure - - - - - 3 changed files: - includes/rts/IPE.h - rts/IPE.c - rts/PrimOps.cmm Changes: ===================================== includes/rts/IPE.h ===================================== @@ -14,4 +14,4 @@ #pragma once void registerInfoProvList(InfoProvEnt **cc_list); -InfoProvEnt * lookupIPE(StgClosure *info); \ No newline at end of file +InfoProvEnt * lookupIPE(StgInfoTable *info); \ No newline at end of file ===================================== rts/IPE.c ===================================== @@ -69,18 +69,17 @@ void registerInfoProvList(InfoProvEnt **ent_list) // MP: TODO: This should not be a linear search, need to improve // the IPE_LIST structure -InfoProvEnt * lookupIPE(StgClosure *clos) +InfoProvEnt * lookupIPE(StgInfoTable *info) { - StgInfoTable * info; - info = GET_INFO(clos); InfoProvEnt *ip, *next; - //printf("%p\n", info); +// printf("%p\n", info); //printf("%p\n\n", clos); for (ip = IPE_LIST; ip != NULL; ip = next) { +// printf("%p\n", ip->info); if (ip->info == info) { //printf("Found %p\n", ip->info); return ip; } next = ip->link; } -} \ No newline at end of file +} ===================================== rts/PrimOps.cmm ===================================== @@ -2412,7 +2412,9 @@ stg_closureSizzezh (P_ clos) stg_whereFromzh (P_ clos) { P_ ipe; - (ipe) = foreign "C" lookupIPE(UNTAG(clos) "ptr"); + W_ info; + info = GET_INFO(UNTAG(clos)); + (ipe) = foreign "C" lookupIPE(info "ptr"); return (ipe); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d706867646ba4702a4069b413d7b6b37d66324b7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d706867646ba4702a4069b413d7b6b37d66324b7 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 Nov 12 15:05:42 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 10:05:42 -0500 Subject: [Git][ghc/ghc][wip/T18733] 237 commits: Use UnitId in the backend instead of Unit Message-ID: <5fad4f465e958_43133fa69954d04c181665@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18733 at Glasgow Haskell Compiler / GHC Commits: 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.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/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Monad.hs → compiler/GHC/Cmm/Parser/Monad.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c8ac8b20a747b060bca3d4bd81edf1a5750ba88...5353fd500b1e92636cd9d45274585fd88a915ff6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c8ac8b20a747b060bca3d4bd81edf1a5750ba88...5353fd500b1e92636cd9d45274585fd88a915ff6 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 Nov 12 15:27:48 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 12 Nov 2020 10:27:48 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fad54745aab3_4313850ad401993e2@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 6d8e2a61 by Ben Gamari at 2020-11-12T10:27:35-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 3562aef6 by Sebastian Graf at 2020-11-12T10:27:36-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - b6c7240b by Sebastian Graf at 2020-11-12T10:27:36-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - fa238692 by Sylvain Henry at 2020-11-12T10:27:40-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 0afd5bf3 by Sylvain Henry at 2020-11-12T10:27:40-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - c5f66025 by Ben Gamari at 2020-11-12T10:27:41-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - docs/users_guide/extending_ghc.rst - ghc/GHCi/UI.hs - ghc/Main.hs - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/101d89040d2889559a9bfe3a43541d3fd0a72f1d...c5f66025685ad3c308708ccce6e2dd83e38e3e2b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/101d89040d2889559a9bfe3a43541d3fd0a72f1d...c5f66025685ad3c308708ccce6e2dd83e38e3e2b 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 Nov 12 15:47:10 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Thu, 12 Nov 2020 10:47:10 -0500 Subject: [Git][ghc/ghc][wip/T18043] 128 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fad58fe4f317_4313ee1e04820475a@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/T18043 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 386b42b8 by Ben Gamari at 2020-11-12T10:47:07-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs - compiler/GHC/Core/Opt/Monad.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/47508fa96aa5175d6ceab00d3fb73af91840a104...386b42b885832f817bf914e24c99eea19cea48da -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/47508fa96aa5175d6ceab00d3fb73af91840a104...386b42b885832f817bf914e24c99eea19cea48da 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 Nov 12 20:38:36 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Thu, 12 Nov 2020 15:38:36 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Use tcSplitTyConApp_maybe in can_eq_nc' Message-ID: <5fad9d4cdee3d_43133fa6a825404824693d@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 5df5c897 by Richard Eisenberg at 2020-11-12T15:38:17-05:00 Use tcSplitTyConApp_maybe in can_eq_nc' - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Canonical.hs Changes: ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -1032,8 +1032,12 @@ can_eq_nc' _flat _rdr_env _envs ev eq_rel -- Decompose type constructor applications -- NB: we have expanded type synonyms already -can_eq_nc' _flat _rdr_env _envs ev eq_rel (TyConApp tc1 tys1) _ (TyConApp tc2 tys2) _ - | not (isTypeFamilyTyCon tc1) +can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1 _ ty2 _ + | Just (tc1, tys1) <- tcSplitTyConApp_maybe ty1 + , Just (tc2, tys2) <- tcSplitTyConApp_maybe ty2 -- + -- we want to catch e.g. Maybe Int ~ (Int -> Int) here for better + -- error messages; hence no direct match on TyConApp + , not (isTypeFamilyTyCon tc1) , not (isTypeFamilyTyCon tc2) = canTyConApp ev eq_rel tc1 tys1 tc2 tys2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5df5c897bf27d1906d50999c0059d95289a74570 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5df5c897bf27d1906d50999c0059d95289a74570 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 Nov 12 20:58:12 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 12 Nov 2020 15:58:12 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5fada1e42d4b5_43133fa6cde303c42525e0@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 06ab8525 by Sebastian Graf at 2020-11-12T15:58:00-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 34d24dcf by Sebastian Graf at 2020-11-12T15:58:00-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - fcef3644 by Sylvain Henry at 2020-11-12T15:58:03-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - efe95b67 by Sylvain Henry at 2020-11-12T15:58:03-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - 5fc856b8 by Ben Gamari at 2020-11-12T15:58:03-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - docs/users_guide/extending_ghc.rst - ghc/GHCi/UI.hs - ghc/Main.hs - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T - testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs - testsuite/tests/plugins/static-plugins.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5f66025685ad3c308708ccce6e2dd83e38e3e2b...5fc856b8ffcc3641bebc9094c58a630e9eb0d185 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5f66025685ad3c308708ccce6e2dd83e38e3e2b...5fc856b8ffcc3641bebc9094c58a630e9eb0d185 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 Nov 12 21:23:53 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 16:23:53 -0500 Subject: [Git][ghc/ghc][wip/T18566] 2 commits: testsuite: Refactor CountParserDeps Message-ID: <5fada7e9d3ee8_4313f3a7870258094@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 132cffce by Ben Gamari at 2020-11-12T15:28:52-05:00 testsuite: Refactor CountParserDeps - - - - - 74491199 by Ben Gamari at 2020-11-12T15:28:52-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 20 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - testsuite/tests/parser/should_run/CountParserDeps.hs - + testsuite/tests/parser/should_run/CountParserDeps.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,223 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = withUserStyle alwaysQualify DefaultDepth $ + hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling " <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = pattern + where + pattern = star <|> wildcard <|> char <|> end + star = PChar '*' <$ P.string "\\*" <*> pattern + wildcard = do + void $ P.char '*' + PWildcard <$> pattern + char = PChar <$> P.anyChar <*> pattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -16,6 +16,7 @@ import GHC.Driver.Session import GHC.Driver.Ppr import GHC.Driver.Plugins ( withPlugins, installCoreToDos ) import GHC.Driver.Env +import GHC.Platform.Ways ( hasWay, Way(WayProf) ) import GHC.Core import GHC.Core.Opt.CSE ( cseProgram ) @@ -44,6 +45,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +158,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = ways dflags `hasWay` WayProf maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +225,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +378,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. @@ -510,6 +519,9 @@ doCorePass CoreDoSpecialising = {-# SCC "Specialise" #-} doCorePass CoreDoSpecConstr = {-# SCC "SpecConstr" #-} specConstrProgram +doCorePass CoreAddCallerCcs = {-# SCC "AddCallerCcs" #-} + addCallerCostCentres + doCorePass CoreDoPrintCore = observe printCore doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat doCorePass CoreDoNothing = return ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -699,6 +700,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1313,6 +1315,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2947,6 +2950,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -4548,6 +4555,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-fprof-callers=⟨name⟩`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ @@ -47,7 +51,7 @@ Compiler Code using ``Void#`` now has to enable :extension:`UnboxedTuples`. ``ghc`` library -~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~ - The ``con_args`` field of ``ConDeclGADT`` has been renamed to ``con_g_args``. This is because the type of ``con_g_args`` is now different from the type of ===================================== docs/users_guide/profiling.rst ===================================== @@ -358,6 +358,38 @@ Automatically placing cost-centres GHC has a number of flags for automatically inserting cost-centres into the compiled program. +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + Note that these cost-centres are added late in compilation (after + simplification) and consequently the names may be slightly different than + they appear in the source program (e.g. a call to ``f`` may inlined with + its wrapper, resulting in an occurrence of its worker, ``$wf``). + + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: none + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic ===================================== testsuite/tests/parser/should_run/CountParserDeps.hs ===================================== @@ -29,12 +29,8 @@ main = do [libdir] <- getArgs modules <- parserDeps libdir let num = sizeUniqSet modules - max_num = 234 - min_num = max_num - 10 -- so that we don't forget to change the number - -- when the number of dependencies decreases - -- putStrLn $ "Found " ++ show num ++ " parser module dependencies" - -- forM_ (map moduleNameString $ nonDetEltsUniqSet modules) putStrLn - unless (num <= max_num && num >= min_num) $ exitWith (ExitFailure num) + putStrLn $ "Found " ++ show num ++ " parser module dependencies" + forM_ (map moduleNameString $ nonDetEltsUniqSet modules) putStrLn parserDeps :: FilePath -> IO (UniqSet ModuleName) parserDeps libdir = ===================================== testsuite/tests/parser/should_run/CountParserDeps.stdout ===================================== @@ -0,0 +1,236 @@ +Found 235 parser module dependencies +GHC.Builtin.Names +GHC.Builtin.PrimOps +GHC.Builtin.Types +GHC.Builtin.Types.Prim +GHC.Builtin.Uniques +GHC.ByteCode.Types +GHC.Cmm +GHC.Cmm.BlockId +GHC.Cmm.CLabel +GHC.Cmm.Dataflow.Block +GHC.Cmm.Dataflow.Collections +GHC.Cmm.Dataflow.Graph +GHC.Cmm.Dataflow.Label +GHC.Cmm.Expr +GHC.Cmm.MachOp +GHC.Cmm.Node +GHC.Cmm.Switch +GHC.Cmm.Type +GHC.CmmToAsm.CFG.Weight +GHC.CmmToAsm.Config +GHC.Core +GHC.Core.Class +GHC.Core.Coercion +GHC.Core.Coercion.Axiom +GHC.Core.Coercion.Opt +GHC.Core.ConLike +GHC.Core.DataCon +GHC.Core.FVs +GHC.Core.FamInstEnv +GHC.Core.InstEnv +GHC.Core.Lint +GHC.Core.Make +GHC.Core.Map +GHC.Core.Multiplicity +GHC.Core.Opt.Arity +GHC.Core.Opt.CallerCC +GHC.Core.Opt.ConstantFold +GHC.Core.Opt.Monad +GHC.Core.Opt.OccurAnal +GHC.Core.PatSyn +GHC.Core.Ppr +GHC.Core.Predicate +GHC.Core.Seq +GHC.Core.SimpleOpt +GHC.Core.Stats +GHC.Core.Subst +GHC.Core.TyCo.FVs +GHC.Core.TyCo.Ppr +GHC.Core.TyCo.Rep +GHC.Core.TyCo.Subst +GHC.Core.TyCo.Tidy +GHC.Core.TyCon +GHC.Core.TyCon.Env +GHC.Core.TyCon.RecWalk +GHC.Core.Type +GHC.Core.Unfold +GHC.Core.Unfold.Make +GHC.Core.Unify +GHC.Core.UsageEnv +GHC.Core.Utils +GHC.CoreToIface +GHC.Data.Bag +GHC.Data.BooleanFormula +GHC.Data.EnumSet +GHC.Data.FastMutInt +GHC.Data.FastString +GHC.Data.FastString.Env +GHC.Data.FiniteMap +GHC.Data.Graph.Directed +GHC.Data.IOEnv +GHC.Data.List.SetOps +GHC.Data.Maybe +GHC.Data.OrdList +GHC.Data.Pair +GHC.Data.Stream +GHC.Data.StringBuffer +GHC.Data.TrieMap +GHC.Driver.Backend +GHC.Driver.Backpack.Syntax +GHC.Driver.CmdLine +GHC.Driver.Env +GHC.Driver.Flags +GHC.Driver.Hooks +GHC.Driver.Monad +GHC.Driver.Phases +GHC.Driver.Pipeline.Monad +GHC.Driver.Plugins +GHC.Driver.Ppr +GHC.Driver.Session +GHC.Hs +GHC.Hs.Binds +GHC.Hs.Decls +GHC.Hs.Doc +GHC.Hs.Expr +GHC.Hs.Extension +GHC.Hs.ImpExp +GHC.Hs.Instances +GHC.Hs.Lit +GHC.Hs.Pat +GHC.Hs.Type +GHC.Hs.Utils +GHC.Iface.Ext.Fields +GHC.Iface.Recomp.Binary +GHC.Iface.Syntax +GHC.Iface.Type +GHC.Linker.Types +GHC.Parser +GHC.Parser.Annotation +GHC.Parser.CharClass +GHC.Parser.Errors +GHC.Parser.Lexer +GHC.Parser.PostProcess +GHC.Parser.PostProcess.Haddock +GHC.Parser.Types +GHC.Platform +GHC.Platform.ARM +GHC.Platform.ARM64 +GHC.Platform.Constants +GHC.Platform.NoRegs +GHC.Platform.PPC +GHC.Platform.Profile +GHC.Platform.Reg +GHC.Platform.Reg.Class +GHC.Platform.Regs +GHC.Platform.S390X +GHC.Platform.SPARC +GHC.Platform.Ways +GHC.Platform.X86 +GHC.Platform.X86_64 +GHC.Prelude +GHC.Runtime.Context +GHC.Runtime.Eval.Types +GHC.Runtime.Heap.Layout +GHC.Runtime.Interpreter.Types +GHC.Settings +GHC.Settings.Config +GHC.Settings.Constants +GHC.Stg.Syntax +GHC.StgToCmm.Types +GHC.SysTools.BaseDir +GHC.SysTools.FileCleanup +GHC.SysTools.Terminal +GHC.Tc.Errors.Hole.FitTypes +GHC.Tc.Types +GHC.Tc.Types.Constraint +GHC.Tc.Types.Evidence +GHC.Tc.Types.Origin +GHC.Tc.Utils.TcType +GHC.Types.Annotations +GHC.Types.Avail +GHC.Types.Basic +GHC.Types.CompleteMatch +GHC.Types.CostCentre +GHC.Types.CostCentre.State +GHC.Types.Cpr +GHC.Types.Demand +GHC.Types.Error +GHC.Types.FieldLabel +GHC.Types.Fixity +GHC.Types.Fixity.Env +GHC.Types.ForeignCall +GHC.Types.ForeignStubs +GHC.Types.HpcInfo +GHC.Types.Id +GHC.Types.Id.Info +GHC.Types.Id.Make +GHC.Types.Literal +GHC.Types.Meta +GHC.Types.Name +GHC.Types.Name.Cache +GHC.Types.Name.Env +GHC.Types.Name.Occurrence +GHC.Types.Name.Ppr +GHC.Types.Name.Reader +GHC.Types.Name.Set +GHC.Types.RepType +GHC.Types.SafeHaskell +GHC.Types.SourceError +GHC.Types.SourceFile +GHC.Types.SourceText +GHC.Types.SrcLoc +GHC.Types.Target +GHC.Types.TyThing +GHC.Types.TypeEnv +GHC.Types.Unique +GHC.Types.Unique.DFM +GHC.Types.Unique.DSet +GHC.Types.Unique.FM +GHC.Types.Unique.Set +GHC.Types.Unique.Supply +GHC.Types.Var +GHC.Types.Var.Env +GHC.Types.Var.Set +GHC.Unit +GHC.Unit.External +GHC.Unit.Finder.Types +GHC.Unit.Home +GHC.Unit.Home.ModInfo +GHC.Unit.Info +GHC.Unit.Module +GHC.Unit.Module.Deps +GHC.Unit.Module.Env +GHC.Unit.Module.Graph +GHC.Unit.Module.Imported +GHC.Unit.Module.Location +GHC.Unit.Module.ModDetails +GHC.Unit.Module.ModGuts +GHC.Unit.Module.ModIface +GHC.Unit.Module.ModSummary +GHC.Unit.Module.Name +GHC.Unit.Module.Status +GHC.Unit.Module.Warnings +GHC.Unit.Parser +GHC.Unit.Ppr +GHC.Unit.State +GHC.Unit.Types +GHC.Utils.Binary +GHC.Utils.Binary.Typeable +GHC.Utils.BufHandle +GHC.Utils.CliOption +GHC.Utils.Error +GHC.Utils.Exception +GHC.Utils.FV +GHC.Utils.Fingerprint +GHC.Utils.GlobalVars +GHC.Utils.IO.Unsafe +GHC.Utils.Json +GHC.Utils.Lexeme +GHC.Utils.Misc +GHC.Utils.Monad +GHC.Utils.Outputable +GHC.Utils.Panic +GHC.Utils.Panic.Plain +GHC.Utils.Ppr +GHC.Utils.Ppr.Colour ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample ===================================== @@ -0,0 +1,79 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc1 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (58 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +clause.clause' Main Main.hs:(63,12)-(65,57) 29.3 37.5 +insert Main Main.hs:(108,1)-(112,8) 27.6 1.7 +disin Main Main.hs:(74,1)-(83,11) 22.4 49.5 +disin.dp Main Main.hs:80:3-14 5.2 0.0 +conjunct Main Main.hs:(70,1)-(71,18) 5.2 0.0 +unicl Main Main.hs:(176,1)-(180,36) 3.4 1.1 +tautclause Main Main.hs:173:1-49 3.4 3.7 +disin.dq Main Main.hs:81:3-14 3.4 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 0.0 2.6 +split.split' Main Main.hs:(165,11)-(166,28) 0.0 2.3 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 22.4 49.5 36.2 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 5.2 0.0 5.2 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 5.2 0.0 5.2 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 3.4 0.0 3.4 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 0.0 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 0.0 2.3 0.0 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 3.4 1.1 63.8 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 0.0 2.6 60.3 46.9 + tautclause Main Main.hs:173:1-49 295 37422 3.4 3.7 3.4 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 56.9 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 56.9 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 29.3 37.5 56.9 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 27.6 1.7 27.6 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample ===================================== @@ -0,0 +1,78 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc2 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (59 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 32.2 49.5 +insert Main Main.hs:(108,1)-(112,8) 27.1 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 25.4 37.5 +tautclause Main Main.hs:173:1-49 3.4 3.7 +split.split' Main Main.hs:(165,11)-(166,28) 3.4 2.3 +disin.dq Main Main.hs:81:3-14 3.4 0.0 +conjunct Main Main.hs:(70,1)-(71,18) 3.4 0.0 +clause Main Main.hs:(61,1)-(65,57) 1.7 1.4 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 0.0 2.6 +unicl Main Main.hs:(176,1)-(180,36) 0.0 1.1 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 32.2 49.5 39.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 3.4 0.0 3.4 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 0.0 0.0 0.0 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 3.4 0.0 3.4 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.4 2.3 3.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 0.0 1.1 57.6 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 0.0 2.6 57.6 46.9 + tautclause Main Main.hs:173:1-49 295 37422 3.4 3.7 3.4 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 54.2 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 1.7 1.4 54.2 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 25.4 37.5 52.5 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 27.1 1.7 27.1 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample ===================================== @@ -0,0 +1,79 @@ + Wed Nov 11 23:04 2020 Time and Allocation Profiling Report (Final) + + CallerCc3 +RTS -hc -p -RTS 7 + + total time = 0.06 secs (55 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 27.3 49.5 +insert Main Main.hs:(108,1)-(112,8) 25.5 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 18.2 37.5 +conjunct Main Main.hs:(70,1)-(71,18) 10.9 0.0 +tautclause Main Main.hs:173:1-49 9.1 3.7 +unicl.unicl'.cp Main Main.hs:180:24-36 1.8 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 1.8 2.6 +unicl Main Main.hs:(176,1)-(180,36) 1.8 1.1 +split.split' Main Main.hs:(165,11)-(166,28) 1.8 2.3 +disin.dq Main Main.hs:81:3-14 1.8 0.0 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 27.3 49.5 40.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 10.9 0.0 10.9 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 0.0 0.0 0.0 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 1.8 0.0 1.8 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 1.8 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 1.8 2.3 1.8 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 1.8 1.1 58.2 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 1.8 2.6 56.4 46.9 + tautclause Main Main.hs:173:1-49 295 37422 9.1 3.7 9.1 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 1.8 0.0 45.5 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 43.6 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 18.2 37.5 43.6 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 25.5 1.7 25.5 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,19 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) +setTestOpts(extra_files(['Main.hs'])) +setTestOpts(extra_run_opts('7')) + +# N.B. Main.hs is stolen from heapprof001. + +test('CallerCc1', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=*.concat -O0']) + +test('CallerCc2', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.concat -O0']) + +test('CallerCc3', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.con*at -O0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54160a2ebf84de74aac4d09cbbb5afd711aab44c...744911991324d708bb154f5918c09906e71e1a49 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54160a2ebf84de74aac4d09cbbb5afd711aab44c...744911991324d708bb154f5918c09906e71e1a49 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 Nov 12 21:24:56 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Thu, 12 Nov 2020 16:24:56 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Try removing (2b). Let's see what the testsuite says Message-ID: <5fada828a54cb_43133fa67eaf4cf425884f@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: fa4f1058 by Richard Eisenberg at 2020-11-12T16:24:38-05:00 Try removing (2b). Let's see what the testsuite says - - - - - 4 changed files: - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -122,7 +122,7 @@ module GHC.Core.Coercion ( simplifyArgsWorker, - badCoercionHole, badCoercionHoleCo, + hasCoercionHoleTy, hasCoercionHoleCo, HoleSet, coercionHolesOfType, coercionHolesOfCo ) where @@ -3050,9 +3050,9 @@ simplifyArgsWorker orig_ki_binders orig_inner_ki orig_fvs %************************************************************************ -} -bad_co_hole_ty :: Type -> Monoid.Any -bad_co_hole_co :: Coercion -> Monoid.Any -(bad_co_hole_ty, _, bad_co_hole_co, _) +has_co_hole_ty :: Type -> Monoid.Any +has_co_hole_co :: Coercion -> Monoid.Any +(has_co_hole_ty, _, has_co_hole_co, _) = foldTyCo folder () where folder = TyCoFolder { tcf_view = const Nothing @@ -3065,15 +3065,13 @@ bad_co_hole_co :: Coercion -> Monoid.Any const2 :: a -> b -> c -> a const2 x _ _ = x --- | Is there a blocking coercion hole in this type? See --- "GHC.Tc.Solver.Canonical" Note [Equalities with incompatible kinds] -badCoercionHole :: Type -> Bool -badCoercionHole = Monoid.getAny . bad_co_hole_ty +-- | Is there a coercion hole in this type? +hasCoercionHoleTy :: Type -> Bool +hasCoercionHoleTy = Monoid.getAny . has_co_hole_ty --- | Is there a blocking coercion hole in this coercion? See --- GHC.Tc.Solver.Canonical Note [Equalities with incompatible kinds] -badCoercionHoleCo :: Coercion -> Bool -badCoercionHoleCo = Monoid.getAny . bad_co_hole_co +-- | Is there a coercion hole in this coercion? +hasCoercionHoleCo :: Coercion -> Bool +hasCoercionHoleCo = Monoid.getAny . has_co_hole_co -- | A set of 'CoercionHole's type HoleSet = UniqSet CoercionHole ===================================== compiler/GHC/Core/Map/Type.hs ===================================== @@ -154,7 +154,7 @@ data TypeMapX a -- Note that there is no tyconapp case; see Note [Equality on AppTys] in GHC.Core.Type -- | Squeeze out any synonyms, and change TyConApps to nested AppTys. Why the --- last one? See Note [Equality on AppTys] in "GHC.Core.Type" +-- last one? See Note [Equality on AppTys] in GHC.Core.Type -- -- Note, however, that we keep Constraint and Type apart here, despite the fact -- that they are both synonyms of TYPE 'LiftedRep (see #11715). ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -43,7 +43,6 @@ import GHC.Builtin.Types ( anyTypeOfKind ) import GHC.Driver.Session( DynFlags ) import GHC.Types.Name.Set import GHC.Types.Name.Reader -import GHC.Types.Unique.Set import GHC.Hs.Type( HsIPName(..) ) import GHC.Data.Pair @@ -109,7 +108,7 @@ canonicalize (CQuantCan (QCI { qci_ev = ev, qci_pend_sc = pend_sc })) = canForAll ev pend_sc canonicalize (CIrredCan { cc_ev = ev, cc_status = status }) - | BlockedCIS holes <- status +{- "RAE" | BlockedCIS holes <- status , isEmptyUniqSet holes -- this would be a CEqCan if it weren't for the blocking hole, but that -- block has been removed. Warp straight to canEqCanLHSHomo. @@ -128,7 +127,7 @@ canonicalize (CIrredCan { cc_ev = ev, cc_status = status }) _ -> canIrred status ev } -- NB: The Irred is /not/ insoluble, so the special case below -- for insolubles (the direct call to canEqNC) does not apply. - +-} | EqPred eq_rel ty1 ty2 <- classifyPredType (ctEvPred ev) = -- For insolubles (all of which are equalities), do /not/ flatten the arguments -- In #14350 doing so led entire-unnecessary and ridiculously large @@ -1034,7 +1033,7 @@ can_eq_nc' _flat _rdr_env _envs ev eq_rel -- NB: we have expanded type synonyms already can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1 _ ty2 _ | Just (tc1, tys1) <- tcSplitTyConApp_maybe ty1 - , Just (tc2, tys2) <- tcSplitTyConApp_maybe ty2 -- + , Just (tc2, tys2) <- tcSplitTyConApp_maybe ty2 -- we want to catch e.g. Maybe Int ~ (Int -> Int) here for better -- error messages; hence no direct match on TyConApp , not (isTypeFamilyTyCon tc1) @@ -2506,8 +2505,17 @@ where noDerived G = G noDerived _ = W -For Wanted/Derived, the [X] constraint is "blocked" (not CEqCan, is CIrred) -until the k1~k2 constraint solved: Wrinkle (2). +For reasons described in Wrinkle (2) below, we want the [X] constraint to be "blocked"; +that is, it should be put aside, and not used to rewrite any other constraint, +until the kind-equality on which it depends (namely 'co' above) is solved. +To achieve this +* The [X] constraint is a CIrredCan +* With a cc_status of BlockedCIS bchs +* Where 'bchs' is the set of "blocking coercion holes". The blocking coercion + holes are the free coercion holes of [X]'s type +* When all the blocking coercion holes in the CIrredCan are filled (solved), + we convert [X] to a CNonCanonical and put it in the work list. +All this is described in more detail in Wrinkle (2). Wrinkles: @@ -2527,8 +2535,8 @@ Wrinkles: So, we have an invariant on CEqCan (TyEq:H) that the RHS does not have any coercion holes. This is checked in checkTypeEq. Any equalities that - have such an RHS are turned in CIrredCans with a BlockedCIS status. We also - must be sure to kick out any constraints that mention coercion holes + have such an RHS are turned into CIrredCans with a BlockedCIS status. We also + must be sure to kick out any such CIrredCan constraints that mention coercion holes when those holes get filled in, so that the unification step can now proceed. (2a) We must now absolutely make sure to kick out any constraints that ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -2058,13 +2058,19 @@ checkTypeEq dflags ty_fam_ok lhs ty -- no bother about impredicativity in coercions, as they're -- inferred go_co co | not (gopt Opt_DeferTypeErrors dflags) - , badCoercionHoleCo co = MTVU_HoleBlocker - -- Wrinkle (4b) in "GHC.Tc.Solver.Canonical" Note [Equalities with incompatible kinds] + , hasCoercionHoleCo co + = MTVU_HoleBlocker -- Wrinkle (2) in GHC.Tc.Solver.Canonical + -- See GHC.Tc.Solver.Canonical Note [Equalities with incompatible kinds] + -- Wrinkle (2) about this case in general, Wrinkle (4b) about the check for + -- deferred type errors. | TyVarLHS tv <- lhs - , tv `elemVarSet` tyCoVarsOfCo co = MTVU_Occurs + , tv `elemVarSet` tyCoVarsOfCo co + = MTVU_Occurs + -- Don't check coercions for type families; see commentary at top of function - | otherwise = ok + | otherwise + = ok good_tc :: TyCon -> Bool good_tc View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa4f10587c630b2afe51a026b81c44d2b064f719 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa4f10587c630b2afe51a026b81c44d2b064f719 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 Nov 12 21:42:52 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Thu, 12 Nov 2020 16:42:52 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Really remove (2b) Message-ID: <5fadac5c2138e_43133fa68f78aa5826025b@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 0dc45fd5 by Richard Eisenberg at 2020-11-12T16:42:41-05:00 Really remove (2b) - - - - - 2 changed files: - compiler/GHC/Core/Type.hs - compiler/GHC/Tc/Solver/Canonical.hs Changes: ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -1981,6 +1981,8 @@ buildSynTyCon name binders res_kind roles rhs is_fam_free = isFamFreeTy rhs is_forgetful = any (not . (`elemVarSet` tyCoVarsOfType rhs) . binderVar) binders || uniqSetAny isForgetfulSynTyCon (tyConsOfType rhs) + -- NB: This is allowed to be conservative, returning True more often + -- than it should. See comments on GHC.Core.TyCon.isForgetfulSynTyCon {- ************************************************************************ ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -50,7 +50,7 @@ import GHC.Utils.Misc import GHC.Data.Bag import GHC.Utils.Monad import Control.Monad -import Data.Maybe ( isJust ) +import Data.Maybe ( isJust, isNothing ) import Data.List ( zip4 ) import GHC.Types.Basic @@ -108,26 +108,6 @@ canonicalize (CQuantCan (QCI { qci_ev = ev, qci_pend_sc = pend_sc })) = canForAll ev pend_sc canonicalize (CIrredCan { cc_ev = ev, cc_status = status }) -{- "RAE" | BlockedCIS holes <- status - , isEmptyUniqSet holes - -- this would be a CEqCan if it weren't for the blocking hole, but that - -- block has been removed. Warp straight to canEqCanLHSHomo. - -- See Wrinkle (2b) of Note [Equalities with incompatible kinds] - = do { pred_ty <- zonkTcType (ctEvPred ev) -- zonk to remove the filled-in coercion - -- hole. Could flatten, but why bother? - ; case classifyPredType pred_ty of - EqPred eq_rel ty1 ty2 - | Just lhs <- canEqLHS_maybe ty1 - -> canEqCanLHSHomo ev eq_rel NotSwapped lhs ty1 ty2 ty2 - - -- the work item was indeed kicked out because the blocking coercion - -- hole got filled in. But perhaps an intervening work item unified - -- a variable in the LHS. We're not in the looping case of Wrinkle (2b), - -- so just go via the general path - _ -> canIrred status ev } - -- NB: The Irred is /not/ insoluble, so the special case below - -- for insolubles (the direct call to canEqNC) does not apply. --} | EqPred eq_rel ty1 ty2 <- classifyPredType (ctEvPred ev) = -- For insolubles (all of which are equalities), do /not/ flatten the arguments -- In #14350 doing so led entire-unnecessary and ridiculously large @@ -999,10 +979,10 @@ can_eq_nc' _flat rdr_env envs ev eq_rel ty1 ps_ty1 ty2 ps_ty2 -- Then, get rid of casts can_eq_nc' flat _rdr_env _envs ev eq_rel (CastTy ty1 co1) _ ty2 ps_ty2 - | not (isTyVarTy ty2) -- See (3) in Note [Equalities with incompatible kinds] + | isNothing (canEqLHS_maybe ty2) -- See (3) in Note [Equalities with incompatible kinds] = canEqCast flat ev eq_rel NotSwapped ty1 co1 ty2 ps_ty2 can_eq_nc' flat _rdr_env _envs ev eq_rel ty1 ps_ty1 (CastTy ty2 co2) _ - | not (isTyVarTy ty1) -- See (3) in Note [Equalities with incompatible kinds] + | isNothing (canEqLHS_maybe ty1) -- See (3) in Note [Equalities with incompatible kinds] = canEqCast flat ev eq_rel IsSwapped ty2 co2 ty1 ps_ty1 ---------------------- @@ -2565,25 +2545,6 @@ Wrinkles: Alternatively, we could be careful not to do unnecessary swaps during canonicalisation, but that seems hard to do, in general. - (2b) Consider this case: - [G] co_given :: k1 ~ k2 - [W] w :: (alpha :: k1) ~ (T a b c :: k2) - Processing the Wanted, we will eventually get to canEqCanLHSHetero, - which will produce - [W] co_abc :: k2 ~ k1 - leaving the Wanted to become - [W] w2 :: alpha ~ (T a b c |> co_abc) - When co_abc gets picked off the work list, it will get solved, - kicking out w2. But canonicalising w2 strips off the cast (toward the - top of can_eq_nc') and then the process repeats. - - Instead, when we're canonicalising something that was made into - an Irred only because of a blocking coercion (that is, with BlockedCIS), - we just jump straight to canEqCanLHSHomo. You might think we can go - straight to canEqCanLHSFinish, but there's a chance that a blocking - coercion hole interfered with the checkTyVarEq call in canEqTyVarFunEq, - so we have to start above that call. - (3) Suppose we have [W] (a :: k1) ~ (rhs :: k2). We duly follow the algorithm detailed here, producing [W] co :: k2 ~ k1, and adding [W] (a :: k1) ~ ((rhs |> co) :: k1) to the irreducibles. Some time @@ -2594,7 +2555,9 @@ Wrinkles: is heterogeneous again, and the process repeats. To avoid this, we don't strip casts off a type if the other type - in the equality is a tyvar. And this is an improvement regardless: + in the equality is a CanEqLHS (the scenario above can happen with a + type family, too. testcase: typecheck/should_compile/T13822). + And this is an improvement regardless: because tyvars can, generally, unify with casted types, there's no reason to go through the work of stripping off the cast when the cast appears opposite a tyvar. This is implemented in the cast case View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0dc45fd5c0cedb3b473d59e7916aeb7ad042ea7e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0dc45fd5c0cedb3b473d59e7916aeb7ad042ea7e 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 Nov 12 21:55:35 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 16:55:35 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/dwarf-info-offset Message-ID: <5fadaf5794030_431310b1eda02630df@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/dwarf-info-offset at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/dwarf-info-offset 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 Nov 12 21:59:45 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 16:59:45 -0500 Subject: [Git][ghc/ghc][wip/dwarf-info-offset] 10 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags Message-ID: <5fadb051a5160_43133fa68f69ce34263465@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/dwarf-info-offset at Glasgow Haskell Compiler / GHC Commits: fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 160ce150 by Ben Gamari at 2020-11-12T16:59:37-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Types/Var.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - includes/rts/Linker.h - includes/rts/storage/GC.h - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0e46fa9ea25804ea3d2eef79b38e963e96456ba2...160ce15024054ac20f52b3ecaea20d86bb5b8b54 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0e46fa9ea25804ea3d2eef79b38e963e96456ba2...160ce15024054ac20f52b3ecaea20d86bb5b8b54 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 Nov 12 22:14:01 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Thu, 12 Nov 2020 17:14:01 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] More reactions to reviews Message-ID: <5fadb3a9c5856_43133fa69883dc6c2659ef@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 0b4d386c by Richard Eisenberg at 2020-11-12T17:13:46-05:00 More reactions to reviews - - - - - 7 changed files: - compiler/GHC/Core/Type.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -1344,6 +1344,9 @@ splitTyConApp_maybe = repSplitTyConApp_maybe . coreFullView -- of @a@ isn't of the form @TYPE rep@). Consequently, you may need to zonk your -- type before using this function. -- +-- This does *not* split types headed with (=>), as that's not a TyCon in the +-- type-checker. +-- -- If you only need the 'TyCon', consider using 'tcTyConAppTyCon_maybe'. tcSplitTyConApp_maybe :: HasCallStack => Type -> Maybe (TyCon, [Type]) -- Defined here to avoid module loops between Unify and TcType. ===================================== compiler/GHC/HsToCore/Monad.hs ===================================== @@ -300,7 +300,11 @@ initTcDsForSolver thing_inside ; let DsGblEnv { ds_mod = mod , ds_fam_inst_env = fam_inst_env , ds_gbl_rdr_env = rdr_env } = gbl - -- this is *the* use of ds_gbl_rdr_env + -- This is *the* use of ds_gbl_rdr_env: + -- Make sure the solver (used by the pattern-match overlap checker) has + -- access to the GlobalRdrEnv and FamInstEnv for the module, so that it + -- knows how to reduce type families, and which newtypes it can unwrap. + DsLclEnv { dsl_loc = loc } = lcl ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -2050,9 +2050,7 @@ simplifyHoles = mapBagM simpl_hole where simpl_hole :: Hole -> TcS Hole - -- do not simplify an extra-constraints wildcard. These holes - -- are filled with already-simplified constraints in - -- chooseInferredQuantifiers (choose_psig_context) + -- See Note [Do not simplify ConstraintHoles] simpl_hole h@(Hole { hole_sort = ConstraintHole }) = return h -- other wildcards should be simplified for printing @@ -2102,6 +2100,41 @@ test T12227. But we don't get to discard all redundant equality superclasses, alas; see #15205. +Note [Do not simplify ConstraintHoles] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Before printing the inferred value for a type hole (a _ wildcard in +a partial type signature), we simplify it w.r.t. any Givens. This +makes for an easier-to-understand diagnostic for the user. + +However, we do not wish to do this for extra-constraint holes. Here is +the example for why (partial-sigs/should_compile/T12844): + + bar :: _ => FooData rngs + bar = foo + + data FooData rngs + + class Foo xs where foo :: (Head xs ~ '(r,r')) => FooData xs + + type family Head (xs :: [k]) where Head (x ': xs) = x + +GHC correctly infers that the extra-constraints wildcard on `bar` +should be (Head rngs ~ '(r, r'), Foo rngs). It then adds this constraint +as a Given on the implication constraint for `bar`. The Hole for +the _ is stored within the implication's WantedConstraints. +When simplifyHoles is called, that constraint is already assumed as +a Given. Simplifying with respect to it turns it into +('(r, r') ~ '(r, r'), Foo rngs), which is disastrous. + +Furthermore, there is no need to simplify here: extra-constraints wildcards +are filled in with the output of the solver, in chooseInferredQuantifiers +(choose_psig_context), so they are already simplified. (Contrast to normal +type holes, which are just bound to a meta-variable.) Avoiding the poor output +is simple: just don't simplify extra-constraints wildcards. + +This is the only reason we need to track ConstraintHole separately +from TypeHole in HoleSort. + Note [Tracking redundant constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ With Opt_WarnRedundantConstraints, GHC can report which ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -2312,8 +2312,6 @@ canEqCanLHSFinish ev eq_rel swapped lhs rhs -- guaranteed that tyVarKind lhs == typeKind rhs, for (TyEq:K) -- (TyEq:N) is checked in can_eq_nc', and (TyEq:TV) is handled in canEqTyVarHomo - -- this next line checks also for coercion holes; see - -- Note [Equalities with incompatible kinds] = do { dflags <- getDynFlags ; new_ev <- rewriteEqEvidence ev swapped lhs_ty rhs rewrite_co1 rewrite_co2 @@ -2321,6 +2319,8 @@ canEqCanLHSFinish ev eq_rel swapped lhs rhs -- equalities, in case have x ~ (y :: ..x...) -- #12593 -- guarantees (TyEq:OC), (TyEq:F), and (TyEq:H) + -- this next line checks also for coercion holes (TyEq:H); see + -- Note [Equalities with incompatible kinds] ; case canEqOK dflags eq_rel lhs rhs of CanEqOK -> do { traceTcS "canEqOK" (ppr lhs $$ ppr rhs) @@ -2692,6 +2692,10 @@ Note that * We track the cycle-breaker variables in inert_cycle_breakers in InertSet * We eventually fill in the cycle-breakers, with `cbv := F a`. No one else fills in cycle-breakers! +* In inert_cycle_breakers, we remember the (cbv, F a) pair; that is, we + remember the /original/ type. The [G] F a ~ cbv constraint may be rewritten + by other givens (eg if we have another [G] a ~ (b,c), but at the end we + still fill in with cbv := F a * This fill-in is done when solving is complete, by restoreTyVarCycles in nestImplicTcS and runTcSWithEvBinds. * The evidence for the new `F a ~ cbv` constraint is Refl, because we know this fill-in is @@ -2738,6 +2742,8 @@ Details: (2) Our goal here is to avoid loops in rewriting. We can thus skip looking in coercions, as we don't rewrite in coercions. + (There is no worry about unifying a meta-variable here: this Note is + only about Givens.) (3) As we're substituting, we can build ill-kinded types. For example, if we have Proxy (F a) b, where (b :: F a), then @@ -2820,6 +2826,10 @@ Details: we only want to break cycles for user-written loopy Givens, and a CycleBreakerTv certainly isn't user-written. +NB: This same situation (an equality like b ~ Maybe (F b)) can arise with +Wanteds, but we have no concrete case incentivising special treatment. It +would just be a CIrredCan. + -} {- ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -273,7 +273,8 @@ data HoleSort = ExprHole Id | ConstraintHole -- ^ A hole in a constraint, like @f :: (_, Eq a) => ... -- Differentiated from TypeHole because a ConstraintHole - -- is simplified differently. See GHC.Tc.Solver.simplifyHoles. + -- is simplified differently. See + -- Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. instance Outputable Hole where ppr (Hole { hole_sort = ExprHole id ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -857,6 +857,10 @@ any_rewritable :: Bool -- Ignore casts and coercions -- ORing the results of the predicates above together -- Do not look inside casts and coercions if 'ignore_cos' is True -- See Note [anyRewritableTyVar must be role-aware] +-- +-- This looks like it should use foldTyCo, but that function is +-- role-agnostic, and this one must be role-aware. We could make +-- foldTyCon role-aware, but that may slow down more common usages. {-# INLINE any_rewritable #-} -- this allows specialization of predicates any_rewritable ignore_cos role tv_pred tc_pred should_expand = go role emptyVarSet ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -1989,6 +1989,11 @@ checkTypeEq :: DynFlags -> AreTypeFamiliesOK -> CanEqLHS -> TcType -- inside the kinds of variables it mentions. For (d) we look deeply -- in coercions when the LHS is a tyvar (but skip coercions for type family -- LHSs), and for (e) see Note [CEqCan occurs check] in GHC.Tc.Types.Constraint. +-- +-- checkTypeEq is called from +-- * checkTyFamEq, checkTyVarEq (which inline it to specialise away the +-- case-analysis on 'lhs' +-- * checkEqCanLHSFinish, which does not know the form of 'lhs' checkTypeEq dflags ty_fam_ok lhs ty = go ty where @@ -2047,14 +2052,15 @@ checkTypeEq dflags ty_fam_ok lhs ty -- this slightly peculiar way of defining this means -- we don't have to evaluate this `case` at every tyconapp go_tc = case lhs of - TyVarLHS {} -> \ tc tys -> if good_tc tc - then mapM go tys >> ok - else MTVU_Bad + TyVarLHS {} -> \ tc tys -> + if | good_tc tc -> mapM go tys >> ok + | otherwise -> MTVU_Bad TyFamLHS fam_tc fam_args -> \ tc tys -> if | tcEqTyConApps fam_tc fam_args tc tys -> MTVU_Occurs | good_tc tc -> mapM go tys >> ok | otherwise -> MTVU_Bad + -- no bother about impredicativity in coercions, as they're -- inferred go_co co | not (gopt Opt_DeferTypeErrors dflags) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b4d386cc779db18e9fdb266cf76bff341fb126a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0b4d386cc779db18e9fdb266cf76bff341fb126a 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 Nov 12 22:57:05 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 17:57:05 -0500 Subject: [Git][ghc/ghc][wip/dwarf-info-offset] dwarf: Apply info table offset consistently Message-ID: <5fadbdc132d39_43133fa6bc06ae3027717f@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/dwarf-info-offset at Glasgow Haskell Compiler / GHC Commits: bd3d97ca by Ben Gamari at 2020-11-12T17:56:38-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Dwarf/Types.hs Changes: ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -178,7 +178,8 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL $$ pprString producer $$ pprData4 dW_LANG_Haskell $$ pprString compDir - $$ pprWord platform (pdoc platform lowLabel) + -- Offset due to Note [Info Offset] + $$ pprWord platform (pdoc platform lowLabel <> text "-1") $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc then sectionOffset platform (ptext lineLbl) (ptext dwarfLineLabel) @@ -189,7 +190,8 @@ pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = $$ pprString name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) - $$ pprWord platform (pdoc platform label) + -- Offset due to Note [Info Offset] + $$ pprWord platform (pdoc platform label <> text "-1") $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel label) $$ pprByte 1 $$ pprByte dW_OP_call_frame_cfa @@ -256,7 +258,10 @@ pprDwarfARanges platform arngs unitU = $$ pprWord platform (char '0') pprDwarfARange :: Platform -> DwarfARange -> SDoc -pprDwarfARange platform arng = pprWord platform (pdoc platform $ dwArngStartLabel arng) $$ pprWord platform length +pprDwarfARange platform arng = + -- Offset due to Note [Info offset]. + pprWord platform (pdoc platform (dwArngStartLabel arng) <> text "-1") + $$ pprWord platform length where length = pdoc platform (dwArngEndLabel arng) <> char '-' <> pdoc platform (dwArngStartLabel arng) @@ -356,7 +361,7 @@ pprFrameProc platform frameLbl initUw (DwarfFrameProc procLbl hasInfo blocks) fdeEndLabel = mkAsmTempDerivedLabel procLbl (fsLit "_fde_end") procEnd = mkAsmTempEndLabel procLbl ifInfo str = if hasInfo then text str else empty - -- see [Note: Info Offset] + -- see Note [Info Offset] in vcat [ whenPprDebug $ text "# Unwinding for" <+> pdoc platform procLbl <> colon , pprData4' (pdoc platform fdeEndLabel <> char '-' <> pdoc platform fdeLabel) , pdoc platform fdeLabel <> colon @@ -398,7 +403,7 @@ pprFrameBlock platform (DwarfFrameBlock hasInfo uws0) = in if oldUws == uws then (empty, oldUws) - else let -- see [Note: Info Offset] + else let -- see Note [Info Offset] needsOffset = firstDecl && hasInfo lblDoc = pdoc platform lbl <> if needsOffset then text "-1" else empty @@ -407,6 +412,7 @@ pprFrameBlock platform (DwarfFrameBlock hasInfo uws0) = in (doc, uws) -- Note [Info Offset] +-- ~~~~~~~~~~~~~~~~~~ -- -- GDB was pretty much written with C-like programs in mind, and as a -- result they assume that once you have a return address, it is a @@ -426,6 +432,14 @@ pprFrameBlock platform (DwarfFrameBlock hasInfo uws0) = -- correct function name for the frame, as that uses the symbol table, -- which we can not manipulate as easily. -- +-- We apply this offset in several places: +-- +-- * unwind information in .debug_frames +-- * the subprogram and lexical_block DIEs in .debug_info +-- * the ranges in .debug_aranges +-- +-- In the latter two cases we apply the offset unconditionally. +-- -- There's a GDB patch to address this at [1]. At the moment of writing -- it's not merged, so I recommend building GDB with the patch if you -- care about unwinding. The hack above doesn't cover every case. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd3d97ca81081a8a76e0f101e477a4175978b20f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd3d97ca81081a8a76e0f101e477a4175978b20f 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 Nov 12 23:23:19 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 18:23:19 -0500 Subject: [Git][ghc/ghc][wip/bump-time] 15 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fadc3e74776c_4313d3e9aec278882@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 5b6cb317 by Ben Gamari at 2020-11-12T18:22:39-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Types/Var.hs - compiler/ghc.cabal.in - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - ghc/ghc-bin.cabal.in - includes/rts/Linker.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/rts/storage/Heap.h - includes/rts/storage/TSO.h - libraries/Cabal - libraries/base/GHC/Exts.hs - libraries/directory - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/hpc - libraries/time - libraries/unix - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8271dde51d7f5311bd8a09a8f9292db86b908f65...5b6cb3173797295e33f3084f77d71c244407571e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8271dde51d7f5311bd8a09a8f9292db86b908f65...5b6cb3173797295e33f3084f77d71c244407571e 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 Fri Nov 13 01:09:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 20:09:30 -0500 Subject: [Git][ghc/ghc][wip/T18566] Introduce -fprof-callers flag Message-ID: <5faddcca36476_43133fa6ae8db4c42857e4@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 8bb6eacc by Ben Gamari at 2020-11-13T01:07:26+00:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 18 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,223 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = withUserStyle alwaysQualify DefaultDepth $ + hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling:" <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = pattern + where + pattern = star <|> wildcard <|> char <|> end + star = PChar '*' <$ P.string "\\*" <*> pattern + wildcard = do + void $ P.char '*' + PWildcard <$> pattern + char = PChar <$> P.anyChar <*> pattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -16,6 +16,7 @@ import GHC.Driver.Session import GHC.Driver.Ppr import GHC.Driver.Plugins ( withPlugins, installCoreToDos ) import GHC.Driver.Env +import GHC.Platform.Ways ( hasWay, Way(WayProf) ) import GHC.Core import GHC.Core.Opt.CSE ( cseProgram ) @@ -44,6 +45,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -156,6 +158,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = ways dflags `hasWay` WayProf maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -222,12 +225,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -371,7 +378,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. @@ -510,6 +519,9 @@ doCorePass CoreDoSpecialising = {-# SCC "Specialise" #-} doCorePass CoreDoSpecConstr = {-# SCC "SpecConstr" #-} specConstrProgram +doCorePass CoreAddCallerCcs = {-# SCC "AddCallerCcs" #-} + addCallerCostCentres + doCorePass CoreDoPrintCore = observe printCore doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat doCorePass CoreDoNothing = return ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -699,6 +700,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1313,6 +1315,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2947,6 +2950,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -4548,6 +4555,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-fprof-callers=⟨name⟩`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ @@ -47,7 +51,7 @@ Compiler Code using ``Void#`` now has to enable :extension:`UnboxedTuples`. ``ghc`` library -~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~ - The ``con_args`` field of ``ConDeclGADT`` has been renamed to ``con_g_args``. This is because the type of ``con_g_args`` is now different from the type of ===================================== docs/users_guide/profiling.rst ===================================== @@ -358,6 +358,38 @@ Automatically placing cost-centres GHC has a number of flags for automatically inserting cost-centres into the compiled program. +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + Note that these cost-centres are added late in compilation (after + simplification) and consequently the names may be slightly different than + they appear in the source program (e.g. a call to ``f`` may inlined with + its wrapper, resulting in an occurrence of its worker, ``$wf``). + + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: none + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample ===================================== @@ -0,0 +1,79 @@ + Fri Nov 13 01:06 2020 Time and Allocation Profiling Report (Final) + + CallerCc1 +RTS -hc -p -RTS 7 + + total time = 0.09 secs (87 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 35.6 49.5 +insert Main Main.hs:(108,1)-(112,8) 21.8 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 17.2 37.5 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 6.9 2.6 +conjunct Main Main.hs:(70,1)-(71,18) 5.7 0.0 +split.split' Main Main.hs:(165,11)-(166,28) 3.4 2.3 +disin.dp Main Main.hs:80:3-14 3.4 0.0 +unicl Main Main.hs:(176,1)-(180,36) 2.3 1.1 +tautclause Main Main.hs:173:1-49 2.3 3.7 +disin.dq Main Main.hs:81:3-14 1.1 0.0 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling:Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling:Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 35.6 49.5 46.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 5.7 0.0 5.7 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 3.4 0.0 3.4 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 1.1 0.0 1.1 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.4 2.3 3.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 2.3 1.1 50.6 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 6.9 2.6 48.3 46.9 + tautclause Main Main.hs:173:1-49 295 37422 2.3 3.7 2.3 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 39.1 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 39.1 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 17.2 37.5 39.1 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 21.8 1.7 21.8 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample ===================================== @@ -0,0 +1,78 @@ + Fri Nov 13 01:06 2020 Time and Allocation Profiling Report (Final) + + CallerCc2 +RTS -hc -p -RTS 7 + + total time = 0.09 secs (91 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 26.4 49.5 +clause.clause' Main Main.hs:(63,12)-(65,57) 23.1 37.5 +insert Main Main.hs:(108,1)-(112,8) 18.7 1.7 +conjunct Main Main.hs:(70,1)-(71,18) 8.8 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 5.5 2.6 +tautclause Main Main.hs:173:1-49 5.5 3.7 +unicl Main Main.hs:(176,1)-(180,36) 3.3 1.1 +split.split' Main Main.hs:(165,11)-(166,28) 3.3 2.3 +disin.dp Main Main.hs:80:3-14 3.3 0.0 +clause Main Main.hs:(61,1)-(65,57) 2.2 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling:Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling:Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 26.4 49.5 38.5 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 8.8 0.0 8.8 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 3.3 0.0 3.3 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 0.0 0.0 0.0 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.3 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.3 2.3 3.3 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 3.3 1.1 58.2 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 5.5 2.6 54.9 46.9 + tautclause Main Main.hs:173:1-49 295 37422 5.5 3.7 5.5 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 44.0 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 2.2 1.4 44.0 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 23.1 37.5 41.8 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 18.7 1.7 18.7 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample ===================================== @@ -0,0 +1,78 @@ + Fri Nov 13 01:06 2020 Time and Allocation Profiling Report (Final) + + CallerCc3 +RTS -hc -p -RTS 7 + + total time = 0.09 secs (85 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 29.4 49.5 +insert Main Main.hs:(108,1)-(112,8) 24.7 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 23.5 37.5 +conjunct Main Main.hs:(70,1)-(71,18) 10.6 0.0 +tautclause Main Main.hs:173:1-49 4.7 3.7 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 3.5 2.6 +split.split' Main Main.hs:(165,11)-(166,28) 2.4 2.3 +disin.dp Main Main.hs:80:3-14 1.2 0.0 +unicl Main Main.hs:(176,1)-(180,36) 0.0 1.1 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling:Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling:Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 29.4 49.5 41.2 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 10.6 0.0 10.6 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 1.2 0.0 1.2 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 0.0 0.0 0.0 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 2.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 2.4 2.3 2.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 0.0 1.1 56.5 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 3.5 2.6 56.5 46.9 + tautclause Main Main.hs:173:1-49 295 37422 4.7 3.7 4.7 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 48.2 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 48.2 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 23.5 37.5 48.2 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 24.7 1.7 24.7 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,19 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) +setTestOpts(extra_files(['Main.hs'])) +setTestOpts(extra_run_opts('7')) + +# N.B. Main.hs is stolen from heapprof001. + +test('CallerCc1', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=*.concat -O0']) + +test('CallerCc2', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.concat -O0']) + +test('CallerCc3', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.con*at -O0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8bb6eacc77324238401ed96bc47f273f1b61750f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8bb6eacc77324238401ed96bc47f273f1b61750f 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 Fri Nov 13 02:28:31 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 12 Nov 2020 21:28:31 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: testsuite: Add testcase for #18733 Message-ID: <5fadef4f2b495_43133fa68e1fbe3030288@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 80fcb3bc by Sebastian Graf at 2020-11-12T21:28:21-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - faa7a5ac by Sebastian Graf at 2020-11-12T21:28:21-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - fee472c1 by Sylvain Henry at 2020-11-12T21:28:23-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - baf7ded8 by Sylvain Henry at 2020-11-12T21:28:23-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - 6881bb60 by Ben Gamari at 2020-11-12T21:28:23-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - docs/users_guide/extending_ghc.rst - ghc/GHCi/UI.hs - ghc/Main.hs - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T - + testsuite/tests/driver/T18733/Library1.hs - + testsuite/tests/driver/T18733/Library2.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5fc856b8ffcc3641bebc9094c58a630e9eb0d185...6881bb6080b0bf83d0a6f48ab75b1dad549da8cd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5fc856b8ffcc3641bebc9094c58a630e9eb0d185...6881bb6080b0bf83d0a6f48ab75b1dad549da8cd 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 Fri Nov 13 02:31:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 12 Nov 2020 21:31:09 -0500 Subject: [Git][ghc/ghc][wip/T17605] 18 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fadefed607da_43133fa69935b388304988@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T17605 at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - d6454f67 by Ben Gamari at 2020-11-12T21:05:40-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - affa40c3 by Ben Gamari at 2020-11-12T21:05:40-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - 0a32843f by Ben Gamari at 2020-11-12T21:05:40-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - 8937c9b6 by Ben Gamari at 2020-11-12T21:05:40-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Types/Var.hs - docs/users_guide/debug-info.rst - docs/users_guide/phases.rst - includes/rts/Linker.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/rts/storage/Heap.h - includes/rts/storage/TSO.h - libraries/base/GHC/Exts.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Heap.c - rts/Linker.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ab4eceff307ccc5470244c3ad88d4996d79f843...8937c9b63406cd7a24f301a5158d411a3bc6e96a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ab4eceff307ccc5470244c3ad88d4996d79f843...8937c9b63406cd7a24f301a5158d411a3bc6e96a 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 Fri Nov 13 02:37:53 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 21:37:53 -0500 Subject: [Git][ghc/ghc][wip/T18857] fixup ShortText Message-ID: <5fadf1812fe65_4313f0a0a283055e8@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 71fdb441 by Moritz Angermann at 2020-11-13T02:37:34+00:00 fixup ShortText - - - - - 1 changed file: - libraries/ghc-boot/GHC/Data/ShortText.hs Changes: ===================================== libraries/ghc-boot/GHC/Data/ShortText.hs ===================================== @@ -1,6 +1,22 @@ -{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-} +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} - +-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore. +-- LLVM based GHC's fail to compile memcmp ffi calls. These end up as memcmp$def in the llvm ir, however we +-- don't have any prototypes and subsequently the llvm toolchain chokes on them. Since 7fdcce6d, we use +-- ShortText for the package database. This however introduces this very module; which through inlining ends +-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in +-- the memcmp call we choke on. +-- +-- The solution thusly is to force late binding via the linker instead of inlining when comping with the +-- bootstrap compiler. This will produce a slower (slightly less optimised) stage1 compiler only. +-- +-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion. +-- +-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler, +-- we can drop this code as well. +#if GHC_STAGE < 1 +{-# OPTIONS_GHC -fignore-interface-pragmas #-} +#endif -- | -- An Unicode string for internal GHC use. Meant to replace String -- in places where being a lazy linked is not very useful and a more View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71fdb441d0af4767cb9fc797c3460ce1365e317f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71fdb441d0af4767cb9fc797c3460ce1365e317f 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 Fri Nov 13 02:39:45 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 21:39:45 -0500 Subject: [Git][ghc/ghc][wip/T18857] 132 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fadf1f1b26e0_4313f0a0a28307816@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 38aedc7a by Ben Gamari at 2020-11-12T21:39:41-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' Fixes #18857. - - - - - e6f1d610 by Ben Gamari at 2020-11-12T21:39:41-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - fe45f2c7 by Ben Gamari at 2020-11-12T21:39:41-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 40e89e37 by Ben Gamari at 2020-11-12T21:39:41-05:00 hadrian: Don't use -fllvm to bootstrap under LLVM flavour Previously Hadrian's LLVM build flavours would use `-fllvm` for all invocations, even those to stage0 GHC. This meant that we needed to keep two LLVM versions around in all of the CI images. Moreover, it differed from the behavior of the old make build system's llvm flavours. Change this to reflect the behavior of the `make` build system, using `-fllvm` only with the stage1 and stage2 compilers. - - - - - 3c7f5854 by Moritz Angermann at 2020-11-12T21:39:41-05:00 fixup ShortText - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Exitify.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/71fdb441d0af4767cb9fc797c3460ce1365e317f...3c7f5854d0c5c84de0cf735b511402539a243e72 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/71fdb441d0af4767cb9fc797c3460ce1365e317f...3c7f5854d0c5c84de0cf735b511402539a243e72 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 Fri Nov 13 03:12:49 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 22:12:49 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/angerman/aarch64-arm64-prep Message-ID: <5fadf9b1e205b_43133fa67e44d4783094e@gitlab.haskell.org.mail> Moritz Angermann pushed new branch wip/angerman/aarch64-arm64-prep at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/angerman/aarch64-arm64-prep 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 Fri Nov 13 03:27:51 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 12 Nov 2020 22:27:51 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-arm64-prep] eh? Message-ID: <5fadfd37587eb_4313f36b5c831121c@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-arm64-prep at Glasgow Haskell Compiler / GHC Commits: 90fce8a5 by Moritz Angermann at 2020-11-13T03:27:38+00:00 eh? - - - - - 1 changed file: - compiler/GHC/CmmToAsm.hs Changes: ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -109,7 +109,7 @@ import GHC.CmmToAsm.Monad import GHC.CmmToAsm.CFG import GHC.CmmToAsm.Dwarf import GHC.CmmToAsm.Config -import GHC.ArchmToAsm.Types +import GHC.CmmToAsm.Types import GHC.Cmm.DebugBlock import GHC.Cmm.BlockId View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90fce8a5b0a0bb593b12c5d9bec0234391e157cb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90fce8a5b0a0bb593b12c5d9bec0234391e157cb 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 Fri Nov 13 07:58:46 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 13 Nov 2020 02:58:46 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5fae3cb66c491_43133fa699471dd033103e@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: a506e942 by Sebastian Graf at 2020-11-13T02:58:37-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 31f9cf0c by Sebastian Graf at 2020-11-13T02:58:37-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - 439a4218 by Sylvain Henry at 2020-11-13T02:58:39-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - acde8d07 by Sylvain Henry at 2020-11-13T02:58:39-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - 55f1b984 by Ben Gamari at 2020-11-13T02:58:39-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - docs/users_guide/extending_ghc.rst - ghc/GHCi/UI.hs - ghc/Main.hs - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T - testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs - testsuite/tests/plugins/static-plugins.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6881bb6080b0bf83d0a6f48ab75b1dad549da8cd...55f1b984703094ba9409effb96d9d7b0358010f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6881bb6080b0bf83d0a6f48ab75b1dad549da8cd...55f1b984703094ba9409effb96d9d7b0358010f8 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 Fri Nov 13 11:47:00 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Fri, 13 Nov 2020 06:47:00 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] the char kind: type families, functionality, and submodule updates Message-ID: <5fae723440051_43133fa6bc6a38c435476b@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 5dfd431a by Daniel Rogozin at 2020-11-13T14:46:16+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs - compiler/GHC/Utils/Binary/Typeable.hs - libraries/base/Data/Typeable/Internal.hs - libraries/base/GHC/TypeLits.hs - libraries/binary - libraries/ghc-prim/GHC/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dfd431ae079977e4bc065252ea46354ec677eed -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5dfd431ae079977e4bc065252ea46354ec677eed 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 Fri Nov 13 12:11:36 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Fri, 13 Nov 2020 07:11:36 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-arm64-prep] Update ArchOS.hs Message-ID: <5fae77f8b6096_43133fa6a91e8388366415@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-arm64-prep at Glasgow Haskell Compiler / GHC Commits: 4d3beb17 by Moritz Angermann at 2020-11-13T07:11:35-05:00 Update ArchOS.hs - - - - - 1 changed file: - libraries/ghc-boot/GHC/Platform/ArchOS.hs Changes: ===================================== libraries/ghc-boot/GHC/Platform/ArchOS.hs ===================================== @@ -130,7 +130,7 @@ stringEncodeArch = \case ArchARM ARMv5 _ _ -> "armv5" ArchARM ARMv6 _ _ -> "armv6" ArchARM ARMv7 _ _ -> "armv7" - ArchAArch64 -> "aarch64" + ArchAArch64 -> "aarch64" ArchAlpha -> "alpha" ArchMipseb -> "mipseb" ArchMipsel -> "mipsel" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d3beb17f1ec9cfd5a0fdfe24b09b362a74b4c7d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d3beb17f1ec9cfd5a0fdfe24b09b362a74b4c7d 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 Fri Nov 13 12:12:25 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Fri, 13 Nov 2020 07:12:25 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-arm64-prep] Update Regs.hs Message-ID: <5fae782996474_43137349368367059@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-arm64-prep at Glasgow Haskell Compiler / GHC Commits: e0eb4607 by Moritz Angermann at 2020-11-13T07:12:23-05:00 Update Regs.hs - - - - - 1 changed file: - compiler/GHC/Platform/Regs.hs Changes: ===================================== compiler/GHC/Platform/Regs.hs ===================================== @@ -1,4 +1,3 @@ - module GHC.Platform.Regs (callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg) where @@ -10,7 +9,7 @@ import GHC.Platform import GHC.Platform.Reg import qualified GHC.Platform.ARM as ARM -import qualified GHC.Platform.AArch64 as AArch64 +import qualified GHC.Platform.AArch64 as AArch64 import qualified GHC.Platform.PPC as PPC import qualified GHC.Platform.S390X as S390X import qualified GHC.Platform.SPARC as SPARC View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0eb460712cdf01a5b8b511ce800db814b0727cb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0eb460712cdf01a5b8b511ce800db814b0727cb 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 Fri Nov 13 12:25:59 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Fri, 13 Nov 2020 07:25:59 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-arm64-prep] AArch64/arm64 adjustments Message-ID: <5fae7b57a6dba_43133fa6a88928103720c9@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-arm64-prep at Glasgow Haskell Compiler / GHC Commits: 50a2aa07 by Moritz Angermann at 2020-11-13T12:24:03+00:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Dynamic.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Platform.hs - compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs - compiler/GHC/Platform/Regs.hs - compiler/ghc.cabal.in - config.sub - includes/CodeGen.Platform.hs - includes/rts/Flags.h - includes/rts/storage/GC.h - libraries/ghc-boot/GHC/Platform/ArchOS.hs - libraries/ghci/GHCi/InfoTable.hsc - llvm-targets - rts/Adjustor.c - rts/StgCRun.c - rts/linker/elf_plt_aarch64.c - rts/linker/elf_reloc.c - rts/package.conf.in - rts/rts.cabal.in - rts/sm/Storage.c - utils/llvm-targets/gen-data-layout.sh Changes: ===================================== .gitlab-ci.yml ===================================== @@ -524,6 +524,14 @@ validate-x86_64-darwin: tags: - aarch64-linux +.build-aarch64-linux-deb10-llvm: + extends: .build-aarch64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm + tags: + - aarch64-linux + validate-aarch64-linux-deb10: extends: .build-aarch64-linux-deb10 artifacts: ===================================== aclocal.m4 ===================================== @@ -118,7 +118,7 @@ AC_DEFUN([FPTOOLS_SET_PLATFORM_VARS], GHC_CONVERT_OS([$target_os], [$TargetArch], [TargetOS]) fi - GHC_LLVM_TARGET([$target_cpu],[$target_vendor],[$target_os],[LlvmTarget]) + GHC_LLVM_TARGET([$target],[$target_cpu],[$target_vendor],[$target_os],[LlvmTarget]) GHC_SELECT_FILE_EXTENSIONS([$host], [exeext_host], [soext_host]) GHC_SELECT_FILE_EXTENSIONS([$target], [exeext_target], [soext_target]) @@ -218,7 +218,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], test -z "[$]2" || eval "[$]2=\"ArchARM \$ARM_ISA \$ARM_ISA_EXT \$ARM_ABI\"" ;; aarch64) - test -z "[$]2" || eval "[$]2=ArchARM64" + test -z "[$]2" || eval "[$]2=ArchAArch64" ;; alpha) test -z "[$]2" || eval "[$]2=ArchAlpha" @@ -327,9 +327,14 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], AC_LINK_IFELSE( [AC_LANG_PROGRAM([], [__asm__ (".subsections_via_symbols");])], [AC_MSG_RESULT(yes) - TargetHasSubsectionsViaSymbols=YES - AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1], + if test x"$TargetArch" = xaarch64; then + dnl subsections via symbols is busted on arm64 + TargetHasSubsectionsViaSymbols=NO + else + TargetHasSubsectionsViaSymbols=YES + AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1], [Define to 1 if Apple-style dead-stripping is supported.]) + fi ], [TargetHasSubsectionsViaSymbols=NO AC_MSG_RESULT(no)]) @@ -1976,7 +1981,7 @@ AC_MSG_CHECKING(for path to top of build tree) # `libraries/base/System/Info.hs`'s documentation. AC_DEFUN([GHC_CONVERT_CPU],[ case "$1" in - aarch64*) + aarch64*|arm64*) $2="aarch64" ;; alpha*) @@ -2058,18 +2063,19 @@ case "$1" in esac ]) -# GHC_LLVM_TARGET(target_cpu, target_vendor, target_os, llvm_target_var) +# GHC_LLVM_TARGET(target, target_cpu, target_vendor, target_os, llvm_target_var) # -------------------------------- # converts the canonicalized target into something llvm can understand AC_DEFUN([GHC_LLVM_TARGET], [ - case "$2-$3" in + llvm_target_cpu=$2 + case "$1" in *-freebsd*-gnueabihf) llvm_target_vendor="unknown" llvm_target_os="freebsd-gnueabihf" ;; - hardfloat-*eabi) + *-hardfloat-*eabi) llvm_target_vendor="unknown" - llvm_target_os="$3""hf" + llvm_target_os="$4""hf" ;; *-mingw32|*-mingw64|*-msys) llvm_target_vendor="unknown" @@ -2080,15 +2086,25 @@ AC_DEFUN([GHC_LLVM_TARGET], [ # turned into just `-linux` and fail to be found # in the `llvm-targets` file. *-android*|*-gnueabi*|*-musleabi*) - GHC_CONVERT_VENDOR([$2],[llvm_target_vendor]) - llvm_target_os="$3" + GHC_CONVERT_VENDOR([$3],[llvm_target_vendor]) + llvm_target_os="$4" + ;; + # apple is a bit about their naming scheme for + # aarch64; and clang on macOS doesn't know that + # aarch64 would be arm64. So for LLVM we'll need + # to call it arm64; while we'll refer to it internally + # as aarch64 for consistency and sanity. + aarch64-apple-*|arm64-apple-*) + llvm_target_cpu="arm64" + GHC_CONVERT_VENDOR([$3],[llvm_target_vendor]) + GHC_CONVERT_OS([$4],[$2],[llvm_target_os]) ;; *) - GHC_CONVERT_VENDOR([$2],[llvm_target_vendor]) - GHC_CONVERT_OS([$3],[$1],[llvm_target_os]) + GHC_CONVERT_VENDOR([$3],[llvm_target_vendor]) + GHC_CONVERT_OS([$4],[$2],[llvm_target_os]) ;; esac - $4="$1-$llvm_target_vendor-$llvm_target_os" + $5="$llvm_target_cpu-$llvm_target_vendor-$llvm_target_os" ]) ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -166,7 +166,7 @@ nativeCodeGen dflags this_mod modLoc h us cmms ArchSPARC64 -> panic "nativeCodeGen: No NCG for SPARC64" ArchS390X -> panic "nativeCodeGen: No NCG for S390X" ArchARM {} -> panic "nativeCodeGen: No NCG for ARM" - ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64" + ArchAArch64 -> panic "nativeCodeGen: No NCG for AArch64" ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha" ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" ArchMipsel -> panic "nativeCodeGen: No NCG for mipsel" @@ -1192,4 +1192,3 @@ initNCGConfig dflags this_mod = NCGConfig , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags } - ===================================== compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs ===================================== @@ -115,7 +115,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl ArchSPARC64 -> panic "trivColorable ArchSPARC64" ArchPPC_64 _ -> 15 ArchARM _ _ _ -> panic "trivColorable ArchARM" - ArchARM64 -> panic "trivColorable ArchARM64" + ArchAArch64 -> panic "trivColorable ArchAArch64" ArchAlpha -> panic "trivColorable ArchAlpha" ArchMipseb -> panic "trivColorable ArchMipseb" ArchMipsel -> panic "trivColorable ArchMipsel" @@ -146,7 +146,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus ArchSPARC64 -> panic "trivColorable ArchSPARC64" ArchPPC_64 _ -> 0 ArchARM _ _ _ -> panic "trivColorable ArchARM" - ArchARM64 -> panic "trivColorable ArchARM64" + ArchAArch64 -> panic "trivColorable ArchAArch64" ArchAlpha -> panic "trivColorable ArchAlpha" ArchMipseb -> panic "trivColorable ArchMipseb" ArchMipsel -> panic "trivColorable ArchMipsel" @@ -179,7 +179,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu ArchSPARC64 -> panic "trivColorable ArchSPARC64" ArchPPC_64 _ -> 20 ArchARM _ _ _ -> panic "trivColorable ArchARM" - ArchARM64 -> panic "trivColorable ArchARM64" + ArchAArch64 -> panic "trivColorable ArchAArch64" ArchAlpha -> panic "trivColorable ArchAlpha" ArchMipseb -> panic "trivColorable ArchMipseb" ArchMipsel -> panic "trivColorable ArchMipsel" ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -223,7 +223,7 @@ linearRegAlloc config entry_ids block_live sccs ArchSPARC64 -> panic "linearRegAlloc ArchSPARC64" ArchPPC -> go $ (frInitFreeRegs platform :: PPC.FreeRegs) ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" - ArchARM64 -> panic "linearRegAlloc ArchARM64" + ArchAArch64 -> panic "linearRegAlloc ArchAArch64" ArchPPC_64 _ -> go $ (frInitFreeRegs platform :: PPC.FreeRegs) ArchAlpha -> panic "linearRegAlloc ArchAlpha" ArchMipseb -> panic "linearRegAlloc ArchMipseb" ===================================== compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs ===================================== @@ -78,7 +78,7 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of ArchSPARC -> SPARC.Instr.maxSpillSlots config ArchSPARC64 -> panic "maxSpillSlots ArchSPARC64" ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" - ArchARM64 -> panic "maxSpillSlots ArchARM64" + ArchAArch64 -> panic "maxSpillSlots ArchAArch64" ArchPPC_64 _ -> PPC.Instr.maxSpillSlots config ArchAlpha -> panic "maxSpillSlots ArchAlpha" ArchMipseb -> panic "maxSpillSlots ArchMipseb" ===================================== compiler/GHC/CmmToAsm/Reg/Target.hs ===================================== @@ -48,7 +48,7 @@ targetVirtualRegSqueeze platform ArchSPARC64 -> panic "targetVirtualRegSqueeze ArchSPARC64" ArchPPC_64 _ -> PPC.virtualRegSqueeze ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" - ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64" + ArchAArch64 -> panic "targetVirtualRegSqueeze ArchAArch64" ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha" ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" @@ -67,7 +67,7 @@ targetRealRegSqueeze platform ArchSPARC64 -> panic "targetRealRegSqueeze ArchSPARC64" ArchPPC_64 _ -> PPC.realRegSqueeze ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" - ArchARM64 -> panic "targetRealRegSqueeze ArchARM64" + ArchAArch64 -> panic "targetRealRegSqueeze ArchAArch64" ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha" ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" @@ -85,7 +85,7 @@ targetClassOfRealReg platform ArchSPARC64 -> panic "targetClassOfRealReg ArchSPARC64" ArchPPC_64 _ -> PPC.classOfRealReg ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" - ArchARM64 -> panic "targetClassOfRealReg ArchARM64" + ArchAArch64 -> panic "targetClassOfRealReg ArchAArch64" ArchAlpha -> panic "targetClassOfRealReg ArchAlpha" ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" @@ -103,7 +103,7 @@ targetMkVirtualReg platform ArchSPARC64 -> panic "targetMkVirtualReg ArchSPARC64" ArchPPC_64 _ -> PPC.mkVirtualReg ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" - ArchARM64 -> panic "targetMkVirtualReg ArchARM64" + ArchAArch64 -> panic "targetMkVirtualReg ArchAArch64" ArchAlpha -> panic "targetMkVirtualReg ArchAlpha" ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" @@ -121,7 +121,7 @@ targetRegDotColor platform ArchSPARC64 -> panic "targetRegDotColor ArchSPARC64" ArchPPC_64 _ -> PPC.regDotColor ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" - ArchARM64 -> panic "targetRegDotColor ArchARM64" + ArchAArch64 -> panic "targetRegDotColor ArchAArch64" ArchAlpha -> panic "targetRegDotColor ArchAlpha" ArchMipseb -> panic "targetRegDotColor ArchMipseb" ArchMipsel -> panic "targetRegDotColor ArchMipsel" ===================================== compiler/GHC/CmmToC.hs ===================================== @@ -1158,7 +1158,7 @@ cLoad platform expr rep bewareLoadStoreAlignment ArchMipseb = True bewareLoadStoreAlignment ArchMipsel = True bewareLoadStoreAlignment (ArchARM {}) = True - bewareLoadStoreAlignment ArchARM64 = True + bewareLoadStoreAlignment ArchAArch64 = True bewareLoadStoreAlignment ArchSPARC = True bewareLoadStoreAlignment ArchSPARC64 = True -- Pessimistically assume that they will also cause problems ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3842,8 +3842,8 @@ default_PIC platform = -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top -- of that. Subsequently we expect all code on aarch64/linux (and macOS) to -- be built with -fPIC. - (OSDarwin, ArchARM64) -> [Opt_PIC] - (OSLinux, ArchARM64) -> [Opt_PIC, Opt_ExternalDynamicRefs] + (OSDarwin, ArchAArch64) -> [Opt_PIC] + (OSLinux, ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs] (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release -- (1 May 2013) we need to ===================================== compiler/GHC/Linker/Dynamic.hs ===================================== @@ -179,7 +179,7 @@ linkDynLib dflags0 o_files dep_packages ++ [ Option "-undefined", Option "dynamic_lookup", Option "-single_module" ] - ++ (if platformArch platform == ArchX86_64 + ++ (if platformArch platform `elem` [ ArchX86_64, ArchAArch64 ] then [ ] else [ Option "-Wl,-read_only_relocs,suppress" ]) ++ [ Option "-install_name", Option instName ] ===================================== compiler/GHC/Linker/Static.hs ===================================== @@ -225,9 +225,9 @@ linkBinary' staticLink dflags o_files dep_units = do (platformOS platform == OSDarwin) && case platformArch platform of ArchX86 -> True - ArchX86_64 -> True - ArchARM {} -> True - ArchARM64 -> True + ArchX86_64 -> True + ArchARM {} -> True + ArchAArch64 -> True _ -> False then ["-Wl,-no_compact_unwind"] else []) @@ -339,4 +339,3 @@ exeFileName platform staticLink output_fn else "a.out" where s ext | null (takeExtension s) = s <.> ext | otherwise = s - ===================================== compiler/GHC/Platform.hs ===================================== @@ -109,7 +109,7 @@ platformOS platform = case platformArchOS platform of isARM :: Arch -> Bool isARM (ArchARM {}) = True -isARM ArchARM64 = True +isARM ArchAArch64 = True isARM _ = False -- | This predicate tells us whether the platform is 32-bit. @@ -232,4 +232,3 @@ platformSOExt platform OSDarwin -> "dylib" OSMinGW32 -> "dll" _ -> "so" - ===================================== compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs ===================================== @@ -1,10 +1,9 @@ {-# LANGUAGE CPP #-} -module GHC.Platform.ARM64 where +module GHC.Platform.AArch64 where import GHC.Prelude #define MACHREGS_NO_REGS 0 #define MACHREGS_aarch64 1 #include "../../../includes/CodeGen.Platform.hs" - ===================================== compiler/GHC/Platform/Regs.hs ===================================== @@ -1,4 +1,3 @@ - module GHC.Platform.Regs (callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg) where @@ -10,7 +9,7 @@ import GHC.Platform import GHC.Platform.Reg import qualified GHC.Platform.ARM as ARM -import qualified GHC.Platform.ARM64 as ARM64 +import qualified GHC.Platform.AArch64 as AArch64 import qualified GHC.Platform.PPC as PPC import qualified GHC.Platform.S390X as S390X import qualified GHC.Platform.SPARC as SPARC @@ -26,12 +25,12 @@ callerSaves platform | platformUnregisterised platform = NoRegs.callerSaves | otherwise = case platformArch platform of - ArchX86 -> X86.callerSaves - ArchX86_64 -> X86_64.callerSaves - ArchS390X -> S390X.callerSaves - ArchSPARC -> SPARC.callerSaves - ArchARM {} -> ARM.callerSaves - ArchARM64 -> ARM64.callerSaves + ArchX86 -> X86.callerSaves + ArchX86_64 -> X86_64.callerSaves + ArchS390X -> S390X.callerSaves + ArchSPARC -> SPARC.callerSaves + ArchARM {} -> ARM.callerSaves + ArchAArch64 -> AArch64.callerSaves arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.callerSaves @@ -48,12 +47,12 @@ activeStgRegs platform | platformUnregisterised platform = NoRegs.activeStgRegs | otherwise = case platformArch platform of - ArchX86 -> X86.activeStgRegs - ArchX86_64 -> X86_64.activeStgRegs - ArchS390X -> S390X.activeStgRegs - ArchSPARC -> SPARC.activeStgRegs - ArchARM {} -> ARM.activeStgRegs - ArchARM64 -> ARM64.activeStgRegs + ArchX86 -> X86.activeStgRegs + ArchX86_64 -> X86_64.activeStgRegs + ArchS390X -> S390X.activeStgRegs + ArchSPARC -> SPARC.activeStgRegs + ArchARM {} -> ARM.activeStgRegs + ArchAArch64 -> AArch64.activeStgRegs arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.activeStgRegs @@ -65,12 +64,12 @@ haveRegBase platform | platformUnregisterised platform = NoRegs.haveRegBase | otherwise = case platformArch platform of - ArchX86 -> X86.haveRegBase - ArchX86_64 -> X86_64.haveRegBase - ArchS390X -> S390X.haveRegBase - ArchSPARC -> SPARC.haveRegBase - ArchARM {} -> ARM.haveRegBase - ArchARM64 -> ARM64.haveRegBase + ArchX86 -> X86.haveRegBase + ArchX86_64 -> X86_64.haveRegBase + ArchS390X -> S390X.haveRegBase + ArchSPARC -> SPARC.haveRegBase + ArchARM {} -> ARM.haveRegBase + ArchAArch64 -> AArch64.haveRegBase arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.haveRegBase @@ -82,12 +81,12 @@ globalRegMaybe platform | platformUnregisterised platform = NoRegs.globalRegMaybe | otherwise = case platformArch platform of - ArchX86 -> X86.globalRegMaybe - ArchX86_64 -> X86_64.globalRegMaybe - ArchS390X -> S390X.globalRegMaybe - ArchSPARC -> SPARC.globalRegMaybe - ArchARM {} -> ARM.globalRegMaybe - ArchARM64 -> ARM64.globalRegMaybe + ArchX86 -> X86.globalRegMaybe + ArchX86_64 -> X86_64.globalRegMaybe + ArchS390X -> S390X.globalRegMaybe + ArchSPARC -> SPARC.globalRegMaybe + ArchARM {} -> ARM.globalRegMaybe + ArchAArch64 -> AArch64.globalRegMaybe arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.globalRegMaybe @@ -99,15 +98,14 @@ freeReg platform | platformUnregisterised platform = NoRegs.freeReg | otherwise = case platformArch platform of - ArchX86 -> X86.freeReg - ArchX86_64 -> X86_64.freeReg - ArchS390X -> S390X.freeReg - ArchSPARC -> SPARC.freeReg - ArchARM {} -> ARM.freeReg - ArchARM64 -> ARM64.freeReg + ArchX86 -> X86.freeReg + ArchX86_64 -> X86_64.freeReg + ArchS390X -> S390X.freeReg + ArchSPARC -> SPARC.freeReg + ArchARM {} -> ARM.freeReg + ArchAArch64 -> AArch64.freeReg arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.freeReg | otherwise -> NoRegs.freeReg - ===================================== compiler/ghc.cabal.in ===================================== @@ -478,7 +478,7 @@ Library GHC.Parser.Types GHC.Platform GHC.Platform.ARM - GHC.Platform.ARM64 + GHC.Platform.AArch64 GHC.Platform.Constants GHC.Platform.NoRegs GHC.Platform.PPC ===================================== config.sub ===================================== @@ -1,8 +1,8 @@ #! /bin/sh # Configuration validation subroutine script. -# Copyright 1992-2019 Free Software Foundation, Inc. +# Copyright 1992-2020 Free Software Foundation, Inc. -timestamp='2019-01-05' +timestamp='2020-09-08' # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by @@ -67,7 +67,7 @@ Report bugs and patches to ." version="\ GNU config.sub ($timestamp) -Copyright 1992-2019 Free Software Foundation, Inc. +Copyright 1992-2020 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." @@ -124,28 +124,27 @@ case $1 in ;; *-*-*-*) basic_machine=$field1-$field2 - os=$field3-$field4 + basic_os=$field3-$field4 ;; *-*-*) # Ambiguous whether COMPANY is present, or skipped and KERNEL-OS is two # parts maybe_os=$field2-$field3 case $maybe_os in - nto-qnx* | linux-gnu* | linux-android* | linux-dietlibc \ - | linux-newlib* | linux-musl* | linux-uclibc* | uclinux-uclibc* \ + nto-qnx* | linux-* | uclinux-uclibc* \ | uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* \ | netbsd*-eabi* | kopensolaris*-gnu* | cloudabi*-eabi* \ | storm-chaos* | os2-emx* | rtmk-nova*) basic_machine=$field1 - os=$maybe_os + basic_os=$maybe_os ;; android-linux) basic_machine=$field1-unknown - os=linux-android + basic_os=linux-android ;; *) basic_machine=$field1-$field2 - os=$field3 + basic_os=$field3 ;; esac ;; @@ -154,7 +153,7 @@ case $1 in case $field1-$field2 in decstation-3100) basic_machine=mips-dec - os= + basic_os= ;; *-*) # Second component is usually, but not always the OS @@ -162,7 +161,7 @@ case $1 in # Prevent following clause from handling this valid os sun*os*) basic_machine=$field1 - os=$field2 + basic_os=$field2 ;; # Manufacturers dec* | mips* | sequent* | encore* | pc533* | sgi* | sony* \ @@ -175,11 +174,11 @@ case $1 in | microblaze* | sim | cisco \ | oki | wec | wrs | winbond) basic_machine=$field1-$field2 - os= + basic_os= ;; *) basic_machine=$field1 - os=$field2 + basic_os=$field2 ;; esac ;; @@ -191,450 +190,451 @@ case $1 in case $field1 in 386bsd) basic_machine=i386-pc - os=bsd + basic_os=bsd ;; a29khif) basic_machine=a29k-amd - os=udi + basic_os=udi ;; adobe68k) basic_machine=m68010-adobe - os=scout + basic_os=scout ;; alliant) basic_machine=fx80-alliant - os= + basic_os= ;; altos | altos3068) basic_machine=m68k-altos - os= + basic_os= ;; am29k) basic_machine=a29k-none - os=bsd + basic_os=bsd ;; amdahl) basic_machine=580-amdahl - os=sysv + basic_os=sysv ;; amiga) basic_machine=m68k-unknown - os= + basic_os= ;; amigaos | amigados) basic_machine=m68k-unknown - os=amigaos + basic_os=amigaos ;; amigaunix | amix) basic_machine=m68k-unknown - os=sysv4 + basic_os=sysv4 ;; apollo68) basic_machine=m68k-apollo - os=sysv + basic_os=sysv ;; apollo68bsd) basic_machine=m68k-apollo - os=bsd + basic_os=bsd ;; aros) basic_machine=i386-pc - os=aros + basic_os=aros ;; aux) basic_machine=m68k-apple - os=aux + basic_os=aux ;; balance) basic_machine=ns32k-sequent - os=dynix + basic_os=dynix ;; blackfin) basic_machine=bfin-unknown - os=linux + basic_os=linux ;; cegcc) basic_machine=arm-unknown - os=cegcc + basic_os=cegcc ;; convex-c1) basic_machine=c1-convex - os=bsd + basic_os=bsd ;; convex-c2) basic_machine=c2-convex - os=bsd + basic_os=bsd ;; convex-c32) basic_machine=c32-convex - os=bsd + basic_os=bsd ;; convex-c34) basic_machine=c34-convex - os=bsd + basic_os=bsd ;; convex-c38) basic_machine=c38-convex - os=bsd + basic_os=bsd ;; cray) basic_machine=j90-cray - os=unicos + basic_os=unicos ;; crds | unos) basic_machine=m68k-crds - os= + basic_os= ;; da30) basic_machine=m68k-da30 - os= + basic_os= ;; decstation | pmax | pmin | dec3100 | decstatn) basic_machine=mips-dec - os= + basic_os= ;; delta88) basic_machine=m88k-motorola - os=sysv3 + basic_os=sysv3 ;; dicos) basic_machine=i686-pc - os=dicos + basic_os=dicos ;; djgpp) basic_machine=i586-pc - os=msdosdjgpp + basic_os=msdosdjgpp ;; ebmon29k) basic_machine=a29k-amd - os=ebmon + basic_os=ebmon ;; es1800 | OSE68k | ose68k | ose | OSE) basic_machine=m68k-ericsson - os=ose + basic_os=ose ;; gmicro) basic_machine=tron-gmicro - os=sysv + basic_os=sysv ;; go32) basic_machine=i386-pc - os=go32 + basic_os=go32 ;; h8300hms) basic_machine=h8300-hitachi - os=hms + basic_os=hms ;; h8300xray) basic_machine=h8300-hitachi - os=xray + basic_os=xray ;; h8500hms) basic_machine=h8500-hitachi - os=hms + basic_os=hms ;; harris) basic_machine=m88k-harris - os=sysv3 + basic_os=sysv3 ;; - hp300) + hp300 | hp300hpux) basic_machine=m68k-hp + basic_os=hpux ;; hp300bsd) basic_machine=m68k-hp - os=bsd - ;; - hp300hpux) - basic_machine=m68k-hp - os=hpux + basic_os=bsd ;; hppaosf) basic_machine=hppa1.1-hp - os=osf + basic_os=osf ;; hppro) basic_machine=hppa1.1-hp - os=proelf + basic_os=proelf ;; i386mach) basic_machine=i386-mach - os=mach - ;; - vsta) - basic_machine=i386-pc - os=vsta + basic_os=mach ;; isi68 | isi) basic_machine=m68k-isi - os=sysv + basic_os=sysv ;; m68knommu) basic_machine=m68k-unknown - os=linux + basic_os=linux ;; magnum | m3230) basic_machine=mips-mips - os=sysv + basic_os=sysv ;; merlin) basic_machine=ns32k-utek - os=sysv + basic_os=sysv ;; mingw64) basic_machine=x86_64-pc - os=mingw64 + basic_os=mingw64 ;; mingw32) basic_machine=i686-pc - os=mingw32 + basic_os=mingw32 ;; mingw32ce) basic_machine=arm-unknown - os=mingw32ce + basic_os=mingw32ce ;; monitor) basic_machine=m68k-rom68k - os=coff + basic_os=coff ;; morphos) basic_machine=powerpc-unknown - os=morphos + basic_os=morphos ;; moxiebox) basic_machine=moxie-unknown - os=moxiebox + basic_os=moxiebox ;; msdos) basic_machine=i386-pc - os=msdos + basic_os=msdos ;; msys) basic_machine=i686-pc - os=msys + basic_os=msys ;; mvs) basic_machine=i370-ibm - os=mvs + basic_os=mvs ;; nacl) basic_machine=le32-unknown - os=nacl + basic_os=nacl ;; ncr3000) basic_machine=i486-ncr - os=sysv4 + basic_os=sysv4 ;; netbsd386) basic_machine=i386-pc - os=netbsd + basic_os=netbsd ;; netwinder) basic_machine=armv4l-rebel - os=linux + basic_os=linux ;; news | news700 | news800 | news900) basic_machine=m68k-sony - os=newsos + basic_os=newsos ;; news1000) basic_machine=m68030-sony - os=newsos + basic_os=newsos ;; necv70) basic_machine=v70-nec - os=sysv + basic_os=sysv ;; nh3000) basic_machine=m68k-harris - os=cxux + basic_os=cxux ;; nh[45]000) basic_machine=m88k-harris - os=cxux + basic_os=cxux ;; nindy960) basic_machine=i960-intel - os=nindy + basic_os=nindy ;; mon960) basic_machine=i960-intel - os=mon960 + basic_os=mon960 ;; nonstopux) basic_machine=mips-compaq - os=nonstopux + basic_os=nonstopux ;; os400) basic_machine=powerpc-ibm - os=os400 + basic_os=os400 ;; OSE68000 | ose68000) basic_machine=m68000-ericsson - os=ose + basic_os=ose ;; os68k) basic_machine=m68k-none - os=os68k + basic_os=os68k ;; paragon) basic_machine=i860-intel - os=osf + basic_os=osf ;; parisc) basic_machine=hppa-unknown - os=linux + basic_os=linux + ;; + psp) + basic_machine=mipsallegrexel-sony + basic_os=psp ;; pw32) basic_machine=i586-unknown - os=pw32 + basic_os=pw32 ;; rdos | rdos64) basic_machine=x86_64-pc - os=rdos + basic_os=rdos ;; rdos32) basic_machine=i386-pc - os=rdos + basic_os=rdos ;; rom68k) basic_machine=m68k-rom68k - os=coff + basic_os=coff ;; sa29200) basic_machine=a29k-amd - os=udi + basic_os=udi ;; sei) basic_machine=mips-sei - os=seiux + basic_os=seiux ;; sequent) basic_machine=i386-sequent - os= + basic_os= ;; sps7) basic_machine=m68k-bull - os=sysv2 + basic_os=sysv2 ;; st2000) basic_machine=m68k-tandem - os= + basic_os= ;; stratus) basic_machine=i860-stratus - os=sysv4 + basic_os=sysv4 ;; sun2) basic_machine=m68000-sun - os= + basic_os= ;; sun2os3) basic_machine=m68000-sun - os=sunos3 + basic_os=sunos3 ;; sun2os4) basic_machine=m68000-sun - os=sunos4 + basic_os=sunos4 ;; sun3) basic_machine=m68k-sun - os= + basic_os= ;; sun3os3) basic_machine=m68k-sun - os=sunos3 + basic_os=sunos3 ;; sun3os4) basic_machine=m68k-sun - os=sunos4 + basic_os=sunos4 ;; sun4) basic_machine=sparc-sun - os= + basic_os= ;; sun4os3) basic_machine=sparc-sun - os=sunos3 + basic_os=sunos3 ;; sun4os4) basic_machine=sparc-sun - os=sunos4 + basic_os=sunos4 ;; sun4sol2) basic_machine=sparc-sun - os=solaris2 + basic_os=solaris2 ;; sun386 | sun386i | roadrunner) basic_machine=i386-sun - os= + basic_os= ;; sv1) basic_machine=sv1-cray - os=unicos + basic_os=unicos ;; symmetry) basic_machine=i386-sequent - os=dynix + basic_os=dynix ;; t3e) basic_machine=alphaev5-cray - os=unicos + basic_os=unicos ;; t90) basic_machine=t90-cray - os=unicos + basic_os=unicos ;; toad1) basic_machine=pdp10-xkl - os=tops20 + basic_os=tops20 ;; tpf) basic_machine=s390x-ibm - os=tpf + basic_os=tpf ;; udi29k) basic_machine=a29k-amd - os=udi + basic_os=udi ;; ultra3) basic_machine=a29k-nyu - os=sym1 + basic_os=sym1 ;; v810 | necv810) basic_machine=v810-nec - os=none + basic_os=none ;; vaxv) basic_machine=vax-dec - os=sysv + basic_os=sysv ;; vms) basic_machine=vax-dec - os=vms + basic_os=vms + ;; + vsta) + basic_machine=i386-pc + basic_os=vsta ;; vxworks960) basic_machine=i960-wrs - os=vxworks + basic_os=vxworks ;; vxworks68) basic_machine=m68k-wrs - os=vxworks + basic_os=vxworks ;; vxworks29k) basic_machine=a29k-wrs - os=vxworks + basic_os=vxworks ;; xbox) basic_machine=i686-pc - os=mingw32 + basic_os=mingw32 ;; ymp) basic_machine=ymp-cray - os=unicos + basic_os=unicos ;; *) basic_machine=$1 - os= + basic_os= ;; esac ;; @@ -686,17 +686,17 @@ case $basic_machine in bluegene*) cpu=powerpc vendor=ibm - os=cnk + basic_os=cnk ;; decsystem10* | dec10*) cpu=pdp10 vendor=dec - os=tops10 + basic_os=tops10 ;; decsystem20* | dec20*) cpu=pdp10 vendor=dec - os=tops20 + basic_os=tops20 ;; delta | 3300 | motorola-3300 | motorola-delta \ | 3300-motorola | delta-motorola) @@ -706,7 +706,7 @@ case $basic_machine in dpx2*) cpu=m68k vendor=bull - os=sysv3 + basic_os=sysv3 ;; encore | umax | mmax) cpu=ns32k @@ -715,7 +715,7 @@ case $basic_machine in elxsi) cpu=elxsi vendor=elxsi - os=${os:-bsd} + basic_os=${basic_os:-bsd} ;; fx2800) cpu=i860 @@ -728,7 +728,7 @@ case $basic_machine in h3050r* | hiux*) cpu=hppa1.1 vendor=hitachi - os=hiuxwe2 + basic_os=hiuxwe2 ;; hp3k9[0-9][0-9] | hp9[0-9][0-9]) cpu=hppa1.0 @@ -771,36 +771,36 @@ case $basic_machine in i*86v32) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv32 + basic_os=sysv32 ;; i*86v4*) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv4 + basic_os=sysv4 ;; i*86v) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv + basic_os=sysv ;; i*86sol2) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=solaris2 + basic_os=solaris2 ;; j90 | j90-cray) cpu=j90 vendor=cray - os=${os:-unicos} + basic_os=${basic_os:-unicos} ;; iris | iris4d) cpu=mips vendor=sgi - case $os in + case $basic_os in irix*) ;; *) - os=irix4 + basic_os=irix4 ;; esac ;; @@ -811,26 +811,26 @@ case $basic_machine in *mint | mint[0-9]* | *MiNT | *MiNT[0-9]*) cpu=m68k vendor=atari - os=mint + basic_os=mint ;; news-3600 | risc-news) cpu=mips vendor=sony - os=newsos + basic_os=newsos ;; next | m*-next) cpu=m68k vendor=next - case $os in + case $basic_os in openstep*) ;; nextstep*) ;; ns2*) - os=nextstep2 + basic_os=nextstep2 ;; *) - os=nextstep3 + basic_os=nextstep3 ;; esac ;; @@ -841,12 +841,12 @@ case $basic_machine in op50n-* | op60c-*) cpu=hppa1.1 vendor=oki - os=proelf + basic_os=proelf ;; pa-hitachi) cpu=hppa1.1 vendor=hitachi - os=hiuxwe2 + basic_os=hiuxwe2 ;; pbd) cpu=sparc @@ -883,12 +883,12 @@ case $basic_machine in sde) cpu=mipsisa32 vendor=sde - os=${os:-elf} + basic_os=${basic_os:-elf} ;; simso-wrs) cpu=sparclite vendor=wrs - os=vxworks + basic_os=vxworks ;; tower | tower-32) cpu=m68k @@ -905,7 +905,7 @@ case $basic_machine in w89k-*) cpu=hppa1.1 vendor=winbond - os=proelf + basic_os=proelf ;; none) cpu=none @@ -958,11 +958,11 @@ case $cpu-$vendor in # some cases the only manufacturer, in others, it is the most popular. craynv-unknown) vendor=cray - os=${os:-unicosmp} + basic_os=${basic_os:-unicosmp} ;; c90-unknown | c90-cray) vendor=cray - os=${os:-unicos} + basic_os=${Basic_os:-unicos} ;; fx80-unknown) vendor=alliant @@ -1006,7 +1006,7 @@ case $cpu-$vendor in dpx20-unknown | dpx20-bull) cpu=rs6000 vendor=bull - os=${os:-bosx} + basic_os=${basic_os:-bosx} ;; # Here we normalize CPU types irrespective of the vendor @@ -1015,7 +1015,7 @@ case $cpu-$vendor in ;; blackfin-*) cpu=bfin - os=linux + basic_os=linux ;; c54x-*) cpu=tic54x @@ -1028,7 +1028,7 @@ case $cpu-$vendor in ;; e500v[12]-*) cpu=powerpc - os=$os"spe" + basic_os=${basic_os}"spe" ;; mips3*-*) cpu=mips64 @@ -1038,7 +1038,7 @@ case $cpu-$vendor in ;; m68knommu-*) cpu=m68k - os=linux + basic_os=linux ;; m9s12z-* | m68hcs12z-* | hcs12z-* | s12z-*) cpu=s12z @@ -1048,7 +1048,7 @@ case $cpu-$vendor in ;; parisc-*) cpu=hppa - os=linux + basic_os=linux ;; pentium-* | p5-* | k5-* | k6-* | nexgen-* | viac3-*) cpu=i586 @@ -1104,11 +1104,14 @@ case $cpu-$vendor in xscale-* | xscalee[bl]-*) cpu=`echo "$cpu" | sed 's/^xscale/arm/'` ;; + arm64-*) + cpu=aarch64 + ;; # Recognize the canonical CPU Types that limit and/or modify the # company names they are paired with. cr16-*) - os=${os:-elf} + basic_os=${basic_os:-elf} ;; crisv32-* | etraxfs*-*) cpu=crisv32 @@ -1119,7 +1122,7 @@ case $cpu-$vendor in vendor=axis ;; crx-*) - os=${os:-elf} + basic_os=${basic_os:-elf} ;; neo-tandem) cpu=neo @@ -1141,16 +1144,12 @@ case $cpu-$vendor in cpu=nsx vendor=tandem ;; - s390-*) - cpu=s390 - vendor=ibm - ;; - s390x-*) - cpu=s390x - vendor=ibm + mipsallegrexel-sony) + cpu=mipsallegrexel + vendor=sony ;; tile*-*) - os=${os:-linux-gnu} + basic_os=${basic_os:-linux-gnu} ;; *) @@ -1167,12 +1166,12 @@ case $cpu-$vendor in | am33_2.0 \ | amdgcn \ | arc | arceb \ - | arm | arm[lb]e | arme[lb] | armv* \ + | arm | arm[lb]e | arme[lb] | armv* \ | avr | avr32 \ | asmjs \ | ba \ | be32 | be64 \ - | bfin | bs2000 \ + | bfin | bpf | bs2000 \ | c[123]* | c30 | [cjt]90 | c4x \ | c8051 | clipper | craynv | csky | cydra \ | d10v | d30v | dlx | dsp16xx \ @@ -1232,6 +1231,7 @@ case $cpu-$vendor in | pyramid \ | riscv | riscv32 | riscv64 \ | rl78 | romp | rs6000 | rx \ + | s390 | s390x \ | score \ | sh | shl \ | sh[1234] | sh[24]a | sh[24]ae[lb] | sh[23]e | she[lb] | sh[lb]e \ @@ -1278,8 +1278,43 @@ esac # Decode manufacturer-specific aliases for certain operating systems. -if [ x$os != x ] +if test x$basic_os != x then + +# First recognize some ad-hoc caes, or perhaps split kernel-os, or else just +# set os. +case $basic_os in + gnu/linux*) + kernel=linux + os=`echo $basic_os | sed -e 's|gnu/linux|gnu|'` + ;; + nto-qnx*) + kernel=nto + os=`echo $basic_os | sed -e 's|nto-qnx|qnx|'` + ;; + *-*) + # shellcheck disable=SC2162 + IFS="-" read kernel os <&2 - exit 1 + # No normalization, but not necessarily accepted, that comes below. ;; esac + else # Here we handle the default operating systems that come with various machines. @@ -1533,6 +1493,7 @@ else # will signal an error saying that MANUFACTURER isn't an operating # system, and we'll never get to this point. +kernel= case $cpu-$vendor in score-*) os=elf @@ -1544,7 +1505,8 @@ case $cpu-$vendor in os=riscix1.2 ;; arm*-rebel) - os=linux + kernel=linux + os=gnu ;; arm*-semi) os=aout @@ -1710,84 +1672,169 @@ case $cpu-$vendor in os=none ;; esac + fi +# Now, validate our (potentially fixed-up) OS. +case $os in + # Sometimes we do "kernel-abi", so those need to count as OSes. + musl* | newlib* | uclibc*) + ;; + # Likewise for "kernel-libc" + eabi | eabihf | gnueabi | gnueabihf) + ;; + # Now accept the basic system types. + # The portable systems comes first. + # Each alternative MUST end in a * to match a version number. + gnu* | android* | bsd* | mach* | minix* | genix* | ultrix* | irix* \ + | *vms* | esix* | aix* | cnk* | sunos | sunos[34]* \ + | hpux* | unos* | osf* | luna* | dgux* | auroraux* | solaris* \ + | sym* | plan9* | psp* | sim* | xray* | os68k* | v88r* \ + | hiux* | abug | nacl* | netware* | windows* \ + | os9* | macos* | osx* | ios* \ + | mpw* | magic* | mmixware* | mon960* | lnews* \ + | amigaos* | amigados* | msdos* | newsos* | unicos* | aof* \ + | aos* | aros* | cloudabi* | sortix* | twizzler* \ + | nindy* | vxsim* | vxworks* | ebmon* | hms* | mvs* \ + | clix* | riscos* | uniplus* | iris* | isc* | rtu* | xenix* \ + | mirbsd* | netbsd* | dicos* | openedition* | ose* \ + | bitrig* | openbsd* | solidbsd* | libertybsd* | os108* \ + | ekkobsd* | freebsd* | riscix* | lynxos* | os400* \ + | bosx* | nextstep* | cxux* | aout* | elf* | oabi* \ + | ptx* | coff* | ecoff* | winnt* | domain* | vsta* \ + | udi* | lites* | ieee* | go32* | aux* | hcos* \ + | chorusrdb* | cegcc* | glidix* \ + | cygwin* | msys* | pe* | moss* | proelf* | rtems* \ + | midipix* | mingw32* | mingw64* | mint* \ + | uxpv* | beos* | mpeix* | udk* | moxiebox* \ + | interix* | uwin* | mks* | rhapsody* | darwin* \ + | openstep* | oskit* | conix* | pw32* | nonstopux* \ + | storm-chaos* | tops10* | tenex* | tops20* | its* \ + | os2* | vos* | palmos* | uclinux* | nucleus* | morphos* \ + | scout* | superux* | sysv* | rtmk* | tpf* | windiss* \ + | powermax* | dnix* | nx6 | nx7 | sei* | dragonfly* \ + | skyos* | haiku* | rdos* | toppers* | drops* | es* \ + | onefs* | tirtos* | phoenix* | fuchsia* | redox* | bme* \ + | midnightbsd* | amdhsa* | unleashed* | emscripten* | wasi* \ + | nsk* | powerunix* | genode* | zvmoe* | qnx* ) + ;; + # This one is extra strict with allowed versions + sco3.2v2 | sco3.2v[4-9]* | sco5v6*) + # Don't forget version if it is 3.2v4 or newer. + ;; + none) + ;; + *) + echo Invalid configuration \`"$1"\': OS \`"$os"\' not recognized 1>&2 + exit 1 + ;; +esac + +# As a final step for OS-related things, validate the OS-kernel combination +# (given a valid OS), if there is a kernel. +case $kernel-$os in + linux-gnu* | linux-dietlibc* | linux-android* | linux-newlib* | linux-musl* | linux-uclibc* ) + ;; + -dietlibc* | -newlib* | -musl* | -uclibc* ) + # These are just libc implementations, not actual OSes, and thus + # require a kernel. + echo "Invalid configuration \`$1': libc \`$os' needs explicit kernel." 1>&2 + exit 1 + ;; + kfreebsd*-gnu* | kopensolaris*-gnu*) + ;; + nto-qnx*) + ;; + *-eabi* | *-gnueabi*) + ;; + -*) + # Blank kernel with real OS is always fine. + ;; + *-*) + echo "Invalid configuration \`$1': Kernel \`$kernel' not known to work with OS \`$os'." 1>&2 + exit 1 + ;; +esac + # Here we handle the case where we know the os, and the CPU type, but not the # manufacturer. We pick the logical manufacturer. case $vendor in unknown) - case $os in - riscix*) + case $cpu-$os in + *-riscix*) vendor=acorn ;; - sunos*) + *-sunos*) vendor=sun ;; - cnk*|-aix*) + *-cnk* | *-aix*) vendor=ibm ;; - beos*) + *-beos*) vendor=be ;; - hpux*) + *-hpux*) vendor=hp ;; - mpeix*) + *-mpeix*) vendor=hp ;; - hiux*) + *-hiux*) vendor=hitachi ;; - unos*) + *-unos*) vendor=crds ;; - dgux*) + *-dgux*) vendor=dg ;; - luna*) + *-luna*) vendor=omron ;; - genix*) + *-genix*) vendor=ns ;; - clix*) + *-clix*) vendor=intergraph ;; - mvs* | opened*) + *-mvs* | *-opened*) + vendor=ibm + ;; + *-os400*) vendor=ibm ;; - os400*) + s390-* | s390x-*) vendor=ibm ;; - ptx*) + *-ptx*) vendor=sequent ;; - tpf*) + *-tpf*) vendor=ibm ;; - vxsim* | vxworks* | windiss*) + *-vxsim* | *-vxworks* | *-windiss*) vendor=wrs ;; - aux*) + *-aux*) vendor=apple ;; - hms*) + *-hms*) vendor=hitachi ;; - mpw* | macos*) + *-mpw* | *-macos*) vendor=apple ;; - *mint | mint[0-9]* | *MiNT | MiNT[0-9]*) + *-*mint | *-mint[0-9]* | *-*MiNT | *-MiNT[0-9]*) vendor=atari ;; - vos*) + *-vos*) vendor=stratus ;; esac ;; esac -echo "$cpu-$vendor-$os" +echo "$cpu-$vendor-${kernel:+$kernel-}$os" exit # Local variables: ===================================== includes/CodeGen.Platform.hs ===================================== @@ -94,7 +94,7 @@ import GHC.Platform.Reg # define zmm14 30 # define zmm15 31 --- Note: these are only needed for ARM/ARM64 because globalRegMaybe is now used in CmmSink.hs. +-- Note: these are only needed for ARM/AArch64 because globalRegMaybe is now used in CmmSink.hs. -- Since it's only used to check 'isJust', the actual values don't matter, thus -- I'm not sure if these are the correct numberings. -- Normally, the register names are just stringified as part of the REG() macro @@ -1096,4 +1096,3 @@ freeReg _ = True freeReg = panic "freeReg not defined for this platform" #endif - ===================================== includes/rts/Flags.h ===================================== @@ -199,6 +199,8 @@ typedef struct _CONCURRENT_FLAGS { * When linkerAlwaysPic is true, the runtime linker assume that all object * files were compiled with -fPIC -fexternal-dynamic-refs and load them * anywhere in the address space. + * Note that there is no 32bit darwin system we can realistically expect to + * run on or compile for. */ #if defined(darwin_HOST_OS) || defined(aarch64_HOST_ARCH) #define DEFAULT_LINKER_ALWAYS_PIC true ===================================== includes/rts/storage/GC.h ===================================== @@ -202,7 +202,7 @@ typedef void* AdjustorExecutable; AdjustorWritable allocateExec(W_ len, AdjustorExecutable *exec_addr); void flushExec(W_ len, AdjustorExecutable exec_addr); -#if defined(ios_HOST_OS) +#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) AdjustorWritable execToWritable(AdjustorExecutable exec); #endif void freeExec (AdjustorExecutable p); ===================================== libraries/ghc-boot/GHC/Platform/ArchOS.hs ===================================== @@ -41,7 +41,7 @@ data Arch | ArchSPARC | ArchSPARC64 | ArchARM ArmISA [ArmISAExt] ArmABI - | ArchARM64 + | ArchAArch64 | ArchAlpha | ArchMipseb | ArchMipsel @@ -130,7 +130,7 @@ stringEncodeArch = \case ArchARM ARMv5 _ _ -> "armv5" ArchARM ARMv6 _ _ -> "armv6" ArchARM ARMv7 _ _ -> "armv7" - ArchARM64 -> "aarch64" + ArchAArch64 -> "aarch64" ArchAlpha -> "alpha" ArchMipseb -> "mipseb" ArchMipsel -> "mipsel" ===================================== libraries/ghci/GHCi/InfoTable.hsc ===================================== @@ -69,7 +69,7 @@ data Arch = ArchSPARC | ArchX86_64 | ArchAlpha | ArchARM - | ArchARM64 + | ArchAArch64 | ArchPPC64 | ArchPPC64LE | ArchS390X @@ -102,7 +102,7 @@ mArch = #elif defined(arm_HOST_ARCH) Just ArchARM #elif defined(aarch64_HOST_ARCH) - Just ArchARM64 + Just ArchAArch64 #elif defined(powerpc64_HOST_ARCH) Just ArchPPC64 #elif defined(powerpc64le_HOST_ARCH) @@ -214,7 +214,7 @@ mkJumpToAddr' platform a = case platform of , 0x11, 0xff, 0x2f, 0xe1 , byte0 w32, byte1 w32, byte2 w32, byte3 w32] - ArchARM64 { } -> + ArchAArch64 { } -> -- Generates: -- -- ldr x1, label ===================================== llvm-targets ===================================== @@ -1,7 +1,7 @@ -[("i386-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) -,("i686-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) -,("x86_64-unknown-windows", ("e-m:w-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+soft-float -fp16 -vfp2 -vfp2sp -vfp2d16 -vfp2d16sp -vfp3 -vfp3sp -vfp3d16 -vfp3d16sp -vfp4 -vfp4sp -vfp4d16 -vfp4d16sp -fp-armv8 -fp-armv8sp -fp-armv8d16 -fp-armv8d16sp -fullfp16 -neon -crypto -dotprod -fp16fml -fp64 -d32 -fpregs +strict-align")) +[("i386-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("i686-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("x86_64-unknown-windows", ("e-m:w-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+strict-align")) ,("arm-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("arm-unknown-linux-musleabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("armv6-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1136jf-s", "+strict-align")) @@ -21,31 +21,32 @@ ,("aarch64-unknown-linux-gnu", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("aarch64-unknown-linux-musl", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("aarch64-unknown-linux", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i386-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux-musl", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux-android", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16")) -,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) +,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("x86_64-unknown-linux-gnu", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-musl", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-android", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16")) +,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) ,("aarch64-unknown-linux-android", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) +,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) ,("powerpc64le-unknown-linux-gnu", ("e-m:e-i64:64-n32:64", "ppc64le", "")) ,("powerpc64le-unknown-linux-musl", ("e-m:e-i64:64-n32:64", "ppc64le", "+secure-plt")) ,("powerpc64le-unknown-linux", ("e-m:e-i64:64-n32:64", "ppc64le", "")) ,("s390x-ibm-linux", ("E-m:e-i1:8:16-i8:8:16-i64:64-f128:64-a:8:16-n32:64", "z10", "")) -,("i386-apple-darwin", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) -,("x86_64-apple-darwin", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) -,("armv7-apple-ios", ("e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) -,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("i386-apple-ios", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) -,("x86_64-apple-ios", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) -,("amd64-portbld-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", "")) +,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", "")) +,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "vortex", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) +,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) +,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes")) +,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) +,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) +,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("aarch64-unknown-freebsd", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("armv6-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("armv7-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+strict-align")) ===================================== rts/Adjustor.c ===================================== @@ -99,7 +99,7 @@ freeHaskellFunctionPtr(void* ptr) { ffi_closure *cl; -#if defined(ios_HOST_OS) +#if defined(ios_HOST_OS) || defined(darwin_HOST_OS) cl = execToWritable(ptr); #else cl = (ffi_closure*)ptr; ===================================== rts/StgCRun.c ===================================== @@ -932,7 +932,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { "br %1\n\t" ".globl " STG_RETURN "\n\t" -#if !defined(ios_HOST_OS) +#if !defined(ios_HOST_OS) && !defined(darwin_HOST_OS) ".type " STG_RETURN ", %%function\n" #endif STG_RETURN ":\n\t" @@ -941,7 +941,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { */ "add sp, sp, %3\n\t" /* - * Return the new register table, taking it from Stg's R1 (ARM64's R22). + * Return the new register table, taking it from Stg's R1 (AArch64's R22). */ "mov %0, x22\n\t" /* ===================================== rts/linker/elf_plt_aarch64.c ===================================== @@ -46,8 +46,8 @@ bool needStubForRelaAarch64(Elf_Rela * rela) { bool makeStubAarch64(Stub * s) { // We (the linker) may corrupt registers x16 (IP0) and x17 (IP1) [AAPCS64] - // and the condition flags, according to the "ELF for the ARM64 - // Architecture". + // and the condition flags, according to the "ELF for the ARM 64-bit + // Architecture (AArch64)". // // [Special purpose regs] // X16 and X17 are IP0 and IP1, intra-procedure-call temporary registers. ===================================== rts/linker/elf_reloc.c ===================================== @@ -4,7 +4,7 @@ #if defined(OBJFORMAT_ELF) -/* we currently only use this abstraction for elf/arm64 */ +/* we currently only use this abstraction for elf/aarch64 */ #if defined(aarch64_HOST_ARCH) bool ===================================== rts/package.conf.in ===================================== @@ -318,7 +318,7 @@ ld-options: , "-Wl,-search_paths_first" #endif -#if defined(darwin_HOST_OS) && !defined(x86_64_HOST_ARCH) +#if defined(darwin_HOST_OS) && !defined(x86_64_HOST_ARCH) && !defined(aarch64_HOST_ARCH) , "-read_only_relocs", "warning" #endif ===================================== rts/rts.cabal.in ===================================== @@ -398,7 +398,7 @@ library if os(osx) ld-options: "-Wl,-search_paths_first" - if !arch(x86_64) + if !arch(x86_64) && !arch(aarch64) ld-options: -read_only_relocs warning cmm-sources: Apply.cmm ===================================== rts/sm/Storage.c ===================================== @@ -30,7 +30,7 @@ #include "GC.h" #include "Evac.h" #include "NonMoving.h" -#if defined(ios_HOST_OS) +#if defined(ios_HOST_OS) || defined(darwin_HOST_OS) #include "Hash.h" #endif @@ -1648,7 +1648,7 @@ StgWord calcTotalCompactW (void) should be modified to use allocateExec instead of VirtualAlloc. ------------------------------------------------------------------------- */ -#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) +#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) #include #endif @@ -1679,7 +1679,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) /* x86 doesn't need to do anything, so just suppress some warnings. */ (void)len; (void)exec_addr; -#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) +#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); #elif defined(__clang__) @@ -1734,7 +1734,7 @@ void freeExec (AdjustorExecutable addr) RELEASE_SM_LOCK } -#elif defined(ios_HOST_OS) +#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) static HashTable* allocatedExecs; ===================================== utils/llvm-targets/gen-data-layout.sh ===================================== @@ -84,9 +84,12 @@ TARGETS=( # macOS "i386-apple-darwin" "x86_64-apple-darwin" + "arm64-apple-darwin" # iOS - "armv7-apple-ios arm64-apple-ios" - "i386-apple-ios x86_64-apple-ios" + "armv7-apple-ios" + "arm64-apple-ios" + "i386-apple-ios" + "x86_64-apple-ios" ######################### # FreeBSD View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/50a2aa075ab72758f61ab40ec2929cd4e2d30022 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/50a2aa075ab72758f61ab40ec2929cd4e2d30022 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 Fri Nov 13 13:29:01 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 13 Nov 2020 08:29:01 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5fae8a1d83825_43133fa68f747de839102e@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 62838a7e by Sebastian Graf at 2020-11-13T08:28:52-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - b9ea1969 by Sebastian Graf at 2020-11-13T08:28:52-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - db107104 by David Eichmann at 2020-11-13T08:28:52-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 238fa01a by Ben Gamari at 2020-11-13T08:28:53-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 13 changed files: - .gitlab-ci.yml - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - includes/RtsAPI.h - rts/RtsAPI.c - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== .gitlab-ci.yml ===================================== @@ -307,16 +307,20 @@ hadrian-ghc-in-ghci: - .gitlab/ci.sh setup - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache variables: GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache lint-base: extends: .lint-params script: - hadrian/build -c -j stage1:lib:base - hadrian/build -j lint:base - cache: - key: lint ############################################################ # Validation via Pipelines (make) ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity at@(AT oss _) ar + | oss `lengthAtMost` ar = at + | otherwise = AT (take ar oss) topDiv + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== includes/RtsAPI.h ===================================== @@ -17,8 +17,10 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" +#include "rts/Types.h" #include "rts/EventLogWriter.h" + /* * Running the scheduler */ @@ -566,6 +568,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== rts/RtsAPI.c ===================================== @@ -15,6 +15,7 @@ #include "Prelude.h" #include "Schedule.h" #include "Capability.h" +#include "StableName.h" #include "StablePtr.h" #include "Threads.h" #include "Weak.h" @@ -809,6 +810,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +874,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/55f1b984703094ba9409effb96d9d7b0358010f8...238fa01aac08f19b11daddd588949ddace09aa47 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/55f1b984703094ba9409effb96d9d7b0358010f8...238fa01aac08f19b11daddd588949ddace09aa47 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 Fri Nov 13 13:57:59 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 08:57:59 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11.1 Message-ID: <5fae90e769c8e_43133fa6ca0188fc396168@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: 177bdc53 by Ben Gamari at 2020-11-13T08:57:49-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 9 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/Main.hs - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 24ab6ad4e440db4d06ea79ee54e6ac8788d6c249 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit c25d6a76702b454426e149fb590da5cb69f3bd0a ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit e079823775066bcab56b22842be6cce6e060fb9f ===================================== utils/ghc-cabal/Main.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -28,6 +29,7 @@ import Distribution.Verbosity import qualified Distribution.InstalledPackageInfo as Installed import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Utils.ShortText (fromShortText) +import Distribution.Utils.Path (getSymbolicPath) import Control.Exception (bracket) import Control.Monad @@ -433,7 +435,7 @@ generate directory distdir config_args variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd), - variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), + variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/177bdc53ad609edd47391e0775173ef24b0798f2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/177bdc53ad609edd47391e0775173ef24b0798f2 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 Fri Nov 13 14:12:06 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 09:12:06 -0500 Subject: [Git][ghc/ghc][wip/boxed-rep] 2 commits: Fix broken tests Message-ID: <5fae943674140_4313d8252504052a3@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/boxed-rep at Glasgow Haskell Compiler / GHC Commits: 7b1da914 by Andrew Martin at 2020-11-12T20:15:53-05:00 Fix broken tests - - - - - 39caf4f1 by Andrew Martin at 2020-11-12T20:18:45-05:00 Remove incomplete comment - - - - - 3 changed files: - libraries/base/Data/Typeable/Internal.hs - testsuite/tests/pmcheck/should_compile/T18249.hs - testsuite/tests/rts/T8308/T8308.stdout Changes: ===================================== libraries/base/Data/Typeable/Internal.hs ===================================== @@ -863,17 +863,7 @@ splitApps = go [] -- even worse! We have to construct several different TyCons by hand -- so that we can build the fingerprint for TYPE ('BoxedRep 'LiftedRep). -- If we call `typeRep @('BoxedRep 'LiftedRep)` while trying to compute --- the fingerprint of `TYPE ('BoxedRep 'LiftedRep)`, we get a loop since --- that invocacion of `typeRep` leads to: --- --- * fpTYPELiftedRep (starting point) --- * typeRep @('BoxedRep 'LiftedRep) --- * mkTrApp (applied to 'BoxedRep and 'LiftedRep, attempts TYPE shortcut) --- * eqTypeRep (second argument is trTYPE, let's pursue this) --- * sameTypeRep (second argument is trTYPE) --- * typeRepFingerprint (argument is trTYPE, matches TrFun case) --- * Dang, I have to think about this more tomorrow. The --- loop is real, but it evades me right now. +-- the fingerprint of `TYPE ('BoxedRep 'LiftedRep)`, we get a loop. -- -- The ticket to find a better way to deal with this is -- #14480. ===================================== testsuite/tests/pmcheck/should_compile/T18249.hs ===================================== @@ -14,7 +14,7 @@ f :: Int# -> Int f !_ | False = 1 f _ = 2 -newtype UVoid :: TYPE 'UnliftedRep where +newtype UVoid :: TYPE ('BoxedRep 'Unlifted) where UVoid :: UVoid -> UVoid g :: UVoid -> Int ===================================== testsuite/tests/rts/T8308/T8308.stdout ===================================== @@ -1 +1 @@ -7 +1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa16578b606480c7782c6bcb0845bae93840d376...39caf4f1edde204edd323596ba2b2b2890dce093 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa16578b606480c7782c6bcb0845bae93840d376...39caf4f1edde204edd323596ba2b2b2890dce093 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 Fri Nov 13 14:38:21 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 09:38:21 -0500 Subject: [Git][ghc/ghc][wip/T18043] rts: Flush eventlog buffers from flushEventLog Message-ID: <5fae9a5d21681_43133fa68e4a49ac4094e1@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18043 at Glasgow Haskell Compiler / GHC Commits: c0909c9a by Ben Gamari at 2020-11-13T09:38:10-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 11 changed files: - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -17,7 +17,6 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" -#include "rts/EventLogWriter.h" /* * Running the scheduler @@ -58,6 +57,9 @@ typedef struct CapabilityPublic_ { StgRegTable r; } CapabilityPublic; +/* N.B. this needs the Capability declaration above. */ +#include "rts/EventLogWriter.h" + /* ---------------------------------------------------------------------------- RTS configuration settings, for passing to hs_init_ghc() ------------------------------------------------------------------------- */ ===================================== includes/rts/EventLogWriter.h ===================================== @@ -68,3 +68,8 @@ bool startEventLogging(const EventLogWriter *writer); * Stop event logging and destroy the current EventLogWriter. */ void endEventLogging(void); + +/* + * Flush the eventlog. cap can be NULL if one is not held. + */ +void flushEventLog(Capability **cap); ===================================== libraries/base/Debug/Trace.hs ===================================== @@ -37,6 +37,7 @@ module Debug.Trace ( -- $eventlog_tracing traceEvent, traceEventIO, + flushEventLog, -- * Execution phase markers -- $markers @@ -319,3 +320,11 @@ traceMarkerIO :: String -> IO () traceMarkerIO msg = GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> case traceMarker# p s of s' -> (# s', () #) + +-- | Immediately flush the event log, if enabled. +-- +-- @since 4.15.0.0 +flushEventLog :: IO () +flushEventLog = c_flushEventLog nullPtr + +foreign import ccall "flushEventLog" c_flushEventLog :: Ptr () -> IO () ===================================== rts/Capability.c ===================================== @@ -23,6 +23,7 @@ #include "Schedule.h" #include "Sparks.h" #include "Trace.h" +#include "eventlog/EventLog.h" // for flushLocalEventsBuf #include "sm/GC.h" // for gcWorkerThread() #include "STM.h" #include "RtsUtils.h" @@ -982,6 +983,10 @@ yieldCapability debugTrace(DEBUG_nonmoving_gc, "Flushing update remembered set blocks..."); break; + case SYNC_FLUSH_EVENT_LOG: + flushLocalEventsBuf(cap); + break; + default: break; } ===================================== rts/Capability.h ===================================== @@ -267,7 +267,8 @@ typedef enum { SYNC_OTHER, SYNC_GC_SEQ, SYNC_GC_PAR, - SYNC_FLUSH_UPD_REM_SET + SYNC_FLUSH_UPD_REM_SET, + SYNC_FLUSH_EVENT_LOG } SyncType; // ===================================== rts/RtsSymbols.c ===================================== @@ -594,6 +594,7 @@ SymI_HasProto(__word_encodeFloat) \ SymI_HasProto(stg_atomicallyzh) \ SymI_HasProto(barf) \ + SymI_HasProto(flushEventLog) \ SymI_HasProto(deRefStablePtr) \ SymI_HasProto(debugBelch) \ SymI_HasProto(errorBelch) \ ===================================== rts/Schedule.c ===================================== @@ -2070,7 +2070,7 @@ forkProcess(HsStablePtr *entry stopTimer(); // See #4074 #if defined(TRACING) - flushEventLog(); // so that child won't inherit dirty file buffers + flushAllCapsEventsBufs(); // so that child won't inherit dirty file buffers #endif pid = fork(); ===================================== rts/Trace.c ===================================== @@ -118,10 +118,10 @@ void resetTracing (void) restartEventLogging(); } -void flushTrace (void) +void flushTrace () { if (eventlog_enabled) { - flushEventLog(); + flushEventLog(NULL); } } ===================================== rts/Trace.h ===================================== @@ -319,7 +319,6 @@ void traceConcSweepEnd(void); void traceConcUpdRemSetFlush(Capability *cap); void traceNonmovingHeapCensus(uint32_t log_blk_size, const struct NonmovingAllocCensus *census); - void flushTrace(void); #else /* !TRACING */ ===================================== rts/eventlog/EventLog.c ===================================== @@ -16,6 +16,7 @@ #include "RtsUtils.h" #include "Stats.h" #include "EventLog.h" +#include "Schedule.h" #include #include @@ -270,8 +271,8 @@ stopEventLogWriter(void) } } -void -flushEventLog(void) +static void +flushEventLogWriter(void) { if (event_log_writer != NULL && event_log_writer->flushEventLog != NULL) { @@ -1484,7 +1485,7 @@ void printAndClearEventBuf (EventsBuf *ebuf) "printAndClearEventLog: could not flush event log\n" ); resetEventsBuf(ebuf); - flushEventLog(); + flushEventLogWriter(); return; } @@ -1566,6 +1567,40 @@ void postEventType(EventsBuf *eb, EventType *et) postInt32(eb, EVENT_ET_END); } +void flushLocalEventsBuf(Capability *cap) +{ + EventsBuf *eb = &capEventBuf[cap->no]; + printAndClearEventBuf(eb); +} + +// Flush all capabilities' event buffers when we already hold all capabilities. +// Used during forkProcess. +void flushAllCapsEventsBufs() +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + + for (unsigned int i=0; i < n_capabilities; i++) { + flushLocalEventsBuf(capabilities[i]); + } + flushEventLogWriter(); +} + +void flushEventLog(Capability **cap USED_IF_THREADS) +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + +#if defined(THREADED_RTS) + Task *task = getMyTask(); + stopAllCapabilitiesWith(cap, task, SYNC_FLUSH_EVENT_LOG); + releaseAllCapabilities(n_capabilities, cap ? *cap : NULL, task); +#endif + flushEventLogWriter(); +} + #else enum EventLogStatus eventLogStatus(void) @@ -1579,4 +1614,6 @@ bool startEventLogging(const EventLogWriter *writer STG_UNUSED) { void endEventLogging(void) {} +void flushEventLog(Capability **cap STG_UNUSED) {} + #endif /* TRACING */ ===================================== rts/eventlog/EventLog.h ===================================== @@ -28,8 +28,10 @@ void initEventLogging(void); void restartEventLogging(void); void freeEventLogging(void); void abortEventLogging(void); // #4512 - after fork child needs to abort -void flushEventLog(void); // event log inherited from parent void moreCapEventBufs (uint32_t from, uint32_t to); +void flushLocalEventsBuf(Capability *cap); +void flushAllCapsEventsBufs(void); +void flushAllEventsBufs(Capability *cap); /* * Post a scheduler event to the capability's event buffer (an event @@ -175,6 +177,9 @@ void postNonmovingHeapCensus(int log_blk_size, #else /* !TRACING */ +INLINE_HEADER void flushLocalEventsBuf(Capability *cap STG_UNUSED) +{ /* nothing */ } + INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, EventTypeNum tag STG_UNUSED, StgThreadID id STG_UNUSED, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c0909c9a8242aa2928ccf59c207c9315aaec8a3f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c0909c9a8242aa2928ccf59c207c9315aaec8a3f 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 Fri Nov 13 15:16:37 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 10:16:37 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-eventlog Message-ID: <5faea3552e01b_43133fa68e9ac1d4415461@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/ghc-eventlog at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-eventlog 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 Fri Nov 13 16:08:24 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Fri, 13 Nov 2020 11:08:24 -0500 Subject: [Git][ghc/ghc][wip/T18939] 2 commits: Name (tc)SplitForAll- functions more consistently Message-ID: <5faeaf789d22_43133fa699c540ac42408b@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18939 at Glasgow Haskell Compiler / GHC Commits: 2987366d by Ryan Scott at 2020-11-13T10:22:34-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 796c146f by Ryan Scott at 2020-11-13T10:56:27-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. Fixes #18939. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Validity.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9a63c8312918c5d2902836abe4e605da135a2a2d...796c146f07bb21ca04e60815e4911568e0f949cb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9a63c8312918c5d2902836abe4e605da135a2a2d...796c146f07bb21ca04e60815e4911568e0f949cb 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 Fri Nov 13 16:16:05 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Fri, 13 Nov 2020 11:16:05 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 2 commits: Revisit [Prevent unification with type families] Message-ID: <5faeb14588684_43133fa6a88f31244280ad@gitlab.haskell.org.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: f235a943 by Richard Eisenberg at 2020-11-12T17:29:20-05:00 Revisit [Prevent unification with type families] - - - - - 7d26bf41 by Richard Eisenberg at 2020-11-13T11:15:53-05:00 Don't flatten during instance lookup - - - - - 3 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -41,7 +41,6 @@ import GHC.Unit.Types import GHC.Core.Class import GHC.Types.Var import GHC.Types.Var.Set -import GHC.Types.Var.Env import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.Unique (getUnique) @@ -836,13 +835,10 @@ lookupInstEnv' ie vis_mods cls tys -- Unification will break badly if the variables overlap -- They shouldn't because we allocate separate uniques for them -- See Note [Template tyvars are fresh] - let in_scope = mkInScopeSet (tpl_tv_set `unionVarSet` tys_tv_set) - flattened_tys = flattenTys in_scope tys in - -- NB: important to flatten here. Otherwise, it looks like - -- instance C Int cannot match a target [W] C (F Bool). - -- See Note [Flattening type-family applications when matching instances] - -- in GHC.Core.Unify. - case tcUnifyTysFG instanceBindFun tpl_tys flattened_tys of + case tcUnifyTysFG instanceBindFun tpl_tys tys of + -- We consider MaybeApart to be a case where the instance might + -- apply in the future. This covers an instance like C Int and + -- a target like [W] C (F a), where F is a type family. SurelyApart -> find ms us rest _ -> find ms (item:us) rest where ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -1015,7 +1015,8 @@ can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1 _ ty2 _ | Just (tc1, tys1) <- tcSplitTyConApp_maybe ty1 , Just (tc2, tys2) <- tcSplitTyConApp_maybe ty2 -- we want to catch e.g. Maybe Int ~ (Int -> Int) here for better - -- error messages; hence no direct match on TyConApp + -- error messages rather than decomposing into AppTys; + -- hence no direct match on TyConApp , not (isTypeFamilyTyCon tc1) , not (isTypeFamilyTyCon tc2) = canTyConApp ev eq_rel tc1 tys1 tc2 tys2 ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -1434,7 +1434,7 @@ uUnfilledVar2 origin t_or_k swapped tv1 ty2 where go dflags cur_lvl | canSolveByUnification cur_lvl tv1 ty2 - -- See Note [Prevent unification with type families] about the False: + -- See Note [Prevent unification with type families] about the NoTypeFamilies: , MTVU_OK ty2' <- metaTyVarUpdateOK dflags NoTypeFamilies tv1 ty2 = do { co_k <- uType KindLevel kind_origin (tcTypeKind ty2') (tyVarKind tv1) ; traceTc "uUnfilledVar2 ok" $ @@ -1677,6 +1677,9 @@ It would be lovely in the future to revisit this problem and remove this extra, unnecessary check. But we retain it for now as it seems to work better in practice. +Revisited in Nov '20, along with removing flattening variables. Problem +is still present, and the solution (NoTypeFamilies) is still the same. + Note [Refactoring hazard: metaTyVarUpdateOK] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ I (Richard E.) have a sad story about refactoring this code, retained here View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b4d386cc779db18e9fdb266cf76bff341fb126a...7d26bf41f46bbbe9f1479fdb970d171f2f867326 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b4d386cc779db18e9fdb266cf76bff341fb126a...7d26bf41f46bbbe9f1479fdb970d171f2f867326 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 Fri Nov 13 16:17:36 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 11:17:36 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/timings-allocations Message-ID: <5faeb1a0ba37f_43133fa698ea5d484290e5@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/timings-allocations at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/timings-allocations 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 Fri Nov 13 17:31:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 12:31:38 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Optimise nullary type constructor usage Message-ID: <5faec2fa11af9_4313f0251ac452189@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 041b16b2 by Ben Gamari at 2020-11-13T12:31:24-05:00 Optimise nullary type constructor usage During the compilation of programs GHC very frequently deals with the `Type` type, which is a synonym of `TYPE 'LiftedRep`. This patch teaches GHC to avoid expanding the `Type` synonym (and other nullary type synonyms) during type comparisons, saving a good amount of work. This optimisation is described in `Note [Comparing nullary type synonyms]`. To maximize the impact of this optimisation, we introduce a few special-cases to reduce `TYPE 'LiftedRep` to `Type`. See `Note [Prefer Type over TYPE 'LiftedPtrRep]`. Closes #17958. Metric Decrease: T18698b T1969 T12227 T12545 T12707 T14683 T3064 T5631 T5642 T9020 T9872a T13035 haddock.Cabal haddock.base - - - - - 22 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - + compiler/GHC/Builtin/Types/Prim.hs-boot - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/printer/T18052a.stderr - testsuite/tests/simplCore/should_compile/T13143.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -170,6 +170,7 @@ import GHC.Types.Var (VarBndr (Bndr)) import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE, mAX_SUM_SIZE ) import GHC.Unit.Module ( Module ) import GHC.Core.Type +import qualified GHC.Core.TyCo.Rep as TyCoRep (Type(TyConApp)) import GHC.Types.RepType import GHC.Core.DataCon import GHC.Core.ConLike @@ -691,7 +692,7 @@ constraintKindTyCon :: TyCon constraintKindTyCon = pcTyCon constraintKindTyConName Nothing [] [] liftedTypeKind, typeToTypeKind, constraintKind :: Kind -liftedTypeKind = tYPE liftedRepTy +liftedTypeKind = TyCoRep.TyConApp liftedTypeKindTyCon [] typeToTypeKind = liftedTypeKind `mkVisFunTyMany` liftedTypeKind constraintKind = mkTyConApp constraintKindTyCon [] @@ -1415,8 +1416,8 @@ runtimeRepTy = mkTyConTy runtimeRepTyCon -- type Type = tYPE 'LiftedRep liftedTypeKindTyCon :: TyCon liftedTypeKindTyCon = buildSynTyCon liftedTypeKindTyConName - [] liftedTypeKind [] - (tYPE liftedRepTy) + [] liftedTypeKind [] rhs + where rhs = TyCoRep.TyConApp tYPETyCon [liftedRepTy] runtimeRepTyCon :: TyCon runtimeRepTyCon = pcTyCon runtimeRepTyConName Nothing [] ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -551,10 +551,6 @@ mkPrimTcName built_in_syntax occ key tycon = mkWiredInName gHC_PRIM (mkTcOccFS occ) key (mkATyCon tycon) built_in_syntax ----------------------------- --- | Given a RuntimeRep, applies TYPE to it. --- see Note [TYPE and RuntimeRep] -tYPE :: Type -> Type -tYPE rr = TyConApp tYPETyCon [rr] -- Given a Multiplicity, applies FUN to it. functionWithMultiplicity :: Type -> Type ===================================== compiler/GHC/Builtin/Types/Prim.hs-boot ===================================== @@ -0,0 +1,5 @@ +module GHC.Builtin.Types.Prim where + +import GHC.Core.TyCon + +tYPETyCon :: TyCon ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -52,6 +52,7 @@ module GHC.Core.TyCo.Rep ( mkVisFunTyMany, mkVisFunTysMany, mkInvisFunTyMany, mkInvisFunTysMany, mkTyConApp, + tYPE, -- * Functions over binders TyCoBinder(..), TyCoVarBinder, TyBinder, @@ -90,8 +91,9 @@ import GHC.Core.TyCon import GHC.Core.Coercion.Axiom -- others -import GHC.Builtin.Names ( liftedTypeKindTyConKey, manyDataConKey ) -import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, manyDataConTy ) +import GHC.Builtin.Names ( liftedTypeKindTyConKey, liftedRepDataConKey, manyDataConKey, tYPETyConKey ) +import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, liftedTypeKind, manyDataConTy ) +import {-# SOURCE #-} GHC.Builtin.Types.Prim ( tYPETyCon ) import GHC.Types.Basic ( LeftOrRight(..), pickLR ) import GHC.Types.Unique ( hasKey ) import GHC.Utils.Outputable @@ -1018,12 +1020,64 @@ mkTyConApp tycon tys -- avoid reboxing every time `mkTyConApp` is called. = ASSERT2( null tys, ppr tycon $$ ppr tys ) manyDataConTy + -- See Note [Prefer Type over TYPE 'LiftedRep]. + | tycon `hasKey` tYPETyConKey + , [rep] <- tys + = tYPE rep + -- The catch-all case | otherwise = TyConApp tycon tys +{- +Note [Prefer Type over TYPE 'LiftedRep] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The Core of nearly any program will have numerous occurrences of + at TYPE 'LiftedRep@ floating about. Consequently, we try hard to ensure +that operations on such types are efficient. Specifically, we strive to + + a. Avoid heap allocation of such types + b. Use a small (shallow in the tree-depth sense) representation + for such types + +Goal (b) is particularly useful as it makes traversals (e.g. free variable +traversal, substitution, and comparison) more efficient. +Comparison in particular takes special advantage of nullary type synonym +applications, Note [Comparing nullary type synonyms] in "GHC.Core.Type". + +To accomplish these we use a number of tricks: + + * Instead of representing the lifted kind as + @TyConApp tYPETyCon [liftedRepDataCon]@ we rather prefer to + use the 'GHC.Types.Type' type synonym. This serves goal (b) + since there are no applied type arguments to traverse, e.g., during + comparison. + + * We have a top-level binding to represent `TyConApp GHC.Types.Type []` + (namely 'GHC.Builtin.Types.Prim.liftedTypeKind'), ensuring that we + don't need to allocate such types (goal (a)). + + * To avoid allocating 'TyConApp' constructors + 'GHC.Builtin.Types.Prim.tYPE' catches the lifted case and returns + `liftedTypeKind` instead of building an application (goal (a)). + + * Similarly, 'Type.mkTyConApp' catches applications of `TYPE` and + handles them using 'GHC.Builtin.Types.Prim.tYPE', ensuring + that it benefits from the optimisation described above (goal (a)). + +See #17958. +-} + +-- | Given a RuntimeRep, applies TYPE to it. +-- See Note [TYPE and RuntimeRep] in GHC.Builtin.Types.Prim. +tYPE :: Type -> Type +tYPE (TyConApp tc []) + -- See Note [Prefer Type of TYPE 'LiftedRep] + | tc `hasKey` liftedRepDataConKey = liftedTypeKind -- TYPE 'LiftedRep +tYPE rr = TyConApp tYPETyCon [rr] + -- This is a single, global definition of the type `Type` -- Defined here so it is only allocated once. --- See Note [mkTyConApp and Type] +-- See Note [mkTyConApp and Type] in this module. liftedTypeKindTyConApp :: Type liftedTypeKindTyConApp = TyConApp liftedTypeKindTyCon [] ===================================== compiler/GHC/Core/TyCo/Subst.hs ===================================== @@ -424,6 +424,7 @@ zipTCvSubst tcvs tys -- | Generates the in-scope set for the 'TCvSubst' from the types in the -- incoming environment. No CoVars, please! mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst +mkTvSubstPrs [] = emptyTCvSubst mkTvSubstPrs prs = ASSERT2( onlyTyVarsAndNoCoercionTy, text "prs" <+> ppr prs ) mkTvSubst in_scope tenv ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2310,12 +2310,14 @@ expandSynTyCon_maybe -- ^ Expand a type synonym application, if any expandSynTyCon_maybe tc tys | SynonymTyCon { tyConTyVars = tvs, synTcRhs = rhs, tyConArity = arity } <- tc - = case tys `listLengthCmp` arity of - GT -> Just (tvs `zip` tys, rhs, drop arity tys) - EQ -> Just (tvs `zip` tys, rhs, []) - LT -> Nothing - | otherwise - = Nothing + = case tys of + [] -> Just ([], rhs, []) -- Avoid a bit of work in the case of nullary synonyms + _ -> case tys `listLengthCmp` arity of + GT -> Just (tvs `zip` tys, rhs, drop arity tys) + EQ -> Just (tvs `zip` tys, rhs, []) + LT -> Nothing + | otherwise + = Nothing ---------------- ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -382,15 +382,16 @@ how roles in kinds might work out. -} -- | Gives the typechecker view of a type. This unwraps synonyms but --- leaves 'Constraint' alone. c.f. coreView, which turns Constraint into --- TYPE LiftedRep. Returns Nothing if no unwrapping happens. +-- leaves 'Constraint' alone. c.f. 'coreView', which turns 'Constraint' into +-- @TYPE LiftedRep at . Returns 'Nothing' if no unwrapping happens. -- See also Note [coreView vs tcView] {-# INLINE tcView #-} tcView :: Type -> Maybe Type -tcView (TyConApp tc tys) | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') +tcView (TyConApp tc tys) + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- The free vars of 'rhs' should all be bound by 'tenv', so it's - -- ok to use 'substTy' here. + -- ok to use 'substTy' here (which is what expandSynTyConApp_maybe does). -- See also Note [The substitution invariant] in GHC.Core.TyCo.Subst. -- Its important to use mkAppTys, rather than (foldl AppTy), -- because the function part might well return a @@ -399,17 +400,16 @@ tcView _ = Nothing {-# INLINE coreView #-} coreView :: Type -> Maybe Type --- ^ This function Strips off the /top layer only/ of a type synonym +-- ^ This function strips off the /top layer only/ of a type synonym -- application (if any) its underlying representation type. --- Returns Nothing if there is nothing to look through. +-- Returns 'Nothing' if there is nothing to look through. -- This function considers 'Constraint' to be a synonym of @TYPE LiftedRep at . -- -- By being non-recursive and inlined, this case analysis gets efficiently -- joined onto the case analysis that the caller is already doing coreView ty@(TyConApp tc tys) - | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') - -- This equation is exactly like tcView + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- At the Core level, Constraint = Type -- See Note [coreView vs tcView] @@ -419,6 +419,30 @@ coreView ty@(TyConApp tc tys) coreView _ = Nothing +----------------------------------------------- +expandSynTyConApp_maybe :: TyCon -> [Type] -> Maybe Type +expandSynTyConApp_maybe tc tys + | Just (tvs, rhs) <- synTyConDefn_maybe tc + , n_tys <= arity + = Just (expand_syn arity tvs rhs n_tys tys) + | otherwise + = Nothing + where + n_tys = length tys + arity = tyConArity tc +-- Without this INLINE the call to expandSynTyConApp_maybe in coreView +-- will result in an avoidable allocation. +{-# INLINE expandSynTyConApp_maybe #-} + +-- | A helper for 'expandSynTyConApp_maybe' to avoid inlining this cold path +-- into call-sites. +expand_syn :: Int -> [TyVar] -> Type -> Int -> [Type] -> Type +expand_syn arity tvs rhs n_tys tys + | n_tys > arity = mkAppTys rhs' (drop arity tys) + | otherwise = rhs' + where + rhs' = substTy (mkTvSubstPrs (tvs `zip` tys)) rhs + {-# INLINE coreFullView #-} coreFullView :: Type -> Type -- ^ Iterates 'coreView' until there is no more to synonym to expand. @@ -2194,6 +2218,36 @@ But the left is an AppTy while the right is a TyConApp. The solution is to use repSplitAppTy_maybe to break up the TyConApp into its pieces and then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * TcCanonical.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See [Prefer Type over TYPE 'LiftedRep] in +GHC.Core.TyCo.Rep for details. + -} eqType :: Type -> Type -> Bool @@ -2305,6 +2359,10 @@ nonDetCmpTypeX env orig_t1 orig_t2 = -- Returns both the resulting ordering relation between the two types -- and whether either contains a cast. go :: RnEnv2 -> Type -> Type -> TypeOrdering + -- See Note [Comparing nullary type synonyms]. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = TEQ go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 | Just t2' <- coreView t2 = go env t1 t2' ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -957,7 +957,12 @@ unify_ty :: UMEnv -- Respects newtypes, PredTypes unify_ty env ty1 ty2 kco - -- Use tcView, not coreView. See Note [coreView vs tcView] in GHC.Core.Type. + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + | TyConApp tc1 [] <- ty1 + , TyConApp tc2 [] <- ty2 + , tc1 == tc2 = return () + + -- TODO: More commentary needed here | Just ty1' <- tcView ty1 = unify_ty env ty1' ty2 kco | Just ty2' <- tcView ty2 = unify_ty env ty1 ty2' kco | CastTy ty1' co <- ty1 = if um_unif env ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -961,6 +961,11 @@ can_eq_nc' -> Type -> Type -- RHS, after and before type-synonym expansion, resp -> TcS (StopOrContinue Ct) +-- See Note [Comparing nullary type synonyms] in GHC.Core.Type. +can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1@(TyConApp tc1 []) _ps_ty1 (TyConApp tc2 []) _ps_ty2 + | tc1 == tc2 + = canEqReflexive ev eq_rel ty1 + -- Expand synonyms first; see Note [Type synonyms and canonicalization] can_eq_nc' flat rdr_env envs ev eq_rel ty1 ps_ty1 ty2 ps_ty2 | Just ty1' <- tcView ty1 = can_eq_nc' flat rdr_env envs ev eq_rel ty1' ps_ty1 ty2 ps_ty2 ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -120,7 +120,6 @@ import GHC.Types.Id as Id import GHC.Types.Name import GHC.Types.Var.Set import GHC.Builtin.Types -import GHC.Builtin.Types.Prim import GHC.Types.Var.Env import GHC.Types.Name.Env import GHC.Utils.Misc ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -1545,6 +1545,11 @@ tc_eq_type keep_syns vis_only orig_ty1 orig_ty2 = go orig_env orig_ty1 orig_ty2 where go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = True + go env t1 t2 | not keep_syns, Just t1' <- tcView t1 = go env t1' t2 go env t1 t2 | not keep_syns, Just t2' <- tcView t2 = go env t1 t2' ===================================== testsuite/tests/deSugar/should_compile/T2431.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 63, types: 43, coercions: 1, joins: 0/0} + = {terms: 63, types: 39, coercions: 1, joins: 0/0} --- RHS size: {terms: 2, types: 4, coercions: 1, joins: 0/0} +-- RHS size: {terms: 2, types: 3, coercions: 1, joins: 0/0} T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a [GblId[DataConWrapper], Caf=NoCafRefs, @@ -15,7 +15,7 @@ T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a T2431.$WRefl = \ (@a) -> T2431.Refl @a @a @~(_N :: a GHC.Prim.~# a) --- RHS size: {terms: 4, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 7, coercions: 0, joins: 0/0} absurd :: forall a. (Int :~: Bool) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] absurd = \ (@a) (x :: Int :~: Bool) -> case x of { } ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -16,13 +16,12 @@ Derived class instances: = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(T14578.Wat f g a -> T14578.Wat f g a -> T14578.Wat f g a) ((GHC.Base.<>) @(T14578.App (Data.Functor.Compose.Compose f g) a)) GHC.Base.sconcat = GHC.Prim.coerce - @(GHC.Base.NonEmpty - (T14578.App (Data.Functor.Compose.Compose f g) a) + @(GHC.Base.NonEmpty (T14578.App (Data.Functor.Compose.Compose f g) a) -> T14578.App (Data.Functor.Compose.Compose f g) a) @(GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a) (GHC.Base.sconcat @@ -31,7 +30,7 @@ Derived class instances: = GHC.Prim.coerce @(b -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(b -> T14578.Wat f g a -> T14578.Wat f g a) (GHC.Base.stimes @(T14578.App (Data.Functor.Compose.Compose f g) a)) ===================================== testsuite/tests/plugins/plugins09.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/plugins10.stdout ===================================== @@ -6,7 +6,6 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: Language.Haskell.TH.Syntax typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat parsePlugin(a) ===================================== testsuite/tests/plugins/plugins11.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/static-plugins.stdout ===================================== @@ -5,11 +5,11 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: System.IO typeCheckPlugin (rn) -interfacePlugin: GHC.Prim -interfacePlugin: GHC.Show interfacePlugin: GHC.Types +interfacePlugin: GHC.Show interfacePlugin: GHC.TopHandler typeCheckPlugin (tc) +interfacePlugin: GHC.Prim interfacePlugin: GHC.CString interfacePlugin: GHC.Num.BigNat ==pure.1 ===================================== testsuite/tests/printer/T18052a.stderr ===================================== @@ -10,9 +10,9 @@ Dependent packages: [base-4.16.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 24, types: 61, coercions: 0, joins: 0/0} + = {terms: 24, types: 52, coercions: 0, joins: 0/0} --- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} T18052a.$b:||: :: forall {a} {b}. a -> b -> (a, b) [GblId, Arity=2, Unf=OtherCon []] T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) @@ -22,7 +22,7 @@ T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) [GblId] (+++) = ++ --- RHS size: {terms: 13, types: 20, coercions: 0, joins: 0/0} +-- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/0} T18052a.$m:||: :: forall {rep :: GHC.Types.RuntimeRep} {r :: TYPE rep} {a} {b}. (a, b) -> (a -> b -> r) -> ((# #) -> r) -> r ===================================== testsuite/tests/simplCore/should_compile/T13143.stderr ===================================== @@ -1,17 +1,17 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 71, types: 44, coercions: 0, joins: 0/0} + = {terms: 71, types: 40, coercions: 0, joins: 0/0} Rec { --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} T13143.$wf [InlPrag=NOINLINE, Occ=LoopBreaker] :: forall {a}. (# #) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] T13143.$wf = \ (@a) _ [Occ=Dead] -> T13143.$wf @a GHC.Prim.(##) end Rec } --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} f [InlPrag=[final]] :: forall a. Int -> a [GblId, Arity=1, ===================================== testsuite/tests/simplCore/should_compile/T18013.stderr ===================================== @@ -129,9 +129,9 @@ Rule fired: Class op fmap (BUILTIN) ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 52, types: 106, coercions: 17, joins: 0/1} + = {terms: 52, types: 101, coercions: 17, joins: 0/1} --- RHS size: {terms: 37, types: 87, coercions: 17, joins: 0/1} +-- RHS size: {terms: 37, types: 84, coercions: 17, joins: 0/1} mapMaybeRule :: forall a b. Rule IO a b -> Rule IO (Maybe a) (Maybe b) [GblId, ===================================== testsuite/tests/simplCore/should_compile/T7360.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 106, types: 47, coercions: 0, joins: 0/0} + = {terms: 106, types: 45, 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 @@ -31,7 +31,7 @@ T7360.fun4 :: () WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 20 0}] T7360.fun4 = fun1 T7360.Foo1 --- RHS size: {terms: 11, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 11, types: 7, coercions: 0, joins: 0/0} fun2 :: forall {a}. [a] -> ((), Int) [GblId, Arity=1, ===================================== testsuite/tests/typecheck/should_compile/T13032.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Desugar (after optimization) ==================== Result size of Desugar (after optimization) - = {terms: 13, types: 24, coercions: 0, joins: 0/0} + = {terms: 13, types: 18, coercions: 0, joins: 0/0} --- RHS size: {terms: 6, types: 11, coercions: 0, joins: 0/0} +-- RHS size: {terms: 6, types: 8, coercions: 0, joins: 0/0} f :: forall a b. (a ~ b) => a -> b -> Bool [LclIdX, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/041b16b2f64ad96335eda5bd8b1ba6acd329371b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/041b16b2f64ad96335eda5bd8b1ba6acd329371b 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 Fri Nov 13 18:40:46 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Fri, 13 Nov 2020 13:40:46 -0500 Subject: [Git][ghc/ghc][wip/T18939] Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places Message-ID: <5faed32eaf99c_43133fa6a93dfd804576c@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18939 at Glasgow Haskell Compiler / GHC Commits: e5dabf55 by Ryan Scott at 2020-11-13T13:40:02-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 15 changed files: - compiler/GHC/Core/Type.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Validity.hs - + testsuite/tests/typecheck/should_compile/T18939_Compile.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/T18939_Fail.hs - + testsuite/tests/typecheck/should_fail/T18939_Fail.stderr - testsuite/tests/typecheck/should_fail/all.T - utils/haddock Changes: ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -76,7 +76,7 @@ module GHC.Core.Type ( coAxNthLHS, stripCoercionTy, - splitPiTysInvisible, splitPiTysInvisibleN, + splitInvisPiTys, splitInvisPiTysN, invisibleTyBndrCount, filterOutInvisibleTypes, filterOutInferredTypes, partitionInvisibleTypes, partitionInvisibles, @@ -1559,7 +1559,7 @@ splitForAllTyCoVars ty = split ty ty [] split orig_ty ty tvs | Just ty' <- coreView ty = split orig_ty ty' tvs split orig_ty _ tvs = (reverse tvs, orig_ty) --- | Splits the longest initial sequence of ForAllTys' that satisfy +-- | Splits the longest initial sequence of 'ForAllTy's that satisfy -- @argf_pred@, returning the binders transformed by @argf_pred@ splitSomeForAllTyCoVarBndrs :: (ArgFlag -> Maybe af) -> Type -> ([VarBndr TyCoVar af], Type) splitSomeForAllTyCoVarBndrs argf_pred ty = split ty ty [] @@ -1716,12 +1716,12 @@ invisibleTyBndrCount :: Type -> Int -- Includes invisible predicate arguments; e.g. for -- e.g. forall {k}. (k ~ *) => k -> k -- returns 2 not 1 -invisibleTyBndrCount ty = length (fst (splitPiTysInvisible ty)) +invisibleTyBndrCount ty = length (fst (splitInvisPiTys ty)) --- Like splitPiTys, but returns only *invisible* binders, including constraints --- Stops at the first visible binder -splitPiTysInvisible :: Type -> ([TyCoBinder], Type) -splitPiTysInvisible ty = split ty ty [] +-- | Like 'splitPiTys', but returns only *invisible* binders, including constraints. +-- Stops at the first visible binder. +splitInvisPiTys :: Type -> ([TyCoBinder], Type) +splitInvisPiTys ty = split ty ty [] where split _ (ForAllTy b res) bs | Bndr _ vis <- b @@ -1732,11 +1732,11 @@ splitPiTysInvisible ty = split ty ty [] | Just ty' <- coreView ty = split orig_ty ty' bs split orig_ty _ bs = (reverse bs, orig_ty) -splitPiTysInvisibleN :: Int -> Type -> ([TyCoBinder], Type) --- Same as splitPiTysInvisible, but stop when --- - you have found 'n' TyCoBinders, +splitInvisPiTysN :: Int -> Type -> ([TyCoBinder], Type) +-- ^ Same as 'splitInvisPiTys', but stop when +-- - you have found @n@ 'TyCoBinder's, -- - or you run out of invisible binders -splitPiTysInvisibleN n ty = split n ty ty [] +splitInvisPiTysN n ty = split n ty ty [] where split n orig_ty ty bs | n == 0 = (reverse bs, orig_ty) ===================================== compiler/GHC/HsToCore/Foreign/Decl.hs ===================================== @@ -316,7 +316,7 @@ dsPrimCall :: Id -> Coercion -> ForeignCall dsPrimCall fn_id co fcall = do let ty = coercionLKind co - (tvs, fun_ty) = tcSplitForAllTyVars ty + (tvs, fun_ty) = tcSplitForAllInvisTyVars ty (arg_tys, io_res_ty) = tcSplitFunTys fun_ty args <- newSysLocalsDs arg_tys -- no FFI levity-polymorphism @@ -489,7 +489,7 @@ dsFExportDynamic id co0 cconv = do where ty = coercionLKind co0 - (tvs,sans_foralls) = tcSplitForAllTyVars ty + (tvs,sans_foralls) = tcSplitForAllInvisTyVars ty ([Scaled arg_mult arg_ty], fn_res_ty) = tcSplitFunTys sans_foralls Just (io_tc, res_ty) = tcSplitIOType_maybe fn_res_ty -- Must have an IO type; hence Just ===================================== compiler/GHC/Runtime/Heap/Inspect.hs ===================================== @@ -1389,4 +1389,4 @@ quantifyType ty = ( filter isTyVar $ tyCoVarsOfTypeWellScoped rho , rho) where - (_tvs, rho) = tcSplitForAllTyVars ty + (_tvs, rho) = tcSplitForAllInvisTyVars ty ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2568,13 +2568,13 @@ kcCheckDeclHeader_sig kisig name flav split_invis :: Kind -> Maybe Kind -> ([TyCoBinder], Kind) split_invis sig_ki Nothing = -- instantiate all invisible binders - splitPiTysInvisible sig_ki + splitInvisPiTys sig_ki split_invis sig_ki (Just res_ki) = -- subtraction a la checkExpectedKind let n_res_invis_bndrs = invisibleTyBndrCount res_ki n_sig_invis_bndrs = invisibleTyBndrCount sig_ki n_inst = n_sig_invis_bndrs - n_res_invis_bndrs - in splitPiTysInvisibleN n_inst sig_ki + in splitInvisPiTysN n_inst sig_ki -- A quantifier from a kind signature zipped with a user-written binder for it. data ZippedBinder = ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -950,7 +950,7 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity tc_kind_sig (Just hs_kind) = do { sig_kind <- tcLHsKindSig data_ctxt hs_kind ; lvl <- getTcLevel - ; let (tvs, inner_kind) = tcSplitForAllTyVars sig_kind + ; let (tvs, inner_kind) = tcSplitForAllInvisTyVars sig_kind ; (subst, _tvs') <- tcInstSkolTyVarsAt lvl False emptyTCvSubst tvs -- Perhaps surprisingly, we don't need the skolemised tvs themselves ; return (substTy subst inner_kind) } ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -223,8 +223,8 @@ check_inst sig_inst = do skol_info = InstSkol -- Based off of tcSplitDFunTy (tvs, theta, pred) = - case tcSplitForAllTyVars ty of { (tvs, rho) -> - case splitFunTys rho of { (theta, pred) -> + case tcSplitForAllInvisTyVars ty of { (tvs, rho) -> + case splitFunTys rho of { (theta, pred) -> (tvs, theta, pred) }} origin = InstProvidedOrigin (tcg_semantic_mod tcg_env) sig_inst (skol_subst, tvs_skols) <- tcInstSkolTyVars tvs -- Skolemize ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -464,7 +464,7 @@ tcInstType inst_tyvars id subst' = extendTCvInScopeSet subst (tyCoVarsOfType rho) ; return (tv_prs, substTheta subst' theta, substTy subst' tau) } where - (tyvars, rho) = tcSplitForAllTyVars (idType id) + (tyvars, rho) = tcSplitForAllInvisTyVars (idType id) (theta, tau) = tcSplitPhiTy rho tcInstTypeBndrs :: Id -> TcM ([(Name, InvisTVBinder)], TcThetaType, TcType) ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -60,7 +60,7 @@ module GHC.Tc.Utils.TcType ( -- These are important because they do not look through newtypes getTyVar, tcSplitForAllTyVarBinder_maybe, - tcSplitForAllTyVars, tcSplitSomeForAllTyVars, + tcSplitForAllTyVars, tcSplitForAllInvisTyVars, tcSplitSomeForAllTyVars, tcSplitForAllReqTVBinders, tcSplitForAllInvisTVBinders, tcSplitPiTys, tcSplitPiTy_maybe, tcSplitForAllTyVarBinders, tcSplitPhiTy, tcSplitPredFunTy_maybe, @@ -1223,12 +1223,17 @@ tcSplitForAllTyVarBinder_maybe (ForAllTy tv ty) = ASSERT( isTyVarBinder tv ) Jus tcSplitForAllTyVarBinder_maybe _ = Nothing -- | Like 'tcSplitPiTys', but splits off only named binders, --- returning just the tycovars. +-- returning just the tyvars. tcSplitForAllTyVars :: Type -> ([TyVar], Type) tcSplitForAllTyVars ty = ASSERT( all isTyVar (fst sty) ) sty where sty = splitForAllTyCoVars ty +-- | Like 'tcSplitForAllTyVars', but only splits 'ForAllTy's with 'Invisible' +-- type variable binders. +tcSplitForAllInvisTyVars :: Type -> ([TyVar], Type) +tcSplitForAllInvisTyVars ty = tcSplitSomeForAllTyVars isInvisibleArgFlag ty + -- | Like 'tcSplitForAllTyVars', but only splits a 'ForAllTy' if @argf_pred argf@ -- is 'True', where @argf@ is the visibility of the @ForAllTy@'s binder and -- @argf_pred@ is a predicate over visibilities provided as an argument to this @@ -1284,9 +1289,11 @@ tcSplitPhiTy ty Just (pred, ty) -> split ty (pred:ts) Nothing -> (reverse ts, ty) --- | Split a sigma type into its parts. +-- | Split a sigma type into its parts. This only splits /invisible/ type +-- variable binders, as these are the only forms of binder that the typechecker +-- will implicitly instantiate. tcSplitSigmaTy :: Type -> ([TyVar], ThetaType, Type) -tcSplitSigmaTy ty = case tcSplitForAllTyVars ty of +tcSplitSigmaTy ty = case tcSplitForAllInvisTyVars ty of (tvs, rho) -> case tcSplitPhiTy rho of (theta, tau) -> (tvs, theta, tau) @@ -1469,9 +1476,9 @@ tcSplitDFunTy :: Type -> ([TyVar], [Type], Class, [Type]) -- the latter specifically stops at PredTy arguments, -- and we don't want to do that here tcSplitDFunTy ty - = case tcSplitForAllTyVars ty of { (tvs, rho) -> - case splitFunTys rho of { (theta, tau) -> - case tcSplitDFunHead tau of { (clas, tys) -> + = case tcSplitForAllInvisTyVars ty of { (tvs, rho) -> + case splitFunTys rho of { (theta, tau) -> + case tcSplitDFunHead tau of { (clas, tys) -> (tvs, map scaledThing theta, clas, tys) }}} tcSplitDFunHead :: Type -> (Class, [Type]) @@ -1489,7 +1496,7 @@ tcSplitMethodTy :: Type -> ([TyVar], PredType, Type) -- tcSplitMethodTy just peels off the outer forall and -- that first predicate tcSplitMethodTy ty - | (sel_tyvars,sel_rho) <- tcSplitForAllTyVars ty + | (sel_tyvars,sel_rho) <- tcSplitForAllInvisTyVars ty , Just (first_pred, local_meth_ty) <- tcSplitPredFunTy_maybe sel_rho = (sel_tyvars, first_pred, local_meth_ty) | otherwise ===================================== compiler/GHC/Tc/Validity.hs ===================================== @@ -924,7 +924,7 @@ forAllTyErr env rank ty , vcat [ hang herald 2 (ppr_tidy env ty) , suggestion ] ) where - (tvs, _theta, _tau) = tcSplitSigmaTy ty + (tvs, _rho) = tcSplitForAllTyVars ty herald | null tvs = text "Illegal qualified type:" | otherwise = text "Illegal polymorphic type:" suggestion = case rank of ===================================== testsuite/tests/typecheck/should_compile/T18939_Compile.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE StandaloneKindSignatures #-} +{-# LANGUAGE TypeFamilies #-} +module T18939_Compile where + +import Data.Kind + +data family Hm :: forall a -> a -> Type +data instance Hm :: forall a -> a -> Type ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -726,6 +726,7 @@ test('T18323', normal, compile, ['']) test('T18585', normal, compile, ['']) test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) +test('T18939_Compile', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) test('T17186', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T18939_Fail.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE PolyKinds #-} +module T18939_Fail where + +data F (f :: forall a -> a) ===================================== testsuite/tests/typecheck/should_fail/T18939_Fail.stderr ===================================== @@ -0,0 +1,5 @@ + +T18939_Fail.hs:5:1: error: + • Illegal polymorphic type: forall a -> a + Perhaps you intended to use RankNTypes + • In the data type declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -583,6 +583,7 @@ test('T18714', normal, compile_fail, ['']) test('T18723a', normal, compile_fail, ['']) test('T18723b', normal, compile_fail, ['']) test('T18723c', normal, compile_fail, ['']) +test('T18939_Fail', normal, compile_fail, ['']) test('too-many', normal, compile_fail, ['']) test('T18640a', normal, compile_fail, ['']) test('T18640b', normal, compile_fail, ['']) ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit ad9cbad7312a64e6757c32bd9488c55ba4f2fec9 +Subproject commit 4d0498d503bd51b7d7626497580232685a2691a1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e5dabf5534b55a340df10ed486fdb6afb054457d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e5dabf5534b55a340df10ed486fdb6afb054457d 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 Fri Nov 13 18:41:27 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 13 Nov 2020 13:41:27 -0500 Subject: [Git][ghc/ghc][wip/tyconapp-opts] Optimise nullary type constructor usage Message-ID: <5faed357a58cb_43133fa6ae2835b845818b@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/tyconapp-opts at Glasgow Haskell Compiler / GHC Commits: 334ca3f8 by Ben Gamari at 2020-11-13T13:41:19-05:00 Optimise nullary type constructor usage During the compilation of programs GHC very frequently deals with the `Type` type, which is a synonym of `TYPE 'LiftedRep`. This patch teaches GHC to avoid expanding the `Type` synonym (and other nullary type synonyms) during type comparisons, saving a good amount of work. This optimisation is described in `Note [Comparing nullary type synonyms]`. To maximize the impact of this optimisation, we introduce a few special-cases to reduce `TYPE 'LiftedRep` to `Type`. See `Note [Prefer Type over TYPE 'LiftedPtrRep]`. Closes #17958. Metric Decrease: T18698b T1969 T12227 T12545 T12707 T14683 T3064 T5631 T5642 T9020 T9872a T13035 haddock.Cabal haddock.base - - - - - 22 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - + compiler/GHC/Builtin/Types/Prim.hs-boot - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs - testsuite/tests/deSugar/should_compile/T2431.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - testsuite/tests/plugins/plugins09.stdout - testsuite/tests/plugins/plugins10.stdout - testsuite/tests/plugins/plugins11.stdout - testsuite/tests/plugins/static-plugins.stdout - testsuite/tests/printer/T18052a.stderr - testsuite/tests/simplCore/should_compile/T13143.stderr - testsuite/tests/simplCore/should_compile/T18013.stderr - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/typecheck/should_compile/T13032.stderr Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -170,6 +170,7 @@ import GHC.Types.Var (VarBndr (Bndr)) import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE, mAX_SUM_SIZE ) import GHC.Unit.Module ( Module ) import GHC.Core.Type +import qualified GHC.Core.TyCo.Rep as TyCoRep (Type(TyConApp)) import GHC.Types.RepType import GHC.Core.DataCon import GHC.Core.ConLike @@ -691,7 +692,7 @@ constraintKindTyCon :: TyCon constraintKindTyCon = pcTyCon constraintKindTyConName Nothing [] [] liftedTypeKind, typeToTypeKind, constraintKind :: Kind -liftedTypeKind = tYPE liftedRepTy +liftedTypeKind = TyCoRep.TyConApp liftedTypeKindTyCon [] typeToTypeKind = liftedTypeKind `mkVisFunTyMany` liftedTypeKind constraintKind = mkTyConApp constraintKindTyCon [] @@ -1415,8 +1416,8 @@ runtimeRepTy = mkTyConTy runtimeRepTyCon -- type Type = tYPE 'LiftedRep liftedTypeKindTyCon :: TyCon liftedTypeKindTyCon = buildSynTyCon liftedTypeKindTyConName - [] liftedTypeKind [] - (tYPE liftedRepTy) + [] liftedTypeKind [] rhs + where rhs = TyCoRep.TyConApp tYPETyCon [liftedRepTy] runtimeRepTyCon :: TyCon runtimeRepTyCon = pcTyCon runtimeRepTyConName Nothing [] ===================================== compiler/GHC/Builtin/Types/Prim.hs ===================================== @@ -551,10 +551,6 @@ mkPrimTcName built_in_syntax occ key tycon = mkWiredInName gHC_PRIM (mkTcOccFS occ) key (mkATyCon tycon) built_in_syntax ----------------------------- --- | Given a RuntimeRep, applies TYPE to it. --- see Note [TYPE and RuntimeRep] -tYPE :: Type -> Type -tYPE rr = TyConApp tYPETyCon [rr] -- Given a Multiplicity, applies FUN to it. functionWithMultiplicity :: Type -> Type ===================================== compiler/GHC/Builtin/Types/Prim.hs-boot ===================================== @@ -0,0 +1,5 @@ +module GHC.Builtin.Types.Prim where + +import GHC.Core.TyCon + +tYPETyCon :: TyCon ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -52,6 +52,7 @@ module GHC.Core.TyCo.Rep ( mkVisFunTyMany, mkVisFunTysMany, mkInvisFunTyMany, mkInvisFunTysMany, mkTyConApp, + tYPE, -- * Functions over binders TyCoBinder(..), TyCoVarBinder, TyBinder, @@ -90,8 +91,9 @@ import GHC.Core.TyCon import GHC.Core.Coercion.Axiom -- others -import GHC.Builtin.Names ( liftedTypeKindTyConKey, manyDataConKey ) -import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, manyDataConTy ) +import GHC.Builtin.Names ( liftedTypeKindTyConKey, liftedRepDataConKey, manyDataConKey, tYPETyConKey ) +import {-# SOURCE #-} GHC.Builtin.Types ( liftedTypeKindTyCon, liftedTypeKind, manyDataConTy ) +import {-# SOURCE #-} GHC.Builtin.Types.Prim ( tYPETyCon ) import GHC.Types.Basic ( LeftOrRight(..), pickLR ) import GHC.Types.Unique ( hasKey ) import GHC.Utils.Outputable @@ -1018,12 +1020,64 @@ mkTyConApp tycon tys -- avoid reboxing every time `mkTyConApp` is called. = ASSERT2( null tys, ppr tycon $$ ppr tys ) manyDataConTy + -- See Note [Prefer Type over TYPE 'LiftedRep]. + | tycon `hasKey` tYPETyConKey + , [rep] <- tys + = tYPE rep + -- The catch-all case | otherwise = TyConApp tycon tys +{- +Note [Prefer Type over TYPE 'LiftedRep] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The Core of nearly any program will have numerous occurrences of + at TYPE 'LiftedRep@ floating about. Consequently, we try hard to ensure +that operations on such types are efficient. Specifically, we strive to + + a. Avoid heap allocation of such types + b. Use a small (shallow in the tree-depth sense) representation + for such types + +Goal (b) is particularly useful as it makes traversals (e.g. free variable +traversal, substitution, and comparison) more efficient. +Comparison in particular takes special advantage of nullary type synonym +applications, Note [Comparing nullary type synonyms] in "GHC.Core.Type". + +To accomplish these we use a number of tricks: + + * Instead of representing the lifted kind as + @TyConApp tYPETyCon [liftedRepDataCon]@ we rather prefer to + use the 'GHC.Types.Type' type synonym. This serves goal (b) + since there are no applied type arguments to traverse, e.g., during + comparison. + + * We have a top-level binding to represent `TyConApp GHC.Types.Type []` + (namely 'GHC.Builtin.Types.Prim.liftedTypeKind'), ensuring that we + don't need to allocate such types (goal (a)). + + * To avoid allocating 'TyConApp' constructors + 'GHC.Builtin.Types.Prim.tYPE' catches the lifted case and returns + `liftedTypeKind` instead of building an application (goal (a)). + + * Similarly, 'Type.mkTyConApp' catches applications of `TYPE` and + handles them using 'GHC.Builtin.Types.Prim.tYPE', ensuring + that it benefits from the optimisation described above (goal (a)). + +See #17958. +-} + +-- | Given a RuntimeRep, applies TYPE to it. +-- See Note [TYPE and RuntimeRep] in GHC.Builtin.Types.Prim. +tYPE :: Type -> Type +tYPE (TyConApp tc []) + -- See Note [Prefer Type of TYPE 'LiftedRep] + | tc `hasKey` liftedRepDataConKey = liftedTypeKind -- TYPE 'LiftedRep +tYPE rr = TyConApp tYPETyCon [rr] + -- This is a single, global definition of the type `Type` -- Defined here so it is only allocated once. --- See Note [mkTyConApp and Type] +-- See Note [mkTyConApp and Type] in this module. liftedTypeKindTyConApp :: Type liftedTypeKindTyConApp = TyConApp liftedTypeKindTyCon [] ===================================== compiler/GHC/Core/TyCo/Subst.hs ===================================== @@ -424,6 +424,7 @@ zipTCvSubst tcvs tys -- | Generates the in-scope set for the 'TCvSubst' from the types in the -- incoming environment. No CoVars, please! mkTvSubstPrs :: [(TyVar, Type)] -> TCvSubst +mkTvSubstPrs [] = emptyTCvSubst mkTvSubstPrs prs = ASSERT2( onlyTyVarsAndNoCoercionTy, text "prs" <+> ppr prs ) mkTvSubst in_scope tenv ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -2310,12 +2310,14 @@ expandSynTyCon_maybe -- ^ Expand a type synonym application, if any expandSynTyCon_maybe tc tys | SynonymTyCon { tyConTyVars = tvs, synTcRhs = rhs, tyConArity = arity } <- tc - = case tys `listLengthCmp` arity of - GT -> Just (tvs `zip` tys, rhs, drop arity tys) - EQ -> Just (tvs `zip` tys, rhs, []) - LT -> Nothing - | otherwise - = Nothing + = case tys of + [] -> Just ([], rhs, []) -- Avoid a bit of work in the case of nullary synonyms + _ -> case tys `listLengthCmp` arity of + GT -> Just (tvs `zip` tys, rhs, drop arity tys) + EQ -> Just (tvs `zip` tys, rhs, []) + LT -> Nothing + | otherwise + = Nothing ---------------- ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -382,15 +382,16 @@ how roles in kinds might work out. -} -- | Gives the typechecker view of a type. This unwraps synonyms but --- leaves 'Constraint' alone. c.f. coreView, which turns Constraint into --- TYPE LiftedRep. Returns Nothing if no unwrapping happens. +-- leaves 'Constraint' alone. c.f. 'coreView', which turns 'Constraint' into +-- @TYPE LiftedRep at . Returns 'Nothing' if no unwrapping happens. -- See also Note [coreView vs tcView] {-# INLINE tcView #-} tcView :: Type -> Maybe Type -tcView (TyConApp tc tys) | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') +tcView (TyConApp tc tys) + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- The free vars of 'rhs' should all be bound by 'tenv', so it's - -- ok to use 'substTy' here. + -- ok to use 'substTy' here (which is what expandSynTyConApp_maybe does). -- See also Note [The substitution invariant] in GHC.Core.TyCo.Subst. -- Its important to use mkAppTys, rather than (foldl AppTy), -- because the function part might well return a @@ -399,17 +400,16 @@ tcView _ = Nothing {-# INLINE coreView #-} coreView :: Type -> Maybe Type --- ^ This function Strips off the /top layer only/ of a type synonym +-- ^ This function strips off the /top layer only/ of a type synonym -- application (if any) its underlying representation type. --- Returns Nothing if there is nothing to look through. +-- Returns 'Nothing' if there is nothing to look through. -- This function considers 'Constraint' to be a synonym of @TYPE LiftedRep at . -- -- By being non-recursive and inlined, this case analysis gets efficiently -- joined onto the case analysis that the caller is already doing coreView ty@(TyConApp tc tys) - | Just (tenv, rhs, tys') <- expandSynTyCon_maybe tc tys - = Just (mkAppTys (substTy (mkTvSubstPrs tenv) rhs) tys') - -- This equation is exactly like tcView + | res@(Just _) <- expandSynTyConApp_maybe tc tys + = res -- At the Core level, Constraint = Type -- See Note [coreView vs tcView] @@ -419,6 +419,30 @@ coreView ty@(TyConApp tc tys) coreView _ = Nothing +----------------------------------------------- +expandSynTyConApp_maybe :: TyCon -> [Type] -> Maybe Type +expandSynTyConApp_maybe tc tys + | Just (tvs, rhs) <- synTyConDefn_maybe tc + , n_tys >= arity + = Just (expand_syn arity tvs rhs n_tys tys) + | otherwise + = Nothing + where + n_tys = length tys + arity = tyConArity tc +-- Without this INLINE the call to expandSynTyConApp_maybe in coreView +-- will result in an avoidable allocation. +{-# INLINE expandSynTyConApp_maybe #-} + +-- | A helper for 'expandSynTyConApp_maybe' to avoid inlining this cold path +-- into call-sites. +expand_syn :: Int -> [TyVar] -> Type -> Int -> [Type] -> Type +expand_syn arity tvs rhs n_tys tys + | n_tys > arity = mkAppTys rhs' (drop arity tys) + | otherwise = rhs' + where + rhs' = substTy (mkTvSubstPrs (tvs `zip` tys)) rhs + {-# INLINE coreFullView #-} coreFullView :: Type -> Type -- ^ Iterates 'coreView' until there is no more to synonym to expand. @@ -2194,6 +2218,36 @@ But the left is an AppTy while the right is a TyConApp. The solution is to use repSplitAppTy_maybe to break up the TyConApp into its pieces and then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * TcCanonical.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See [Prefer Type over TYPE 'LiftedRep] in +GHC.Core.TyCo.Rep for details. + -} eqType :: Type -> Type -> Bool @@ -2305,6 +2359,10 @@ nonDetCmpTypeX env orig_t1 orig_t2 = -- Returns both the resulting ordering relation between the two types -- and whether either contains a cast. go :: RnEnv2 -> Type -> Type -> TypeOrdering + -- See Note [Comparing nullary type synonyms]. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = TEQ go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 | Just t2' <- coreView t2 = go env t1 t2' ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -957,7 +957,12 @@ unify_ty :: UMEnv -- Respects newtypes, PredTypes unify_ty env ty1 ty2 kco - -- Use tcView, not coreView. See Note [coreView vs tcView] in GHC.Core.Type. + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + | TyConApp tc1 [] <- ty1 + , TyConApp tc2 [] <- ty2 + , tc1 == tc2 = return () + + -- TODO: More commentary needed here | Just ty1' <- tcView ty1 = unify_ty env ty1' ty2 kco | Just ty2' <- tcView ty2 = unify_ty env ty1 ty2' kco | CastTy ty1' co <- ty1 = if um_unif env ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -961,6 +961,11 @@ can_eq_nc' -> Type -> Type -- RHS, after and before type-synonym expansion, resp -> TcS (StopOrContinue Ct) +-- See Note [Comparing nullary type synonyms] in GHC.Core.Type. +can_eq_nc' _flat _rdr_env _envs ev eq_rel ty1@(TyConApp tc1 []) _ps_ty1 (TyConApp tc2 []) _ps_ty2 + | tc1 == tc2 + = canEqReflexive ev eq_rel ty1 + -- Expand synonyms first; see Note [Type synonyms and canonicalization] can_eq_nc' flat rdr_env envs ev eq_rel ty1 ps_ty1 ty2 ps_ty2 | Just ty1' <- tcView ty1 = can_eq_nc' flat rdr_env envs ev eq_rel ty1' ps_ty1 ty2 ps_ty2 ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -120,7 +120,6 @@ import GHC.Types.Id as Id import GHC.Types.Name import GHC.Types.Var.Set import GHC.Builtin.Types -import GHC.Builtin.Types.Prim import GHC.Types.Var.Env import GHC.Types.Name.Env import GHC.Utils.Misc ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -1545,6 +1545,11 @@ tc_eq_type keep_syns vis_only orig_ty1 orig_ty2 = go orig_env orig_ty1 orig_ty2 where go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] in GHC.Core.Type. + go _ (TyConApp tc1 []) (TyConApp tc2 []) + | tc1 == tc2 + = True + go env t1 t2 | not keep_syns, Just t1' <- tcView t1 = go env t1' t2 go env t1 t2 | not keep_syns, Just t2' <- tcView t2 = go env t1 t2' ===================================== testsuite/tests/deSugar/should_compile/T2431.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 63, types: 43, coercions: 1, joins: 0/0} + = {terms: 63, types: 39, coercions: 1, joins: 0/0} --- RHS size: {terms: 2, types: 4, coercions: 1, joins: 0/0} +-- RHS size: {terms: 2, types: 3, coercions: 1, joins: 0/0} T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a [GblId[DataConWrapper], Caf=NoCafRefs, @@ -15,7 +15,7 @@ T2431.$WRefl [InlPrag=INLINE[final] CONLIKE] :: forall a. a :~: a T2431.$WRefl = \ (@a) -> T2431.Refl @a @a @~(_N :: a GHC.Prim.~# a) --- RHS size: {terms: 4, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 7, coercions: 0, joins: 0/0} absurd :: forall a. (Int :~: Bool) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] absurd = \ (@a) (x :: Int :~: Bool) -> case x of { } ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -16,13 +16,12 @@ Derived class instances: = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(T14578.Wat f g a -> T14578.Wat f g a -> T14578.Wat f g a) ((GHC.Base.<>) @(T14578.App (Data.Functor.Compose.Compose f g) a)) GHC.Base.sconcat = GHC.Prim.coerce - @(GHC.Base.NonEmpty - (T14578.App (Data.Functor.Compose.Compose f g) a) + @(GHC.Base.NonEmpty (T14578.App (Data.Functor.Compose.Compose f g) a) -> T14578.App (Data.Functor.Compose.Compose f g) a) @(GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a) (GHC.Base.sconcat @@ -31,7 +30,7 @@ Derived class instances: = GHC.Prim.coerce @(b -> T14578.App (Data.Functor.Compose.Compose f g) a - -> T14578.App (Data.Functor.Compose.Compose f g) a) + -> T14578.App (Data.Functor.Compose.Compose f g) a) @(b -> T14578.Wat f g a -> T14578.Wat f g a) (GHC.Base.stimes @(T14578.App (Data.Functor.Compose.Compose f g) a)) ===================================== testsuite/tests/plugins/plugins09.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/plugins10.stdout ===================================== @@ -6,7 +6,6 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: Language.Haskell.TH.Syntax typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat parsePlugin(a) ===================================== testsuite/tests/plugins/plugins11.stdout ===================================== @@ -3,6 +3,5 @@ interfacePlugin: Prelude interfacePlugin: GHC.Float interfacePlugin: GHC.Base typeCheckPlugin (rn) -interfacePlugin: GHC.Types typeCheckPlugin (tc) interfacePlugin: GHC.Num.BigNat ===================================== testsuite/tests/plugins/static-plugins.stdout ===================================== @@ -5,11 +5,11 @@ interfacePlugin: GHC.Float interfacePlugin: GHC.Base interfacePlugin: System.IO typeCheckPlugin (rn) -interfacePlugin: GHC.Prim -interfacePlugin: GHC.Show interfacePlugin: GHC.Types +interfacePlugin: GHC.Show interfacePlugin: GHC.TopHandler typeCheckPlugin (tc) +interfacePlugin: GHC.Prim interfacePlugin: GHC.CString interfacePlugin: GHC.Num.BigNat ==pure.1 ===================================== testsuite/tests/printer/T18052a.stderr ===================================== @@ -10,9 +10,9 @@ Dependent packages: [base-4.16.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 24, types: 61, coercions: 0, joins: 0/0} + = {terms: 24, types: 52, coercions: 0, joins: 0/0} --- RHS size: {terms: 7, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} T18052a.$b:||: :: forall {a} {b}. a -> b -> (a, b) [GblId, Arity=2, Unf=OtherCon []] T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) @@ -22,7 +22,7 @@ T18052a.$b:||: = \ (@a) (@b) (x :: a) (y :: b) -> (x, y) [GblId] (+++) = ++ --- RHS size: {terms: 13, types: 20, coercions: 0, joins: 0/0} +-- RHS size: {terms: 13, types: 18, coercions: 0, joins: 0/0} T18052a.$m:||: :: forall {rep :: GHC.Types.RuntimeRep} {r :: TYPE rep} {a} {b}. (a, b) -> (a -> b -> r) -> ((# #) -> r) -> r ===================================== testsuite/tests/simplCore/should_compile/T13143.stderr ===================================== @@ -1,17 +1,17 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 71, types: 44, coercions: 0, joins: 0/0} + = {terms: 71, types: 40, coercions: 0, joins: 0/0} Rec { --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} T13143.$wf [InlPrag=NOINLINE, Occ=LoopBreaker] :: forall {a}. (# #) -> a [GblId, Arity=1, Str=b, Cpr=b, Unf=OtherCon []] T13143.$wf = \ (@a) _ [Occ=Dead] -> T13143.$wf @a GHC.Prim.(##) end Rec } --- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} +-- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} f [InlPrag=[final]] :: forall a. Int -> a [GblId, Arity=1, ===================================== testsuite/tests/simplCore/should_compile/T18013.stderr ===================================== @@ -129,9 +129,9 @@ Rule fired: Class op fmap (BUILTIN) ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 52, types: 106, coercions: 17, joins: 0/1} + = {terms: 52, types: 101, coercions: 17, joins: 0/1} --- RHS size: {terms: 37, types: 87, coercions: 17, joins: 0/1} +-- RHS size: {terms: 37, types: 84, coercions: 17, joins: 0/1} mapMaybeRule :: forall a b. Rule IO a b -> Rule IO (Maybe a) (Maybe b) [GblId, ===================================== testsuite/tests/simplCore/should_compile/T7360.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Tidy Core ==================== Result size of Tidy Core - = {terms: 106, types: 47, coercions: 0, joins: 0/0} + = {terms: 106, types: 45, 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 @@ -31,7 +31,7 @@ T7360.fun4 :: () WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 20 0}] T7360.fun4 = fun1 T7360.Foo1 --- RHS size: {terms: 11, types: 8, coercions: 0, joins: 0/0} +-- RHS size: {terms: 11, types: 7, coercions: 0, joins: 0/0} fun2 :: forall {a}. [a] -> ((), Int) [GblId, Arity=1, ===================================== testsuite/tests/typecheck/should_compile/T13032.stderr ===================================== @@ -1,9 +1,9 @@ ==================== Desugar (after optimization) ==================== Result size of Desugar (after optimization) - = {terms: 13, types: 24, coercions: 0, joins: 0/0} + = {terms: 13, types: 18, coercions: 0, joins: 0/0} --- RHS size: {terms: 6, types: 11, coercions: 0, joins: 0/0} +-- RHS size: {terms: 6, types: 8, coercions: 0, joins: 0/0} f :: forall a b. (a ~ b) => a -> b -> Bool [LclIdX, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/334ca3f8d40048fb067d79413bf664475a1de457 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/334ca3f8d40048fb067d79413bf664475a1de457 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 Fri Nov 13 19:29:06 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 13 Nov 2020 14:29:06 -0500 Subject: [Git][ghc/ghc][master] 2 commits: testsuite: Add testcase for #18733 Message-ID: <5faede82802b8_43133fa67e8d55044687f2@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 7 changed files: - compiler/GHC/Iface/Recomp.hs - + testsuite/tests/driver/T18733/Library1.hs - + testsuite/tests/driver/T18733/Library2.hs - + testsuite/tests/driver/T18733/Main.hs - + testsuite/tests/driver/T18733/Makefile - + testsuite/tests/driver/T18733/T18733.stdout - + testsuite/tests/driver/T18733/all.T Changes: ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -65,6 +65,7 @@ import Data.Function import Data.List (find, sortBy, sort) import qualified Data.Map as Map import qualified Data.Set as Set +import Data.Word (Word64) --Qualified import so we can define a Semigroup instance -- but it doesn't clash with Outputable.<> @@ -729,6 +730,77 @@ Names (e.g. the ifName field of a IfaceDecl) and non-binding (e.g. the ifInstCls field of a IfaceClsInst): only in the non-binding case should we include the fingerprint; in the binding case we shouldn't since it is merely the name of the thing that we are currently fingerprinting. + + +Note [Fingerprinting recursive groups] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +The fingerprinting of a single recursive group is a rather subtle affair, as +seen in #18733. + +How not to fingerprint +---------------------- + +Prior to fixing #18733 we used the following (flawed) scheme to fingerprint a +group in hash environment `hash_env0`: + + 1. extend hash_env0, giving each declaration in the group the fingerprint 0 + 2. use this environment to hash the declarations' ABIs, resulting in + group_fingerprint + 3. produce the final hash environment by extending hash_env0, mapping each + declaration of the group to group_fingerprint + +However, this is wrong. Consider, for instance, a program like: + + data A = ARecu B | ABase String deriving (Show) + data B = BRecu A | BBase Int deriving (Show) + + info :: B + info = BBase 1 + +A consequence of (3) is that A and B will have the same fingerprint. This means +that if the user changes `info` to: + + info :: A + info = ABase "hello" + +The program's ABI fingerprint will not change despite `info`'s type, and +therefore ABI, being clearly different. + +However, the incorrectness doesn't end there: (1) means that all recursive +occurrences of names within the group will be given the same fingerprint. This +means that the group's fingerprint won't change if we change an occurrence of A +to B. + +Surprisingly, this bug (#18733) lurked for many years before being uncovered. + +How we now fingerprint +---------------------- + +As seen above, the fingerprinting function must ensure that a groups +fingerprint captures the structure of within-group occurrences. The scheme that +we use is: + + 0. To ensure determinism, sort the declarations into a stable order by + declaration name + + 1. Extend hash_env0, giving each declaration in the group a sequential + fingerprint (e.g. 0, 1, 2, ...). + + 2. Use this environment to hash the declarations' ABIs, resulting in + group_fingerprint. + + Since we included the sequence number in step (1) programs identical up to + transposition of recursive occurrences are distinguisable, avoiding the + second issue mentioned above. + + 3. Produce the final environment by extending hash_env, mapping each + declaration of the group to the hash of (group_fingerprint, i), where + i is the position of the declaration in the stable ordering. + + Including i in the hash ensures that the first issue noted above is + avoided. + -} -- | Add fingerprints for top-level declarations to a 'ModIface'. @@ -854,18 +926,27 @@ addFingerprints hsc_env iface0 return (env', (hash,decl) : decls_w_hashes) fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) - = do let decls = map abiDecl abis + = do let stable_abis = sortBy cmp_abiNames abis + stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env - (zip (repeat fingerprint0) decls) + (zip (map mkRecFingerprint [0..]) stable_decls) + -- See Note [Fingerprinting recursive groups] let hash_fn = mk_put_name local_env1 -- pprTrace "fingerprinting" (ppr (map ifName decls) ) $ do - let stable_abis = sortBy cmp_abiNames abis -- put the cycle in a canonical order hash <- computeFingerprint hash_fn stable_abis - let pairs = zip (repeat hash) decls + let pairs = zip (map (bumpFingerprint hash) [0..]) stable_decls + -- See Note [Fingerprinting recursive groups] local_env2 <- foldM extend_hash_env local_env pairs return (local_env2, pairs ++ decls_w_hashes) + -- Make a fingerprint from the ordinal position of a binding in its group. + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i + + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. @@ -884,7 +965,8 @@ addFingerprints hsc_env iface0 -- when calculating fingerprints, we always need to use canonical -- ordering for lists of things. In particular, the mi_deps has various -- lists of modules and suchlike, so put these all in canonical order: - let sorted_deps = sortDependencies (mi_deps iface0) + let sorted_deps :: Dependencies + sorted_deps = sortDependencies (mi_deps iface0) -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way @@ -971,7 +1053,8 @@ addFingerprints hsc_env iface0 -- -- put the declarations in a canonical order, sorted by OccName - let sorted_decls = Map.elems $ Map.fromList $ + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ [(getOccName d, e) | e@(_, d) <- decls_w_hashes] -- the flag hash depends on: ===================================== testsuite/tests/driver/T18733/Library1.hs ===================================== @@ -0,0 +1,7 @@ +module Library where + +data A = ARecu B | ABase String deriving (Show) +data B = BRecu A | BBase Int deriving (Show) + +info :: B +info = BBase 1 ===================================== testsuite/tests/driver/T18733/Library2.hs ===================================== @@ -0,0 +1,7 @@ +module Library where + +data A = ARecu B | ABase String deriving (Show) +data B = BRecu A | BBase Int deriving (Show) + +info :: A +info = ABase "Hello" ===================================== testsuite/tests/driver/T18733/Main.hs ===================================== @@ -0,0 +1,5 @@ +module Main where + +import Library + +main = putStrLn $ show info ===================================== testsuite/tests/driver/T18733/Makefile ===================================== @@ -0,0 +1,12 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +T18733: + cp Library1.hs Library.hs + '$(TEST_HC)' -v0 -o Main Library.hs Main.hs + ./Main + + cp Library2.hs Library.hs + '$(TEST_HC)' -v0 -o Main Library.hs Main.hs + ./Main ===================================== testsuite/tests/driver/T18733/T18733.stdout ===================================== @@ -0,0 +1,2 @@ +BBase 1 +ABase "Hello" ===================================== testsuite/tests/driver/T18733/all.T ===================================== @@ -0,0 +1,2 @@ +srcs = ['Library1.hs', 'Library2.hs', 'Main.hs'] +test('T18733', extra_files(srcs), makefile_test, []) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5506f1342e51bad71a7525ddad0650d1ac63afeb...5353fd500b1e92636cd9d45274585fd88a915ff6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5506f1342e51bad71a7525ddad0650d1ac63afeb...5353fd500b1e92636cd9d45274585fd88a915ff6 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 Fri Nov 13 19:29:50 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 13 Nov 2020 14:29:50 -0500 Subject: [Git][ghc/ghc][master] 2 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5faedeaee6dc_43133fa67e46b7704738eb@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - 6 changed files: - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity at@(AT oss _) ar + | oss `lengthAtMost` ar = at + | otherwise = AT (take ar oss) topDiv + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5353fd500b1e92636cd9d45274585fd88a915ff6...197d59facbe8f9799df47e86c99f401ced487040 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5353fd500b1e92636cd9d45274585fd88a915ff6...197d59facbe8f9799df47e86c99f401ced487040 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 Fri Nov 13 19:30:29 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 13 Nov 2020 14:30:29 -0500 Subject: [Git][ghc/ghc][master] Add rts_listThreads and rts_listMiscRoots to RtsAPI.h Message-ID: <5faeded57bee5_43133fa68ee0003c47644c@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 6 changed files: - includes/RtsAPI.h - rts/RtsAPI.c - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -17,8 +17,10 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" +#include "rts/Types.h" #include "rts/EventLogWriter.h" + /* * Running the scheduler */ @@ -566,6 +568,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== rts/RtsAPI.c ===================================== @@ -15,6 +15,7 @@ #include "Prelude.h" #include "Schedule.h" #include "Capability.h" +#include "StableName.h" #include "StablePtr.h" #include "Threads.h" #include "Weak.h" @@ -809,6 +810,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +874,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de7ec9dd2bd573d5950ae294747d2bdb45051000 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de7ec9dd2bd573d5950ae294747d2bdb45051000 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 Fri Nov 13 19:30:59 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 13 Nov 2020 14:30:59 -0500 Subject: [Git][ghc/ghc][master] gitlab-ci: Cache cabal store in linting job Message-ID: <5faedef39e4ba_43133fa68ee0003c4793cd@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -307,16 +307,20 @@ hadrian-ghc-in-ghci: - .gitlab/ci.sh setup - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache variables: GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache lint-base: extends: .lint-params script: - hadrian/build -c -j stage1:lib:base - hadrian/build -j lint:base - cache: - key: lint ############################################################ # Validation via Pipelines (make) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24a86f09da3426cf1006004bc45d312725280dd5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24a86f09da3426cf1006004bc45d312725280dd5 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 Sat Nov 14 11:47:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 14 Nov 2020 06:47:38 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] 3 commits: testsuite: Add test for #18346 Message-ID: <5fafc3daea8b1_43133fa67ebede58547419@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: f96d6cd7 by Ben Gamari at 2020-11-14T06:47:14-05:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. (cherry picked from commit ee5dcdf95a7c408e9c339aacebf89a007a735f8f) - - - - - 36c1027d by Ben Gamari at 2020-11-14T06:47:14-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. (cherry picked from commit 6d21ecee535782f01dba9947a49e282afee25724) - - - - - 215f5c30 by Andreas Klebinger at 2020-11-14T06:47:22-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) (cherry picked from commit fda3e50b559f6f25347f9ad7239e5003e27937b0) - - - - - 12 changed files: - compiler/nativeGen/X86/CodeGen.hs - compiler/nativeGen/X86/Cond.hs - rts/PrimOps.cmm - rts/RtsMessages.c - rts/linker/PEi386.c - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm - + testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs - + testsuite/tests/simplCore/should_compile/T18346/T18346.hs - + testsuite/tests/simplCore/should_compile/T18346/all.T Changes: ===================================== compiler/nativeGen/X86/CodeGen.hs ===================================== @@ -1804,6 +1804,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1821,22 +1850,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/nativeGen/X86/Cond.hs ===================================== @@ -13,22 +13,22 @@ import GhcPrelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condUnsigned :: Cond -> Bool ===================================== rts/PrimOps.cmm ===================================== @@ -1821,7 +1821,9 @@ loop: StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; } - ASSERT(StgTSO_block_info(tso) == mvar); + if(StgTSO_block_info(tso) != mvar) { + ccall putMVarError(mvar "ptr", tso "ptr"); + } // save why_blocked here, because waking up the thread destroys // this information W_ why_blocked; ===================================== rts/RtsMessages.c ===================================== @@ -40,6 +40,16 @@ RtsMsgFunction *debugMsgFn = rtsDebugMsgFn; RtsMsgFunction *errorMsgFn = rtsErrorMsgFn; RtsMsgFunction *sysErrorMsgFn = rtsSysErrorMsgFn; +void +putMVarError(StgMVar *mvar, StgTSO *tso) +{ + errorBelch("putMVarzh: uh oh, blocked mismatch\n"); + errorBelch(" tso->why_blocked=%d\n", tso->why_blocked); + errorBelch(" tso->block_info=%p\n", tso->block_info); + errorBelch(" mvar=%p\n", mvar); + barf("he's dead, jim.\n"); +} + void barf(const char*s, ...) { ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + ===================================== testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE RankNTypes #-} + +module MiniLens ((^.), Getting, Lens', lens, view) where + +import Data.Functor.Const (Const(..)) + +type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t + +type Lens' s a = Lens s s a a + +lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b +lens sa sbt afb s = sbt s <$> afb (sa s) +{-# INLINE lens #-} + +type Getting r s a = (a -> Const r a) -> s -> Const r s + +view :: Getting a s a -> s -> a +view l = getConst . l Const +{-# INLINE view #-} + +(^.) :: s -> Getting a s a -> a +s ^. l = getConst (l Const s) +{-# INLINE (^.) #-} ===================================== testsuite/tests/simplCore/should_compile/T18346/T18346.hs ===================================== @@ -0,0 +1,18 @@ +{-# LANGUAGE RankNTypes #-} + +module GHCBug (field) where + +import MiniLens ((^.), Getting, Lens', lens, view) + +t' :: Getting () () () +t' = lens id const +{-# NOINLINE t' #-} + +mlift :: Functor f => Getting b a b -> Lens' (f a) (f b) +mlift l = lens (fmap (^. l)) const +{-# INLINE mlift #-} + +newtype Field = F (Maybe () -> Maybe ()) + +field :: Field +field = F (view (mlift t')) ===================================== testsuite/tests/simplCore/should_compile/T18346/all.T ===================================== @@ -0,0 +1,2 @@ +test('T18346', [extra_files(['MiniLens.hs'])], multimod_compile, ['T18346.hs', '-v0']) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a9d871d567e8f63c63dcd4d65ae18fd42d5c5fdf...215f5c305f3ce53f385b4337dca19d562a034b90 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a9d871d567e8f63c63dcd4d65ae18fd42d5c5fdf...215f5c305f3ce53f385b4337dca19d562a034b90 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 Sat Nov 14 11:49:14 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 14 Nov 2020 06:49:14 -0500 Subject: [Git][ghc/ghc][ghc-8.8] rts/linker: Fix relocation overflow in PE linker Message-ID: <5fafc43a391e4_4313a64bec8549771@gitlab.haskell.org.mail> Ben Gamari pushed to branch ghc-8.8 at Glasgow Haskell Compiler / GHC Commits: c58498b2 by Ben Gamari at 2020-11-14T06:49:01-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. (cherry picked from commit 6d21ecee535782f01dba9947a49e282afee25724) - - - - - 2 changed files: - libraries/Cabal - rts/linker/PEi386.c Changes: ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 8199c3f838a15fb9b7c8d3527603084b2474d877 +Subproject commit bd07f0a095869b91a590d8a564f716a6a136818a ===================================== rts/linker/PEi386.c ===================================== @@ -1943,13 +1943,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1961,14 +1963,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c58498b2dd95bac99cb3fa9014fa64cf12dd2f18 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c58498b2dd95bac99cb3fa9014fa64cf12dd2f18 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 Sat Nov 14 11:50:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 14 Nov 2020 06:50:26 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/backports Message-ID: <5fafc482e1f8_43133fa67e5fc5a85517d6@gitlab.haskell.org.mail> Ben Gamari pushed new branch wip/backports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports 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 Sat Nov 14 12:05:17 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 14 Nov 2020 07:05:17 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: Arity: Rework `ArityType` to fix monotonicity (#18870) Message-ID: <5fafc7fd94f9a_43133fa68ea8f920566626@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - c63c93e1 by Ben Gamari at 2020-11-14T07:05:05-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 3bdd5d9f by Ben Gamari at 2020-11-14T07:05:05-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - 7bada114 by Ben Gamari at 2020-11-14T07:05:05-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a61aec33 by Ben Gamari at 2020-11-14T07:05:05-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - 501a7ec1 by Ben Gamari at 2020-11-14T07:05:05-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 22 changed files: - .gitlab-ci.yml - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - docs/users_guide/debug-info.rst - ghc/ghc-bin.cabal.in - includes/RtsAPI.h - rts/RtsAPI.c - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== .gitlab-ci.yml ===================================== @@ -307,16 +307,20 @@ hadrian-ghc-in-ghci: - .gitlab/ci.sh setup - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache variables: GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache lint-base: extends: .lint-params script: - hadrian/build -c -j stage1:lib:base - hadrian/build -j lint:base - cache: - key: lint ############################################################ # Validation via Pipelines (make) @@ -738,6 +742,15 @@ release-x86_64-linux-deb10: <<: *release extends: .build-x86_64-linux-deb10 +release-x86_64-linux-deb10-dwarf: + <<: *release + extends: .build-x86_64-linux-deb10 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + TEST_ENV: "x86_64-linux-deb10-dwarf" + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz" + ################################# # x86_64-linux-ubuntu 20.04 ################################# @@ -853,7 +866,7 @@ release-x86_64-linux-centos7: # x86_64-linux-fedora27 ################################# -validate-x86_64-linux-fedora27: +.build-x86_64-linux-fedora27: extends: .validate-linux stage: full-build image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora27:$DOCKER_REV" @@ -862,7 +875,6 @@ validate-x86_64-linux-fedora27: LLC: /bin/false OPT: /bin/false TEST_ENV: "x86_64-linux-fedora27" - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" cache: key: linux-x86_64-fedora27 artifacts: @@ -871,6 +883,20 @@ validate-x86_64-linux-fedora27: # longer. expire_in: 8 week +validate-x86_64-linux-fedora27: + extends: .build-x86_64-linux-fedora27 + variables: + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" + +release-x86_64-linux-fedora27-dwarf: + <<: *release + extends: .build-x86_64-linux-fedora27 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux-dwarf.tar.xz" + TEST_ENV: "x86_64-linux-fedora27-dwarf" + ############################################################ # Validation via Pipelines (Windows) ############################################################ ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -44,6 +44,7 @@ module GHC.Cmm.CLabel ( mkAsmTempLabel, mkAsmTempDerivedLabel, mkAsmTempEndLabel, + mkAsmTempProcEndLabel, mkAsmTempDieLabel, mkDirty_MUT_VAR_Label, @@ -755,6 +756,10 @@ mkAsmTempDerivedLabel = AsmTempDerivedLabel mkAsmTempEndLabel :: CLabel -> CLabel mkAsmTempEndLabel l = mkAsmTempDerivedLabel l (fsLit "_end") +-- | A label indicating the end of a procedure. +mkAsmTempProcEndLabel :: CLabel -> CLabel +mkAsmTempProcEndLabel l = mkAsmTempDerivedLabel l (fsLit "_proc_end") + -- | Construct a label for a DWARF Debug Information Entity (DIE) -- describing another symbol. mkAsmTempDieLabel :: CLabel -> CLabel ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -1187,9 +1187,10 @@ initNCGConfig dflags this_mod = NCGConfig ArchX86 -> v _ -> Nothing - , ncgDwarfEnabled = debugLevel dflags > 0 + , ncgDwarfEnabled = debugLevel dflags > 0 , ncgDwarfUnwindings = debugLevel dflags >= 1 - , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags + , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. + , ncgDwarfSourceNotes = debugLevel dflags >= 3 -- We produce GHC-specific source-note DIEs only with -g3 } ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -40,6 +40,7 @@ data NCGConfig = NCGConfig , ncgDwarfUnwindings :: !Bool -- ^ Enable unwindings , ncgDwarfStripBlockInfo :: !Bool -- ^ Strip out block information from generated Dwarf , ncgExposeInternalSymbols :: !Bool -- ^ Expose symbol table entries for internal symbols + , ncgDwarfSourceNotes :: !Bool -- ^ Enable GHC-specific source note DIEs } -- | Return Word size ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -45,7 +45,7 @@ dwarfGen config modLoc us blocks = do | otherwise = dbg compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs - highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + highLabel = mkAsmTempProcEndLabel $ dblCLabel $ last procs dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) , dwName = fromMaybe "" (ml_hs_file modLoc) @@ -99,10 +99,10 @@ dwarfGen config modLoc us blocks = do -- scattered in the final binary. Without split sections, we could make a -- single arange based on the first/last proc. mkDwarfARange :: DebugBlock -> DwarfARange -mkDwarfARange proc = DwarfARange start end +mkDwarfARange proc = DwarfARange lbl end where - start = dblCLabel proc - end = mkAsmTempEndLabel start + lbl = dblCLabel proc + end = mkAsmTempProcEndLabel lbl -- | Header for a compilation unit, establishing global format -- parameters @@ -176,7 +176,7 @@ parent, B. -- | Generate DWARF info for a procedure debug block procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc - = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) + = DwarfSubprogram { dwChildren = map (blockToDwarf config) (dblBlocks prc) , dwName = case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) @@ -195,14 +195,17 @@ procToDwarf config prc goodParent _ = True -- | Generate DWARF info for a block -blockToDwarf :: DebugBlock -> DwarfInfo -blockToDwarf blk - = DwarfBlock { dwChildren = concatMap tickToDwarf (dblTicks blk) - ++ map blockToDwarf (dblBlocks blk) +blockToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo +blockToDwarf config blk + = DwarfBlock { dwChildren = map (blockToDwarf config) (dblBlocks blk) ++ srcNotes , dwLabel = dblCLabel blk , dwMarker = marker } where + srcNotes + | ncgDwarfSourceNotes config = concatMap tickToDwarf (dblTicks blk) + | otherwise = [] + marker | Just _ <- dblPosition blk = Just $ mkAsmTempLabel $ dblLabel blk | otherwise = Nothing -- block was optimized out ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -48,7 +48,7 @@ dW_TAG_ghc_src_note = 0x5b00 -- * Dwarf attributes dW_AT_name, dW_AT_stmt_list, dW_AT_low_pc, dW_AT_high_pc, dW_AT_language, dW_AT_comp_dir, dW_AT_producer, dW_AT_external, dW_AT_frame_base, - dW_AT_use_UTF8, dW_AT_MIPS_linkage_name :: Word + dW_AT_use_UTF8, dW_AT_linkage_name :: Word dW_AT_name = 0x03 dW_AT_stmt_list = 0x10 dW_AT_low_pc = 0x11 @@ -59,7 +59,7 @@ dW_AT_producer = 0x25 dW_AT_external = 0x3f dW_AT_frame_base = 0x40 dW_AT_use_UTF8 = 0x53 -dW_AT_MIPS_linkage_name = 0x2007 +dW_AT_linkage_name = 0x6e -- * Custom DWARF attributes -- Chosen a more or less random section of the vendor-extensible region ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -105,7 +105,7 @@ pprAbbrevDecls platform haveDebugLine = -- DwAbbrSubprogramWithParent subprogramAttrs = [ (dW_AT_name, dW_FORM_string) - , (dW_AT_MIPS_linkage_name, dW_FORM_string) + , (dW_AT_linkage_name, dW_FORM_string) , (dW_AT_external, dW_FORM_flag) , (dW_AT_low_pc, dW_FORM_addr) , (dW_AT_high_pc, dW_FORM_addr) @@ -190,7 +190,7 @@ pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) - $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel label) + $$ pprWord platform (pdoc platform $ mkAsmTempProcEndLabel label) $$ pprByte 1 $$ pprByte dW_OP_call_frame_cfa $$ parentValue @@ -354,7 +354,7 @@ pprFrameProc :: Platform -> CLabel -> UnwindTable -> DwarfFrameProc -> SDoc pprFrameProc platform frameLbl initUw (DwarfFrameProc procLbl hasInfo blocks) = let fdeLabel = mkAsmTempDerivedLabel procLbl (fsLit "_fde") fdeEndLabel = mkAsmTempDerivedLabel procLbl (fsLit "_fde_end") - procEnd = mkAsmTempEndLabel procLbl + procEnd = mkAsmTempProcEndLabel procLbl ifInfo str = if hasInfo then text str else empty -- see [Note: Info Offset] in vcat [ whenPprDebug $ text "# Unwinding for" <+> pdoc platform procLbl <> colon ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -93,8 +93,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = pprProcLabel config lbl $$ pprLabel platform lbl $$ -- blocks guaranteed not null, so label needed vcat (map (pprBasicBlock config top_info) blocks) $$ - (if ncgDwarfEnabled config - then pdoc platform (mkAsmTempEndLabel lbl) <> char ':' else empty) $$ + ppWhen (ncgDwarfEnabled config) (pprBlockEndLabel platform lbl $$ pprProcEndLabel platform lbl) $$ pprSizeDecl platform lbl Just (CmmStaticsRaw info_lbl _) -> @@ -105,6 +104,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = then pdoc platform (mkDeadStripPreventer info_lbl) <> char ':' else empty) $$ vcat (map (pprBasicBlock config top_info) blocks) $$ + ppWhen (ncgDwarfEnabled config) (pprProcEndLabel platform info_lbl) $$ -- above: Even the first block gets a label, because with branch-chain -- elimination, it might be the target of a goto. (if platformHasSubsectionsViaSymbols platform @@ -125,6 +125,16 @@ pprProcLabel config lbl | otherwise = empty +pprProcEndLabel :: Platform -> CLabel -- ^ Procedure name + -> SDoc +pprProcEndLabel platform lbl = + pdoc platform (mkAsmTempProcEndLabel lbl) <> char ':' + +pprBlockEndLabel :: Platform -> CLabel -- ^ Block name + -> SDoc +pprBlockEndLabel platform lbl = + pdoc platform (mkAsmTempEndLabel lbl) <> char ':' + -- | Output the ELF .size directive. pprSizeDecl :: Platform -> CLabel -> SDoc pprSizeDecl platform lbl @@ -137,9 +147,11 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) = maybe_infotable $ pprLabel platform asmLbl $$ vcat (map (pprInstr platform) instrs) $$ - (if ncgDwarfEnabled config - then pdoc (ncgPlatform config) (mkAsmTempEndLabel asmLbl) <> char ':' - else empty + ppWhen (ncgDwarfEnabled config) ( + -- Emit both end labels since this may end up being a standalone + -- top-level block + pprBlockEndLabel platform asmLbl + <> pprProcEndLabel platform asmLbl ) where asmLbl = blockLbl blockid @@ -152,10 +164,8 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) vcat (map (pprData config) info) $$ pprLabel platform infoLbl $$ c $$ - (if ncgDwarfEnabled config - then pdoc platform (mkAsmTempEndLabel infoLbl) <> char ':' - else empty - ) + ppWhen (ncgDwarfEnabled config) (pdoc platform (mkAsmTempEndLabel infoLbl) <> char ':') + -- Make sure the info table has the right .loc for the block -- coming right after it. See [Note: Info Offset] infoTableLoc = case instrs of ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity at@(AT oss _) ar + | oss `lengthAtMost` ar = at + | otherwise = AT (take ar oss) topDiv + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== docs/users_guide/debug-info.rst ===================================== @@ -24,7 +24,9 @@ useable by most UNIX debugging tools. * ``-g1``: produces stack unwinding records for top-level functions (sufficient for basic backtraces) * ``-g2``: produces stack unwinding records for top-level functions as well as inner blocks (allowing more precise backtraces than with ``-g1``). - * ``-g3``: same as ``-g2``. + * ``-g3``: produces GHC-specific DWARF information for use by more + sophisticated Haskell-aware debugging tools (see :ref:`dwarf-dies` for + details) If ⟨n⟩ is omitted, level 2 is assumed. @@ -266,6 +268,7 @@ In particular GHC produces the following DWARF sections, ``.debug_arange`` Address range information necessary for efficient lookup in debug information. +.. _dwarf_dies: Debugging information entities ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -91,6 +91,8 @@ Executable ghc if flag(threaded) ghc-options: -threaded + ghc-options: -eventlog + Other-Extensions: CPP NondecreasingIndentation ===================================== includes/RtsAPI.h ===================================== @@ -17,8 +17,10 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" +#include "rts/Types.h" #include "rts/EventLogWriter.h" + /* * Running the scheduler */ @@ -566,6 +568,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== rts/RtsAPI.c ===================================== @@ -15,6 +15,7 @@ #include "Prelude.h" #include "Schedule.h" #include "Capability.h" +#include "StableName.h" #include "StablePtr.h" #include "Threads.h" #include "Weak.h" @@ -809,6 +810,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +874,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/238fa01aac08f19b11daddd588949ddace09aa47...501a7ec12224d2d8c77ad8df055f5dbd1627752c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/238fa01aac08f19b11daddd588949ddace09aa47...501a7ec12224d2d8c77ad8df055f5dbd1627752c 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 Sat Nov 14 12:07:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 14 Nov 2020 07:07:40 -0500 Subject: [Git][ghc/ghc][wip/T18043] 7 commits: testsuite: Add testcase for #18733 Message-ID: <5fafc88cdabc5_43133fa6cd93ad24570787@gitlab.haskell.org.mail> Ben Gamari pushed to branch wip/T18043 at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - aaaa833b by Ben Gamari at 2020-11-14T07:07:21-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Iface/Recomp.hs - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/RtsAPI.c - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - + testsuite/tests/arityanal/should_compile/T18870.hs - + testsuite/tests/arityanal/should_compile/T18937.hs - testsuite/tests/arityanal/should_compile/all.T - + testsuite/tests/driver/T18733/Library1.hs - + testsuite/tests/driver/T18733/Library2.hs - + testsuite/tests/driver/T18733/Main.hs - + testsuite/tests/driver/T18733/Makefile - + testsuite/tests/driver/T18733/T18733.stdout - + testsuite/tests/driver/T18733/all.T - testsuite/tests/rts/pause-resume/all.T - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c - + testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h Changes: ===================================== .gitlab-ci.yml ===================================== @@ -307,16 +307,20 @@ hadrian-ghc-in-ghci: - .gitlab/ci.sh setup - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache variables: GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache lint-base: extends: .lint-params script: - hadrian/build -c -j stage1:lib:base - hadrian/build -j lint:base - cache: - key: lint ############################################################ # Validation via Pipelines (make) ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -17,14 +17,14 @@ module GHC.Core.Opt.Arity , etaExpand, etaExpandAT , exprBotStrictness_maybe - -- ** ArityType - , ArityType(..), expandableArityType, arityTypeArity - , maxWithArity, isBotArityType, idArityType + -- ** ArityType + , ArityType(..), mkBotArityType, mkTopArityType, expandableArityType + , arityTypeArity, maxWithArity, idArityType - -- ** Join points + -- ** Join points , etaExpandToJoinPoint, etaExpandToJoinPointRule - -- ** Coercions and casts + -- ** Coercions and casts , pushCoArg, pushCoArgs, pushCoValArg, pushCoTyArg , pushCoercionIntoLambda, pushCoDataCon, collectBindersPushingCo ) @@ -455,27 +455,36 @@ ArityType is the result of a compositional analysis on expressions, from which we can decide the real arity of the expression (extracted with function exprEtaExpandArity). +We use the following notation: + at ::= \o1..on.div + div ::= T | x | ⊥ + o ::= ? | 1 +And omit the \. if n = 0. Examples: + \?11.T stands for @AT [NoOneShotInfo,OneShotLam,OneShotLam] topDiv@ + ⊥ stands for @AT [] botDiv@ +See the 'Outputable' instance for more information. It's pretty simple. + Here is what the fields mean. If an arbitrary expression 'f' has ArityType 'at', then - * If at = ABot n, then (f x1..xn) definitely diverges. Partial - applications to fewer than n args may *or may not* diverge. + * If @at = AT [o1,..,on] botDiv@ (notation: \o1..on.⊥), then @f x1..xn@ + definitely diverges. Partial applications to fewer than n args may *or + may not* diverge. We allow ourselves to eta-expand bottoming functions, even if doing so may lose some `seq` sharing, let x = in \y. error (g x y) ==> \y. let x = in error (g x y) - * If at = ATop as, and n=length as, - then expanding 'f' to (\x1..xn. f x1 .. xn) loses no sharing, - assuming the calls of f respect the one-shot-ness of - its definition. + * If @at = AT [o1,..,on] topDiv@ (notation: \o1..on.T), then expanding 'f' + to @\x1..xn. f x1..xn@ loses no sharing, assuming the calls of f respect + the one-shot-ness o1..on of its definition. - NB 'f' is an arbitrary expression, eg (f = g e1 e2). This 'f' - can have ArityType as ATop, with length as > 0, only if e1 e2 are - themselves. + NB 'f' is an arbitrary expression, eg @f = g e1 e2 at . This 'f' can have + arity type @AT oss _@, with @length oss > 0@, only if e1 e2 are themselves + cheap. - * In both cases, f, (f x1), ... (f x1 ... f(n-1)) are definitely + * In both cases, @f@, @f x1@, ... @f x1 ... x(n-1)@ are definitely really functions, or bottom, but *not* casts from a data type, in at least one case branch. (If it's a function in one case branch but an unsafe cast from a data type in another, the program is bogus.) @@ -485,62 +494,128 @@ ArityType 'at', then Example: f = \x\y. let v = in \s(one-shot) \t(one-shot). blah - 'f' has ArityType [ManyShot,ManyShot,OneShot,OneShot] + 'f' has arity type \??11.T The one-shot-ness means we can, in effect, push that 'let' inside the \st. Suppose f = \xy. x+y -Then f :: AT [False,False] ATop - f v :: AT [False] ATop - f :: AT [] ATop - --------------------- Main arity code ---------------------------- +Then f :: \??.T + f v :: \?.T + f :: T -} -data ArityType -- See Note [ArityType] - = ATop [OneShotInfo] - | ABot Arity - deriving( Eq ) - -- There is always an explicit lambda - -- to justify the [OneShot], or the Arity - +-- | The analysis lattice of arity analysis. It is isomorphic to +-- +-- @ +-- data ArityType' +-- = AEnd Divergence +-- | ALam OneShotInfo ArityType' +-- @ +-- +-- Which is easier to display the Hasse diagram for: +-- +-- @ +-- ALam OneShotLam at +-- | +-- AEnd topDiv +-- | +-- ALam NoOneShotInfo at +-- | +-- AEnd exnDiv +-- | +-- AEnd botDiv +-- @ +-- +-- where the @at@ fields of @ALam@ are inductively subject to the same order. +-- That is, @ALam os at1 < ALam os at2@ iff @at1 < at2 at . +-- +-- Why the strange Top element? See Note [Combining case branches]. +-- +-- We rely on this lattice structure for fixed-point iteration in +-- 'findRhsArity'. For the semantics of 'ArityType', see Note [ArityType]. +data ArityType + = AT ![OneShotInfo] !Divergence + -- ^ @AT oss div@ means this value can safely be eta-expanded @length oss@ + -- times, provided use sites respect the 'OneShotInfo's in @oss at . + -- A 'OneShotLam' annotation can come from two sources: + -- * The user annotated a lambda as one-shot with 'GHC.Exts.oneShot' + -- * It's from a lambda binder of a type affected by `-fstate-hack`. + -- See 'idStateHackOneShotInfo'. + -- In both cases, 'OneShotLam' should win over 'NoOneShotInfo', see + -- Note [Combining case branches]. + -- + -- If @div@ is dead-ending ('isDeadEndDiv'), then application to + -- @length os@ arguments will surely diverge, similar to the situation + -- with 'DmdType'. + deriving Eq + +-- | This is the BNF of the generated output: +-- +-- @ +-- @ +-- +-- We format +-- @AT [o1,..,on] topDiv@ as @\o1..on.T@ and +-- @AT [o1,..,on] botDiv@ as @\o1..on.⊥@, respectively. +-- More concretely, @AT [NOI,OS,OS] topDiv@ is formatted as @\?11.T at . +-- If the one-shot info is empty, we omit the leading @\. at . instance Outputable ArityType where - ppr (ATop os) = text "ATop" <> parens (ppr (length os)) - ppr (ABot n) = text "ABot" <> parens (ppr n) + ppr (AT oss div) + | null oss = pp_div div + | otherwise = char '\\' <> hcat (map pp_os oss) <> dot <> pp_div div + where + pp_div Diverges = char '⊥' + pp_div ExnOrDiv = char 'x' + pp_div Dunno = char 'T' + pp_os OneShotLam = char '1' + pp_os NoOneShotInfo = char '?' -arityTypeArity :: ArityType -> Arity --- The number of value args for the arity type -arityTypeArity (ATop oss) = length oss -arityTypeArity (ABot ar) = ar +mkBotArityType :: [OneShotInfo] -> ArityType +mkBotArityType oss = AT oss botDiv -expandableArityType :: ArityType -> Bool --- True <=> eta-expansion will add at least one lambda -expandableArityType (ATop oss) = not (null oss) -expandableArityType (ABot ar) = ar /= 0 +botArityType :: ArityType +botArityType = mkBotArityType [] -isBotArityType :: ArityType -> Bool -isBotArityType (ABot {}) = True -isBotArityType (ATop {}) = False +mkTopArityType :: [OneShotInfo] -> ArityType +mkTopArityType oss = AT oss topDiv -arityTypeOneShots :: ArityType -> [OneShotInfo] -arityTypeOneShots (ATop oss) = oss -arityTypeOneShots (ABot ar) = replicate ar OneShotLam - -- If we are diveging or throwing an exception anyway - -- it's fine to push redexes inside the lambdas +topArityType :: ArityType +topArityType = mkTopArityType [] -botArityType :: ArityType -botArityType = ABot 0 -- Unit for andArityType +-- | The number of value args for the arity type +arityTypeArity :: ArityType -> Arity +arityTypeArity (AT oss _) = length oss -maxWithArity :: ArityType -> Arity -> ArityType -maxWithArity at@(ABot {}) _ = at -maxWithArity at@(ATop oss) ar - | oss `lengthAtLeast` ar = at - | otherwise = ATop (take ar (oss ++ repeat NoOneShotInfo)) +-- | True <=> eta-expansion will add at least one lambda +expandableArityType :: ArityType -> Bool +expandableArityType at = arityTypeArity at /= 0 + +-- | See Note [Dead ends] in "GHC.Types.Demand". +-- Bottom implies a dead end. +isDeadEndArityType :: ArityType -> Bool +isDeadEndArityType (AT _ div) = isDeadEndDiv div -vanillaArityType :: ArityType -vanillaArityType = ATop [] -- Totally uninformative +-- | Expand a non-bottoming arity type so that it has at least the given arity. +maxWithArity :: ArityType -> Arity -> ArityType +maxWithArity at@(AT oss div) !ar + | isDeadEndArityType at = at + | oss `lengthAtLeast` ar = at + | otherwise = AT (take ar $ oss ++ repeat NoOneShotInfo) div + +-- | Trim an arity type so that it has at most the given arity. +-- Any excess 'OneShotInfo's are truncated to 'topDiv', even if they end in +-- 'ABot'. +minWithArity :: ArityType -> Arity -> ArityType +minWithArity at@(AT oss _) ar + | oss `lengthAtMost` ar = at + | otherwise = AT (take ar oss) topDiv + +takeWhileOneShot :: ArityType -> ArityType +takeWhileOneShot (AT oss div) + | isDeadEndDiv div = AT (takeWhile isOneShotInfo oss) topDiv + | otherwise = AT (takeWhile isOneShotInfo oss) div -- | The Arity returned is the number of value args the -- expression can be applied to without doing much work @@ -551,8 +626,9 @@ exprEtaExpandArity dflags e = arityType (etaExpandArityEnv dflags) e getBotArity :: ArityType -> Maybe Arity -- Arity of a divergent function -getBotArity (ABot n) = Just n -getBotArity _ = Nothing +getBotArity (AT oss div) + | isDeadEndDiv div = Just $ length oss + | otherwise = Nothing ---------------------- findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType @@ -563,26 +639,26 @@ findRhsArity :: DynFlags -> Id -> CoreExpr -> Arity -> ArityType -- so it is safe to expand e ==> (\x1..xn. e x1 .. xn) -- (b) if is_bot=True, then e applied to n args is guaranteed bottom findRhsArity dflags bndr rhs old_arity - = go (step botArityType) + = go 0 botArityType -- We always do one step, but usually that produces a result equal to - -- old_arity, and then we stop right away (since arities should not - -- decrease) + -- old_arity, and then we stop right away, because old_arity is assumed + -- to be sound. In other words, arities should never decrease. -- Result: the common case is that there is just one iteration where - go :: ArityType -> ArityType - go cur_atype@(ATop oss) - | length oss <= old_arity = cur_atype - go cur_atype - | new_atype == cur_atype = cur_atype - | otherwise = -#if defined(DEBUG) - pprTrace "Exciting arity" - (vcat [ ppr bndr <+> ppr cur_atype <+> ppr new_atype - , ppr rhs]) -#endif - go new_atype + go :: Int -> ArityType -> ArityType + go !n cur_at@(AT oss div) + | not (isDeadEndDiv div) -- the "stop right away" case + , length oss <= old_arity = cur_at -- from above + | next_at == cur_at = cur_at + | otherwise = + -- Warn if more than 2 iterations. Why 2? See Note [Exciting arity] + WARN( debugIsOn && n > 2, text "Exciting arity" + $$ nest 2 ( + ppr bndr <+> ppr cur_at <+> ppr next_at + $$ ppr rhs) ) + go (n+1) next_at where - new_atype = step cur_atype + next_at = step cur_at step :: ArityType -> ArityType step at = -- pprTrace "step" (ppr bndr <+> ppr at <+> ppr (arityType env rhs)) $ @@ -607,7 +683,7 @@ fifteen years ago! It also shows up in the code for 'rnf' on lists in #4138. We do the neccessary, quite simple fixed-point iteration in 'findRhsArity', -which assumes for a single binding @botArityType@ on the first run and iterates +which assumes for a single binding 'ABot' on the first run and iterates until it finds a stable arity type. Two wrinkles * We often have to ask (see the Case or Let case of 'arityType') whether some @@ -630,6 +706,30 @@ until it finds a stable arity type. Two wrinkles by the 'am_sigs' field in 'FindRhsArity', and 'lookupSigEnv' in the Var case of 'arityType'. +Note [Exciting Arity] +~~~~~~~~~~~~~~~~~~~~~ +The fixed-point iteration in 'findRhsArity' stabilises very quickly in almost +all cases. To get notified of cases where we need an usual number of iterations, +we emit a warning in debug mode, so that we can investigate and make sure that +we really can't do better. It's a gross hack, but catches real bugs (#18870). + +Now, which number is "unusual"? We pick n > 2. Here's a pretty common and +expected example that takes two iterations and would ruin the specificity +of the warning (from T18937): + + f :: [Int] -> Int -> Int + f [] = id + f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) + +Fixed-point iteration starts with arity type ⊥ for f. After the first +iteration, we get arity type \??.T, e.g. arity 2, because we unconditionally +'floatIn' the let-binding (see its bottom case). After the second iteration, +we get arity type \?.T, e.g. arity 1, because now we are no longer allowed +to floatIn the non-cheap let-binding. Which is all perfectly benign, but +means we do two iterations (well, actually 3 'step's to detect we are stable) +and don't want to emit the warning. + Note [Eta expanding through dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ If the experimental -fdicts-cheap flag is on, we eta-expand through @@ -651,44 +751,45 @@ dictionary-typed expression, but that's more work. -} arityLam :: Id -> ArityType -> ArityType -arityLam id (ATop as) = ATop (idStateHackOneShotInfo id : as) -arityLam _ (ABot n) = ABot (n+1) +arityLam id (AT oss div) = AT (idStateHackOneShotInfo id : oss) div floatIn :: Bool -> ArityType -> ArityType -- We have something like (let x = E in b), -- where b has the given arity type. -floatIn _ (ABot n) = ABot n -floatIn True (ATop as) = ATop as -floatIn False (ATop as) = ATop (takeWhile isOneShotInfo as) - -- If E is not cheap, keep arity only for one-shots +floatIn cheap at + | isDeadEndArityType at || cheap = at + -- If E is not cheap, keep arity only for one-shots + | otherwise = takeWhileOneShot at arityApp :: ArityType -> Bool -> ArityType -- Processing (fun arg) where at is the ArityType of fun, -- Knock off an argument and behave like 'let' -arityApp (ABot 0) _ = ABot 0 -arityApp (ABot n) _ = ABot (n-1) -arityApp (ATop []) _ = ATop [] -arityApp (ATop (_:as)) cheap = floatIn cheap (ATop as) - -andArityType :: ArityType -> ArityType -> ArityType -- Used for branches of a 'case' --- This is least upper bound in the ArityType lattice -andArityType (ABot n1) (ABot n2) = ABot (n1 `max` n2) -- Note [ABot branches: use max] -andArityType (ATop as) (ABot _) = ATop as -andArityType (ABot _) (ATop bs) = ATop bs -andArityType (ATop as) (ATop bs) = ATop (as `combine` bs) - where -- See Note [Combining case branches] - combine (a:as) (b:bs) = (a `bestOneShot` b) : combine as bs - combine [] bs = takeWhile isOneShotInfo bs - combine as [] = takeWhile isOneShotInfo as - -{- Note [ABot branches: use max] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +arityApp (AT (_:oss) div) cheap = floatIn cheap (AT oss div) +arityApp at _ = at + +-- | Least upper bound in the 'ArityType' lattice. +-- See the haddocks on 'ArityType' for the lattice. +-- +-- Used for branches of a @case at . +andArityType :: ArityType -> ArityType -> ArityType +andArityType (AT (os1:oss1) div1) (AT (os2:oss2) div2) + | AT oss' div' <- andArityType (AT oss1 div1) (AT oss2 div2) + = AT ((os1 `bestOneShot` os2) : oss') div' -- See Note [Combining case branches] +andArityType (AT [] div1) at2 + | isDeadEndDiv div1 = at2 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at2 -- See Note [Combining case branches] +andArityType at1 (AT [] div2) + | isDeadEndDiv div2 = at1 -- Note [ABot branches: max arity wins] + | otherwise = takeWhileOneShot at1 -- See Note [Combining case branches] + +{- Note [ABot branches: max arity wins] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider case x of True -> \x. error "urk" False -> \xy. error "urk2" -Remember: ABot n means "if you apply to n args, it'll definitely diverge". -So we need (ABot 2) for the whole thing, the /max/ of the ABot arities. +Remember: \o1..on.⊥ means "if you apply to n args, it'll definitely diverge". +So we need \??.⊥ for the whole thing, the /max/ of both arities. Note [Combining case branches] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -698,15 +799,18 @@ Consider True -> z False -> \s(one-shot). e1 in go2 x -We *really* want to eta-expand go and go2. +We *really* want to respect the one-shot annotation provided by the +user and eta-expand go and go2. When combining the branches of the case we have - ATop [] `andAT` ATop [OneShotLam] -and we want to get ATop [OneShotLam]. But if the inner -lambda wasn't one-shot we don't want to do this. -(We need a proper arity analysis to justify that.) + T `andAT` \1.T +and we want to get \1.T. +But if the inner lambda wasn't one-shot (\?.T) we don't want to do this. +(We need a usage analysis to justify that.) So we combine the best of the two branches, on the (slightly dodgy) basis that if we know one branch is one-shot, then they all must be. +Surprisingly, this means that the one-shot arity type is effectively the top +element of the lattice. Note [Arity trimming] ~~~~~~~~~~~~~~~~~~~~~ @@ -718,16 +822,17 @@ most 1, because typeArity (Int -> F a) = 1. So we have to trim the result of calling arityType on (\x y. blah). Failing to do so, and hence breaking the exprArity invariant, led to #5441. -How to trim? For ATop, it's easy. But we must take great care with ABot. -Suppose the expression was (\x y. error "urk"), we'll get (ABot 2). We -absolutely must not trim that to (ABot 1), because that claims that -((\x y. error "urk") |> co) diverges when given one argument, which it -absolutely does not. And Bad Things happen if we think something returns bottom -when it doesn't (#16066). +How to trim? If we end in topDiv, it's easy. But we must take great care with +dead ends (i.e. botDiv). Suppose the expression was (\x y. error "urk"), +we'll get \??.⊥. We absolutely must not trim that to \?.⊥, because that +claims that ((\x y. error "urk") |> co) diverges when given one argument, +which it absolutely does not. And Bad Things happen if we think something +returns bottom when it doesn't (#16066). -So, do not reduce the 'n' in (ABot n); rather, switch (conservatively) to ATop. +So, if we need to trim a dead-ending arity type, switch (conservatively) to +topDiv. -Historical note: long ago, we unconditionally switched to ATop when we +Historical note: long ago, we unconditionally switched to topDiv when we encountered a cast, but that is far too conservative: see #5475 -} @@ -838,25 +943,22 @@ myIsCheapApp sigs fn n_val_args = case lookupVarEnv sigs fn of Nothing -> isCheapApp fn n_val_args -- @Just at@ means local function with @at@ as current ArityType. -- Roughly approximate what 'isCheapApp' is doing. - Just (ABot _) -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils - Just (ATop oss) -> n_val_args < length oss -- Essentially isWorkFreeApp + Just (AT oss div) + | isDeadEndDiv div -> True -- See Note [isCheapApp: bottoming functions] in GHC.Core.Utils + | n_val_args < length oss -> True -- Essentially isWorkFreeApp + | otherwise -> False ---------------- arityType :: ArityEnv -> CoreExpr -> ArityType arityType env (Cast e co) - = case arityType env e of - ATop os -> ATop (take co_arity os) -- See Note [Arity trimming] - ABot n | co_arity < n -> ATop (replicate co_arity noOneShotInfo) - | otherwise -> ABot n + = minWithArity (arityType env e) co_arity -- See Note [Arity trimming] where co_arity = length (typeArity (coercionRKind co)) -- See Note [exprArity invariant] (2); must be true of -- arityType too, since that is how we compute the arity -- of variables, and they in turn affect result of exprArity -- #5441 is a nice demo - -- However, do make sure that ATop -> ATop and ABot -> ABot! - -- Casts don't affect that part. Getting this wrong provoked #5475 arityType env (Var v) | v `elemVarSet` ae_joins env @@ -887,18 +989,15 @@ arityType env (App fun arg ) -- arityType env (Case scrut bndr _ alts) | exprIsDeadEnd scrut || null alts - = botArityType -- Do not eta expand - -- See Note [Dealing with bottom (1)] + = botArityType -- Do not eta expand. See Note [Dealing with bottom (1)] | not (pedanticBottoms env) -- See Note [Dealing with bottom (2)] , myExprIsCheap env scrut (Just (idType bndr)) = alts_type | exprOkForSpeculation scrut = alts_type - | otherwise -- In the remaining cases we may not push - = case alts_type of -- evaluation of the scrutinee in - ATop as -> ATop (takeWhile isOneShotInfo as) - ABot _ -> ATop [] + | otherwise -- In the remaining cases we may not push + = takeWhileOneShot alts_type -- evaluation of the scrutinee in where alts_type = foldr1 andArityType [arityType env rhs | (_,_,rhs) <- alts] @@ -938,7 +1037,7 @@ arityType env (Let (Rec prs) e) arityType env (Tick t e) | not (tickishIsCode t) = arityType env e -arityType _ _ = vanillaArityType +arityType _ _ = topArityType {- Note [Eta-expansion and join points] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -973,12 +1072,12 @@ So we do this: body of the let. * Dually, when we come to a /call/ of a join point, just no-op - by returning botArityType, the bottom element of ArityType, + by returning ABot, the bottom element of ArityType, which so that: bot `andArityType` x = x * This works if the join point is bound in the expression we are taking the arityType of. But if it's bound further out, it makes - no sense to say that (say) the arityType of (j False) is ABot 0. + no sense to say that (say) the arityType of (j False) is ABot. Bad things happen. So we keep track of the in-scope join-point Ids in ae_join. @@ -997,12 +1096,12 @@ idArityType :: Id -> ArityType idArityType v | strict_sig <- idStrictness v , not $ isTopSig strict_sig - , (ds, res) <- splitStrictSig strict_sig + , (ds, div) <- splitStrictSig strict_sig , let arity = length ds - = if isDeadEndDiv res then ABot arity - else ATop (take arity one_shots) + -- Every strictness signature admits an arity signature! + = AT (take arity one_shots) div | otherwise - = ATop (take (idArity v) one_shots) + = AT (take (idArity v) one_shots) topDiv where one_shots :: [OneShotInfo] -- One-shot-ness derived from the type one_shots = typeArity (idType v) @@ -1111,13 +1210,13 @@ Consider foo = \x. case x of True -> (\s{os}. blah) |> co False -> wubble -We'll get an ArityType for foo of (ATop [NoOneShot,OneShot]). +We'll get an ArityType for foo of \?1.T. Then we want to eta-expand to foo = \x. (\eta{os}. (case x of ...as before...) eta) |> some_co That 'eta' binder is fresh, and we really want it to have the -one-shot flag from the inner \s{osf}. By expanding with the +one-shot flag from the inner \s{os}. By expanding with the ArityType gotten from analysing the RHS, we achieve this neatly. This makes a big difference to the one-shot monad trick; @@ -1137,8 +1236,8 @@ see Note [The one-shot state monad trick] in GHC.Utils.Monad. etaExpand :: Arity -> CoreExpr -> CoreExpr etaExpandAT :: ArityType -> CoreExpr -> CoreExpr -etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr -etaExpandAT at orig_expr = eta_expand (arityTypeOneShots at) orig_expr +etaExpand n orig_expr = eta_expand (replicate n NoOneShotInfo) orig_expr +etaExpandAT (AT oss _) orig_expr = eta_expand oss orig_expr -- See Note [Eta expansion with ArityType] -- etaExpand arity e = res ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -42,14 +42,14 @@ import GHC.Core import GHC.Builtin.Types.Prim( realWorldStatePrimTy ) import GHC.Builtin.Names( runRWKey ) import GHC.Types.Demand ( StrictSig(..), Demand, dmdTypeDepth, isStrictDmd - , mkClosedStrictSig, topDmd, seqDmd, botDiv ) + , mkClosedStrictSig, topDmd, seqDmd, isDeadEndDiv ) import GHC.Types.Cpr ( mkCprSig, botCpr ) import GHC.Core.Ppr ( pprCoreExpr ) import GHC.Types.Unique ( hasKey ) import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Utils -import GHC.Core.Opt.Arity ( ArityType(..), arityTypeArity, isBotArityType +import GHC.Core.Opt.Arity ( ArityType(..) , pushCoTyArg, pushCoValArg , idArityType, etaExpandAT ) import GHC.Core.SimpleOpt ( exprIsConApp_maybe, joinPointBinding_maybe, joinPointBindings_maybe ) @@ -796,8 +796,8 @@ addLetBndrInfo :: OutId -> ArityType -> Unfolding -> OutId addLetBndrInfo new_bndr new_arity_type new_unf = new_bndr `setIdInfo` info5 where - new_arity = arityTypeArity new_arity_type - is_bot = isBotArityType new_arity_type + AT oss div = new_arity_type + new_arity = length oss info1 = idInfo new_bndr `setArityInfo` new_arity @@ -816,11 +816,11 @@ addLetBndrInfo new_bndr new_arity_type new_unf = info2 -- Bottoming bindings: see Note [Bottoming bindings] - info4 | is_bot = info3 `setStrictnessInfo` bot_sig - `setCprInfo` bot_cpr - | otherwise = info3 + info4 | isDeadEndDiv div = info3 `setStrictnessInfo` bot_sig + `setCprInfo` bot_cpr + | otherwise = info3 - bot_sig = mkClosedStrictSig (replicate new_arity topDmd) botDiv + bot_sig = mkClosedStrictSig (replicate new_arity topDmd) div bot_cpr = mkCprSig new_arity botCpr -- Zap call arity info. We have used it by now (via ===================================== compiler/GHC/Core/Opt/Simplify/Utils.hs ===================================== @@ -1662,8 +1662,8 @@ tryEtaExpandRhs mode bndr rhs | Just join_arity <- isJoinId_maybe bndr = do { let (join_bndrs, join_body) = collectNBinders join_arity rhs oss = [idOneShotInfo id | id <- join_bndrs, isId id] - arity_type | exprIsDeadEnd join_body = ABot (length oss) - | otherwise = ATop oss + arity_type | exprIsDeadEnd join_body = mkBotArityType oss + | otherwise = mkTopArityType oss ; return (arity_type, rhs) } -- Note [Do not eta-expand join points] -- But do return the correct arity and bottom-ness, because ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -65,6 +65,7 @@ import Data.Function import Data.List (find, sortBy, sort) import qualified Data.Map as Map import qualified Data.Set as Set +import Data.Word (Word64) --Qualified import so we can define a Semigroup instance -- but it doesn't clash with Outputable.<> @@ -729,6 +730,77 @@ Names (e.g. the ifName field of a IfaceDecl) and non-binding (e.g. the ifInstCls field of a IfaceClsInst): only in the non-binding case should we include the fingerprint; in the binding case we shouldn't since it is merely the name of the thing that we are currently fingerprinting. + + +Note [Fingerprinting recursive groups] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +The fingerprinting of a single recursive group is a rather subtle affair, as +seen in #18733. + +How not to fingerprint +---------------------- + +Prior to fixing #18733 we used the following (flawed) scheme to fingerprint a +group in hash environment `hash_env0`: + + 1. extend hash_env0, giving each declaration in the group the fingerprint 0 + 2. use this environment to hash the declarations' ABIs, resulting in + group_fingerprint + 3. produce the final hash environment by extending hash_env0, mapping each + declaration of the group to group_fingerprint + +However, this is wrong. Consider, for instance, a program like: + + data A = ARecu B | ABase String deriving (Show) + data B = BRecu A | BBase Int deriving (Show) + + info :: B + info = BBase 1 + +A consequence of (3) is that A and B will have the same fingerprint. This means +that if the user changes `info` to: + + info :: A + info = ABase "hello" + +The program's ABI fingerprint will not change despite `info`'s type, and +therefore ABI, being clearly different. + +However, the incorrectness doesn't end there: (1) means that all recursive +occurrences of names within the group will be given the same fingerprint. This +means that the group's fingerprint won't change if we change an occurrence of A +to B. + +Surprisingly, this bug (#18733) lurked for many years before being uncovered. + +How we now fingerprint +---------------------- + +As seen above, the fingerprinting function must ensure that a groups +fingerprint captures the structure of within-group occurrences. The scheme that +we use is: + + 0. To ensure determinism, sort the declarations into a stable order by + declaration name + + 1. Extend hash_env0, giving each declaration in the group a sequential + fingerprint (e.g. 0, 1, 2, ...). + + 2. Use this environment to hash the declarations' ABIs, resulting in + group_fingerprint. + + Since we included the sequence number in step (1) programs identical up to + transposition of recursive occurrences are distinguisable, avoiding the + second issue mentioned above. + + 3. Produce the final environment by extending hash_env, mapping each + declaration of the group to the hash of (group_fingerprint, i), where + i is the position of the declaration in the stable ordering. + + Including i in the hash ensures that the first issue noted above is + avoided. + -} -- | Add fingerprints for top-level declarations to a 'ModIface'. @@ -854,18 +926,27 @@ addFingerprints hsc_env iface0 return (env', (hash,decl) : decls_w_hashes) fingerprint_group (local_env, decls_w_hashes) (CyclicSCC abis) - = do let decls = map abiDecl abis + = do let stable_abis = sortBy cmp_abiNames abis + stable_decls = map abiDecl stable_abis local_env1 <- foldM extend_hash_env local_env - (zip (repeat fingerprint0) decls) + (zip (map mkRecFingerprint [0..]) stable_decls) + -- See Note [Fingerprinting recursive groups] let hash_fn = mk_put_name local_env1 -- pprTrace "fingerprinting" (ppr (map ifName decls) ) $ do - let stable_abis = sortBy cmp_abiNames abis -- put the cycle in a canonical order hash <- computeFingerprint hash_fn stable_abis - let pairs = zip (repeat hash) decls + let pairs = zip (map (bumpFingerprint hash) [0..]) stable_decls + -- See Note [Fingerprinting recursive groups] local_env2 <- foldM extend_hash_env local_env pairs return (local_env2, pairs ++ decls_w_hashes) + -- Make a fingerprint from the ordinal position of a binding in its group. + mkRecFingerprint :: Word64 -> Fingerprint + mkRecFingerprint i = Fingerprint 0 i + + bumpFingerprint :: Fingerprint -> Word64 -> Fingerprint + bumpFingerprint fp n = fingerprintFingerprints [ fp, mkRecFingerprint n ] + -- we have fingerprinted the whole declaration, but we now need -- to assign fingerprints to all the OccNames that it binds, to -- use when referencing those OccNames in later declarations. @@ -884,7 +965,8 @@ addFingerprints hsc_env iface0 -- when calculating fingerprints, we always need to use canonical -- ordering for lists of things. In particular, the mi_deps has various -- lists of modules and suchlike, so put these all in canonical order: - let sorted_deps = sortDependencies (mi_deps iface0) + let sorted_deps :: Dependencies + sorted_deps = sortDependencies (mi_deps iface0) -- The export hash of a module depends on the orphan hashes of the -- orphan modules below us in the dependency tree. This is the way @@ -971,7 +1053,8 @@ addFingerprints hsc_env iface0 -- -- put the declarations in a canonical order, sorted by OccName - let sorted_decls = Map.elems $ Map.fromList $ + let sorted_decls :: [(Fingerprint, IfaceDecl)] + sorted_decls = Map.elems $ Map.fromList $ [(getOccName d, e) | e@(_, d) <- decls_w_hashes] -- the flag hash depends on: ===================================== includes/RtsAPI.h ===================================== @@ -58,6 +58,9 @@ typedef struct CapabilityPublic_ { StgRegTable r; } CapabilityPublic; +/* N.B. this needs the Capability declaration above. */ +#include "rts/EventLogWriter.h" + /* ---------------------------------------------------------------------------- RTS configuration settings, for passing to hs_init_ghc() ------------------------------------------------------------------------- */ @@ -566,6 +569,16 @@ void rts_resume (PauseToken *pauseToken); // Returns true if the rts is paused. See rts_pause() and rts_resume(). bool rts_isPaused(void); +// List all live threads. The RTS must be paused and this must be called on the +// same thread that called rts_pause(). +typedef void (*ListThreadsCb)(void *user, StgTSO *); +void rts_listThreads(ListThreadsCb cb, void *user); + +// List all non-thread GC roots. The RTS must be paused and this must be called +// on the same thread that called rts_pause(). +typedef void (*ListRootsCb)(void *user, StgClosure *); +void rts_listMiscRoots(ListRootsCb cb, void *user); + /* * The RTS allocates some thread-local data when you make a call into * Haskell using one of the rts_eval() functions. This data is not ===================================== includes/rts/EventLogWriter.h ===================================== @@ -68,3 +68,8 @@ bool startEventLogging(const EventLogWriter *writer); * Stop event logging and destroy the current EventLogWriter. */ void endEventLogging(void); + +/* + * Flush the eventlog. cap can be NULL if one is not held. + */ +void flushEventLog(Capability **cap); ===================================== libraries/base/Debug/Trace.hs ===================================== @@ -37,6 +37,7 @@ module Debug.Trace ( -- $eventlog_tracing traceEvent, traceEventIO, + flushEventLog, -- * Execution phase markers -- $markers @@ -319,3 +320,11 @@ traceMarkerIO :: String -> IO () traceMarkerIO msg = GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> case traceMarker# p s of s' -> (# s', () #) + +-- | Immediately flush the event log, if enabled. +-- +-- @since 4.15.0.0 +flushEventLog :: IO () +flushEventLog = c_flushEventLog nullPtr + +foreign import ccall "flushEventLog" c_flushEventLog :: Ptr () -> IO () ===================================== rts/Capability.c ===================================== @@ -23,6 +23,7 @@ #include "Schedule.h" #include "Sparks.h" #include "Trace.h" +#include "eventlog/EventLog.h" // for flushLocalEventsBuf #include "sm/GC.h" // for gcWorkerThread() #include "STM.h" #include "RtsUtils.h" @@ -982,6 +983,10 @@ yieldCapability debugTrace(DEBUG_nonmoving_gc, "Flushing update remembered set blocks..."); break; + case SYNC_FLUSH_EVENT_LOG: + flushLocalEventsBuf(cap); + break; + default: break; } ===================================== rts/Capability.h ===================================== @@ -267,7 +267,8 @@ typedef enum { SYNC_OTHER, SYNC_GC_SEQ, SYNC_GC_PAR, - SYNC_FLUSH_UPD_REM_SET + SYNC_FLUSH_UPD_REM_SET, + SYNC_FLUSH_EVENT_LOG } SyncType; // ===================================== rts/RtsAPI.c ===================================== @@ -15,6 +15,7 @@ #include "Prelude.h" #include "Schedule.h" #include "Capability.h" +#include "StableName.h" #include "StablePtr.h" #include "Threads.h" #include "Weak.h" @@ -809,6 +810,46 @@ static void assert_isPausedOnMyTask(const char *functionName) } } +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listThreads"); + + // The rts is paused and can only be resumed by the current thread. Hence it + // is safe to read global thread data. + + for (uint32_t g=0; g < RtsFlags.GcFlags.generations; g++) { + StgTSO *tso = generations[g].threads; + while (tso != END_TSO_QUEUE) { + cb(user, tso); + tso = tso->global_link; + } + } +} + +struct list_roots_ctx { + ListRootsCb cb; + void *user; +}; + +// This is an evac_fn. +static void list_roots_helper(void *user, StgClosure **p) { + struct list_roots_ctx *ctx = (struct list_roots_ctx *) user; + ctx->cb(ctx->user, *p); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb, void *user) +{ + assert_isPausedOnMyTask("rts_listMiscRoots"); + + struct list_roots_ctx ctx; + ctx.cb = cb; + ctx.user = user; + + threadStableNameTable(&list_roots_helper, (void *)&ctx); + threadStablePtrTable(&list_roots_helper, (void *)&ctx); +} #else PauseToken GNU_ATTRIBUTE(__noreturn__) @@ -833,6 +874,18 @@ bool rts_isPaused() "multithreaded RTS."); return false; } + +// See RtsAPI.h +void rts_listThreads(ListThreadsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listThreads is only possible for multithreaded RTS."); +} + +// See RtsAPI.h +void rts_listMiscRoots (ListRootsCb cb STG_UNUSED, void *user STG_UNUSED) +{ + errorBelch("Warning: rts_listMiscRoots is only possible for multithreaded RTS."); +} #endif void rts_done (void) ===================================== rts/RtsSymbols.c ===================================== @@ -594,6 +594,7 @@ SymI_HasProto(__word_encodeFloat) \ SymI_HasProto(stg_atomicallyzh) \ SymI_HasProto(barf) \ + SymI_HasProto(flushEventLog) \ SymI_HasProto(deRefStablePtr) \ SymI_HasProto(debugBelch) \ SymI_HasProto(errorBelch) \ ===================================== rts/Schedule.c ===================================== @@ -2070,7 +2070,7 @@ forkProcess(HsStablePtr *entry stopTimer(); // See #4074 #if defined(TRACING) - flushEventLog(); // so that child won't inherit dirty file buffers + flushAllCapsEventsBufs(); // so that child won't inherit dirty file buffers #endif pid = fork(); ===================================== rts/Trace.c ===================================== @@ -118,10 +118,10 @@ void resetTracing (void) restartEventLogging(); } -void flushTrace (void) +void flushTrace () { if (eventlog_enabled) { - flushEventLog(); + flushEventLog(NULL); } } ===================================== rts/Trace.h ===================================== @@ -319,7 +319,6 @@ void traceConcSweepEnd(void); void traceConcUpdRemSetFlush(Capability *cap); void traceNonmovingHeapCensus(uint32_t log_blk_size, const struct NonmovingAllocCensus *census); - void flushTrace(void); #else /* !TRACING */ ===================================== rts/eventlog/EventLog.c ===================================== @@ -16,6 +16,7 @@ #include "RtsUtils.h" #include "Stats.h" #include "EventLog.h" +#include "Schedule.h" #include #include @@ -270,8 +271,8 @@ stopEventLogWriter(void) } } -void -flushEventLog(void) +static void +flushEventLogWriter(void) { if (event_log_writer != NULL && event_log_writer->flushEventLog != NULL) { @@ -1484,7 +1485,7 @@ void printAndClearEventBuf (EventsBuf *ebuf) "printAndClearEventLog: could not flush event log\n" ); resetEventsBuf(ebuf); - flushEventLog(); + flushEventLogWriter(); return; } @@ -1566,6 +1567,40 @@ void postEventType(EventsBuf *eb, EventType *et) postInt32(eb, EVENT_ET_END); } +void flushLocalEventsBuf(Capability *cap) +{ + EventsBuf *eb = &capEventBuf[cap->no]; + printAndClearEventBuf(eb); +} + +// Flush all capabilities' event buffers when we already hold all capabilities. +// Used during forkProcess. +void flushAllCapsEventsBufs() +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + + for (unsigned int i=0; i < n_capabilities; i++) { + flushLocalEventsBuf(capabilities[i]); + } + flushEventLogWriter(); +} + +void flushEventLog(Capability **cap USED_IF_THREADS) +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + +#if defined(THREADED_RTS) + Task *task = getMyTask(); + stopAllCapabilitiesWith(cap, task, SYNC_FLUSH_EVENT_LOG); + releaseAllCapabilities(n_capabilities, cap ? *cap : NULL, task); +#endif + flushEventLogWriter(); +} + #else enum EventLogStatus eventLogStatus(void) @@ -1579,4 +1614,6 @@ bool startEventLogging(const EventLogWriter *writer STG_UNUSED) { void endEventLogging(void) {} +void flushEventLog(Capability **cap STG_UNUSED) {} + #endif /* TRACING */ ===================================== rts/eventlog/EventLog.h ===================================== @@ -28,8 +28,10 @@ void initEventLogging(void); void restartEventLogging(void); void freeEventLogging(void); void abortEventLogging(void); // #4512 - after fork child needs to abort -void flushEventLog(void); // event log inherited from parent void moreCapEventBufs (uint32_t from, uint32_t to); +void flushLocalEventsBuf(Capability *cap); +void flushAllCapsEventsBufs(void); +void flushAllEventsBufs(Capability *cap); /* * Post a scheduler event to the capability's event buffer (an event @@ -175,6 +177,9 @@ void postNonmovingHeapCensus(int log_blk_size, #else /* !TRACING */ +INLINE_HEADER void flushLocalEventsBuf(Capability *cap STG_UNUSED) +{ /* nothing */ } + INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, EventTypeNum tag STG_UNUSED, StgThreadID id STG_UNUSED, ===================================== testsuite/tests/arityanal/should_compile/T18870.hs ===================================== @@ -0,0 +1,12 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18870 where + +import GHC.Exts + +-- This function should not lead to an "Exciting arity" DEBUG message. +-- It should only do one round of fixed-point iteration to conclude that it has +-- arity 2. +f :: [a] -> a -> a +f [] = id +f (x:xs) = oneShot (\_ -> f xs x) ===================================== testsuite/tests/arityanal/should_compile/T18937.hs ===================================== @@ -0,0 +1,8 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +module T18937 where + +f :: [Int] -> Int -> Int +f [] = id +f (x:xs) = let y = sum [0..x] + in \z -> f xs (y + z) ===================================== testsuite/tests/arityanal/should_compile/all.T ===================================== @@ -19,3 +19,5 @@ test('Arity16', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dn # Regression tests test('T18793', [ only_ways(['optasm']), grep_errmsg('Arity=') ], compile, ['-dno-typeable-binds -ddump-simpl -dppr-cols=99999 -dsuppress-uniques']) +test('T18870', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) +test('T18937', [ only_ways(['optasm']) ], compile, ['-ddebug-output']) ===================================== testsuite/tests/driver/T18733/Library1.hs ===================================== @@ -0,0 +1,7 @@ +module Library where + +data A = ARecu B | ABase String deriving (Show) +data B = BRecu A | BBase Int deriving (Show) + +info :: B +info = BBase 1 ===================================== testsuite/tests/driver/T18733/Library2.hs ===================================== @@ -0,0 +1,7 @@ +module Library where + +data A = ARecu B | ABase String deriving (Show) +data B = BRecu A | BBase Int deriving (Show) + +info :: A +info = ABase "Hello" ===================================== testsuite/tests/driver/T18733/Main.hs ===================================== @@ -0,0 +1,5 @@ +module Main where + +import Library + +main = putStrLn $ show info ===================================== testsuite/tests/driver/T18733/Makefile ===================================== @@ -0,0 +1,12 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +T18733: + cp Library1.hs Library.hs + '$(TEST_HC)' -v0 -o Main Library.hs Main.hs + ./Main + + cp Library2.hs Library.hs + '$(TEST_HC)' -v0 -o Main Library.hs Main.hs + ./Main ===================================== testsuite/tests/driver/T18733/T18733.stdout ===================================== @@ -0,0 +1,2 @@ +BBase 1 +ABase "Hello" ===================================== testsuite/tests/driver/T18733/all.T ===================================== @@ -0,0 +1,2 @@ +srcs = ['Library1.hs', 'Library2.hs', 'Main.hs'] +test('T18733', extra_files(srcs), makefile_test, []) ===================================== testsuite/tests/rts/pause-resume/all.T ===================================== @@ -18,3 +18,8 @@ test('pause_and_use_rts_api', , extra_files(['pause_resume.c','pause_resume.h']) ], multi_compile_and_run, ['pause_and_use_rts_api', [('pause_resume.c','')], '']) +test('list_threads_and_misc_roots', + [ only_ways(['threaded1', 'threaded2']) + , extra_files(['list_threads_and_misc_roots_c.c','list_threads_and_misc_roots_c.h']) + ], + multi_compile_and_run, ['list_threads_and_misc_roots', [('list_threads_and_misc_roots_c.c','')], '']) \ No newline at end of file ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots.hs ===================================== @@ -0,0 +1,6 @@ + +foreign import ccall safe "list_threads_and_misc_roots_c.h checkGcRoots" + checkGcRoots :: IO () + +main :: IO () +main = checkGcRoots ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.c ===================================== @@ -0,0 +1,54 @@ + +#include "list_threads_and_misc_roots_c.h" + +static int tsoCount = 0; +static StgTSO** tsos; + +static int miscRootsCount = 0; +static StgClosure** miscRoots; + +void collectTSOsCallback(void *user, StgTSO* tso){ + tsoCount++; + tsos = realloc(tsos, sizeof(StgTSO*) * tsoCount); + tsos[tsoCount - 1] = tso; +} + +void collectMiscRootsCallback(void *user, StgClosure* closure){ + miscRootsCount++; + miscRoots = realloc(miscRoots, sizeof(StgClosure*) * miscRootsCount); + miscRoots[miscRootsCount - 1] = closure; +} + +void checkGcRoots(void) +{ + PauseToken * token = rts_pause(); + + // Check TSO collection. + rts_listThreads(&collectTSOsCallback, NULL); + for (int i = 0; i < tsoCount; i++) + { + StgTSO *tso = UNTAG_CLOSURE(tsos[i]); + if (get_itbl(tso)->type != TSO) + { + fprintf(stderr, "tso returned a non-TSO type %zu at index %i\n", + tso->header.info->type, + i); + exit(1); + } + } + + // Check misc GC roots collection. + rts_listMiscRoots(&collectMiscRootsCallback, NULL); + for (int i = 0; i < miscRootsCount; i++) + { + StgClosure *root = UNTAG_CLOSURE(miscRoots[i]); + if (get_itbl(root)->type == TSO) + { + fprintf(stderr, "rts_listThreads unexpectedly returned an TSO type at index %i (TSO=%zu)\n", i, TSO); + exit(1); + } + } + + + rts_resume(token); +} ===================================== testsuite/tests/rts/pause-resume/list_threads_and_misc_roots_c.h ===================================== @@ -0,0 +1,5 @@ + +#include "Rts.h" +#include "RtsAPI.h" + +void checkGcRoots(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0909c9a8242aa2928ccf59c207c9315aaec8a3f...aaaa833b4d1db288b357f6c1c4bea34a6636f5bf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c0909c9a8242aa2928ccf59c207c9315aaec8a3f...aaaa833b4d1db288b357f6c1c4bea34a6636f5bf 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 Sat Nov 14 18:25:33 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 14 Nov 2020 13:25:33 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: nativeGen/dwarf: Fix procedure end addresses Message-ID: <5fb0211d8f0b1_43133fa6aeb01578595887@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 59589b71 by Ben Gamari at 2020-11-14T13:25:21-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - e0b50fd6 by Ben Gamari at 2020-11-14T13:25:21-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - 7d25fe65 by Ben Gamari at 2020-11-14T13:25:21-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - 0535c5ca by Ben Gamari at 2020-11-14T13:25:21-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - 946e7fe3 by Ryan Scott at 2020-11-14T13:25:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 6c5decdc by Ryan Scott at 2020-11-14T13:25:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - d4288977 by Moritz Angermann at 2020-11-14T13:25:22-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - 6382a207 by Ben Gamari at 2020-11-14T13:25:22-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/501a7ec12224d2d8c77ad8df055f5dbd1627752c...6382a207861637ee13f876a0eff9d5f669957dfb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/501a7ec12224d2d8c77ad8df055f5dbd1627752c...6382a207861637ee13f876a0eff9d5f669957dfb 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 Sun Nov 15 01:15:45 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 14 Nov 2020 20:15:45 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: nativeGen/dwarf: Fix procedure end addresses Message-ID: <5fb08141b5c51_43133fa699b41a0c647478@gitlab.haskell.org.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 0bb794ae by Ben Gamari at 2020-11-14T20:15:37-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - b1a5a3ac by Ben Gamari at 2020-11-14T20:15:37-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - 674c6aa9 by Ben Gamari at 2020-11-14T20:15:37-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - 4648a12f by Ben Gamari at 2020-11-14T20:15:37-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - 10c8f2e6 by Ryan Scott at 2020-11-14T20:15:37-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 4842d95a by Ryan Scott at 2020-11-14T20:15:37-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 76f54f42 by Moritz Angermann at 2020-11-14T20:15:38-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - cd788794 by Ben Gamari at 2020-11-14T20:15:39-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6382a207861637ee13f876a0eff9d5f669957dfb...cd78879414e78d0462b762ad10b62d90ca826a98 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6382a207861637ee13f876a0eff9d5f669957dfb...cd78879414e78d0462b762ad10b62d90ca826a98 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 Sun Nov 15 08:35:53 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 15 Nov 2020 03:35:53 -0500 Subject: [Git][ghc/ghc][master] 4 commits: nativeGen/dwarf: Fix procedure end addresses Message-ID: <5fb0e86967dfe_43133fa6cd3181bc67234c@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - 9 changed files: - .gitlab-ci.yml - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - docs/users_guide/debug-info.rst Changes: ===================================== .gitlab-ci.yml ===================================== @@ -742,6 +742,15 @@ release-x86_64-linux-deb10: <<: *release extends: .build-x86_64-linux-deb10 +release-x86_64-linux-deb10-dwarf: + <<: *release + extends: .build-x86_64-linux-deb10 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + TEST_ENV: "x86_64-linux-deb10-dwarf" + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz" + ################################# # x86_64-linux-ubuntu 20.04 ################################# @@ -857,7 +866,7 @@ release-x86_64-linux-centos7: # x86_64-linux-fedora27 ################################# -validate-x86_64-linux-fedora27: +.build-x86_64-linux-fedora27: extends: .validate-linux stage: full-build image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora27:$DOCKER_REV" @@ -866,7 +875,6 @@ validate-x86_64-linux-fedora27: LLC: /bin/false OPT: /bin/false TEST_ENV: "x86_64-linux-fedora27" - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" cache: key: linux-x86_64-fedora27 artifacts: @@ -875,6 +883,20 @@ validate-x86_64-linux-fedora27: # longer. expire_in: 8 week +validate-x86_64-linux-fedora27: + extends: .build-x86_64-linux-fedora27 + variables: + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" + +release-x86_64-linux-fedora27-dwarf: + <<: *release + extends: .build-x86_64-linux-fedora27 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux-dwarf.tar.xz" + TEST_ENV: "x86_64-linux-fedora27-dwarf" + ############################################################ # Validation via Pipelines (Windows) ############################################################ ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -44,6 +44,7 @@ module GHC.Cmm.CLabel ( mkAsmTempLabel, mkAsmTempDerivedLabel, mkAsmTempEndLabel, + mkAsmTempProcEndLabel, mkAsmTempDieLabel, mkDirty_MUT_VAR_Label, @@ -755,6 +756,10 @@ mkAsmTempDerivedLabel = AsmTempDerivedLabel mkAsmTempEndLabel :: CLabel -> CLabel mkAsmTempEndLabel l = mkAsmTempDerivedLabel l (fsLit "_end") +-- | A label indicating the end of a procedure. +mkAsmTempProcEndLabel :: CLabel -> CLabel +mkAsmTempProcEndLabel l = mkAsmTempDerivedLabel l (fsLit "_proc_end") + -- | Construct a label for a DWARF Debug Information Entity (DIE) -- describing another symbol. mkAsmTempDieLabel :: CLabel -> CLabel ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -1187,9 +1187,10 @@ initNCGConfig dflags this_mod = NCGConfig ArchX86 -> v _ -> Nothing - , ncgDwarfEnabled = debugLevel dflags > 0 + , ncgDwarfEnabled = debugLevel dflags > 0 , ncgDwarfUnwindings = debugLevel dflags >= 1 - , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. , ncgExposeInternalSymbols = gopt Opt_ExposeInternalSymbols dflags + , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. + , ncgDwarfSourceNotes = debugLevel dflags >= 3 -- We produce GHC-specific source-note DIEs only with -g3 } ===================================== compiler/GHC/CmmToAsm/Config.hs ===================================== @@ -40,6 +40,7 @@ data NCGConfig = NCGConfig , ncgDwarfUnwindings :: !Bool -- ^ Enable unwindings , ncgDwarfStripBlockInfo :: !Bool -- ^ Strip out block information from generated Dwarf , ncgExposeInternalSymbols :: !Bool -- ^ Expose symbol table entries for internal symbols + , ncgDwarfSourceNotes :: !Bool -- ^ Enable GHC-specific source note DIEs } -- | Return Word size ===================================== compiler/GHC/CmmToAsm/Dwarf.hs ===================================== @@ -45,7 +45,7 @@ dwarfGen config modLoc us blocks = do | otherwise = dbg compPath <- getCurrentDirectory let lowLabel = dblCLabel $ head procs - highLabel = mkAsmTempEndLabel $ dblCLabel $ last procs + highLabel = mkAsmTempProcEndLabel $ dblCLabel $ last procs dwarfUnit = DwarfCompileUnit { dwChildren = map (procToDwarf config) (map stripBlocks procs) , dwName = fromMaybe "" (ml_hs_file modLoc) @@ -99,10 +99,10 @@ dwarfGen config modLoc us blocks = do -- scattered in the final binary. Without split sections, we could make a -- single arange based on the first/last proc. mkDwarfARange :: DebugBlock -> DwarfARange -mkDwarfARange proc = DwarfARange start end +mkDwarfARange proc = DwarfARange lbl end where - start = dblCLabel proc - end = mkAsmTempEndLabel start + lbl = dblCLabel proc + end = mkAsmTempProcEndLabel lbl -- | Header for a compilation unit, establishing global format -- parameters @@ -176,7 +176,7 @@ parent, B. -- | Generate DWARF info for a procedure debug block procToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo procToDwarf config prc - = DwarfSubprogram { dwChildren = map blockToDwarf (dblBlocks prc) + = DwarfSubprogram { dwChildren = map (blockToDwarf config) (dblBlocks prc) , dwName = case dblSourceTick prc of Just s at SourceNote{} -> sourceName s _otherwise -> show (dblLabel prc) @@ -195,14 +195,17 @@ procToDwarf config prc goodParent _ = True -- | Generate DWARF info for a block -blockToDwarf :: DebugBlock -> DwarfInfo -blockToDwarf blk - = DwarfBlock { dwChildren = concatMap tickToDwarf (dblTicks blk) - ++ map blockToDwarf (dblBlocks blk) +blockToDwarf :: NCGConfig -> DebugBlock -> DwarfInfo +blockToDwarf config blk + = DwarfBlock { dwChildren = map (blockToDwarf config) (dblBlocks blk) ++ srcNotes , dwLabel = dblCLabel blk , dwMarker = marker } where + srcNotes + | ncgDwarfSourceNotes config = concatMap tickToDwarf (dblTicks blk) + | otherwise = [] + marker | Just _ <- dblPosition blk = Just $ mkAsmTempLabel $ dblLabel blk | otherwise = Nothing -- block was optimized out ===================================== compiler/GHC/CmmToAsm/Dwarf/Constants.hs ===================================== @@ -48,7 +48,7 @@ dW_TAG_ghc_src_note = 0x5b00 -- * Dwarf attributes dW_AT_name, dW_AT_stmt_list, dW_AT_low_pc, dW_AT_high_pc, dW_AT_language, dW_AT_comp_dir, dW_AT_producer, dW_AT_external, dW_AT_frame_base, - dW_AT_use_UTF8, dW_AT_MIPS_linkage_name :: Word + dW_AT_use_UTF8, dW_AT_linkage_name :: Word dW_AT_name = 0x03 dW_AT_stmt_list = 0x10 dW_AT_low_pc = 0x11 @@ -59,7 +59,7 @@ dW_AT_producer = 0x25 dW_AT_external = 0x3f dW_AT_frame_base = 0x40 dW_AT_use_UTF8 = 0x53 -dW_AT_MIPS_linkage_name = 0x2007 +dW_AT_linkage_name = 0x6e -- * Custom DWARF attributes -- Chosen a more or less random section of the vendor-extensible region ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -105,7 +105,7 @@ pprAbbrevDecls platform haveDebugLine = -- DwAbbrSubprogramWithParent subprogramAttrs = [ (dW_AT_name, dW_FORM_string) - , (dW_AT_MIPS_linkage_name, dW_FORM_string) + , (dW_AT_linkage_name, dW_FORM_string) , (dW_AT_external, dW_FORM_flag) , (dW_AT_low_pc, dW_FORM_addr) , (dW_AT_high_pc, dW_FORM_addr) @@ -190,7 +190,7 @@ pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) $$ pprWord platform (pdoc platform label) - $$ pprWord platform (pdoc platform $ mkAsmTempEndLabel label) + $$ pprWord platform (pdoc platform $ mkAsmTempProcEndLabel label) $$ pprByte 1 $$ pprByte dW_OP_call_frame_cfa $$ parentValue @@ -354,7 +354,7 @@ pprFrameProc :: Platform -> CLabel -> UnwindTable -> DwarfFrameProc -> SDoc pprFrameProc platform frameLbl initUw (DwarfFrameProc procLbl hasInfo blocks) = let fdeLabel = mkAsmTempDerivedLabel procLbl (fsLit "_fde") fdeEndLabel = mkAsmTempDerivedLabel procLbl (fsLit "_fde_end") - procEnd = mkAsmTempEndLabel procLbl + procEnd = mkAsmTempProcEndLabel procLbl ifInfo str = if hasInfo then text str else empty -- see [Note: Info Offset] in vcat [ whenPprDebug $ text "# Unwinding for" <+> pdoc platform procLbl <> colon ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -93,8 +93,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = pprProcLabel config lbl $$ pprLabel platform lbl $$ -- blocks guaranteed not null, so label needed vcat (map (pprBasicBlock config top_info) blocks) $$ - (if ncgDwarfEnabled config - then pdoc platform (mkAsmTempEndLabel lbl) <> char ':' else empty) $$ + ppWhen (ncgDwarfEnabled config) (pprBlockEndLabel platform lbl $$ pprProcEndLabel platform lbl) $$ pprSizeDecl platform lbl Just (CmmStaticsRaw info_lbl _) -> @@ -105,6 +104,7 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = then pdoc platform (mkDeadStripPreventer info_lbl) <> char ':' else empty) $$ vcat (map (pprBasicBlock config top_info) blocks) $$ + ppWhen (ncgDwarfEnabled config) (pprProcEndLabel platform info_lbl) $$ -- above: Even the first block gets a label, because with branch-chain -- elimination, it might be the target of a goto. (if platformHasSubsectionsViaSymbols platform @@ -125,6 +125,16 @@ pprProcLabel config lbl | otherwise = empty +pprProcEndLabel :: Platform -> CLabel -- ^ Procedure name + -> SDoc +pprProcEndLabel platform lbl = + pdoc platform (mkAsmTempProcEndLabel lbl) <> char ':' + +pprBlockEndLabel :: Platform -> CLabel -- ^ Block name + -> SDoc +pprBlockEndLabel platform lbl = + pdoc platform (mkAsmTempEndLabel lbl) <> char ':' + -- | Output the ELF .size directive. pprSizeDecl :: Platform -> CLabel -> SDoc pprSizeDecl platform lbl @@ -137,9 +147,11 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) = maybe_infotable $ pprLabel platform asmLbl $$ vcat (map (pprInstr platform) instrs) $$ - (if ncgDwarfEnabled config - then pdoc (ncgPlatform config) (mkAsmTempEndLabel asmLbl) <> char ':' - else empty + ppWhen (ncgDwarfEnabled config) ( + -- Emit both end labels since this may end up being a standalone + -- top-level block + pprBlockEndLabel platform asmLbl + <> pprProcEndLabel platform asmLbl ) where asmLbl = blockLbl blockid @@ -152,10 +164,8 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) vcat (map (pprData config) info) $$ pprLabel platform infoLbl $$ c $$ - (if ncgDwarfEnabled config - then pdoc platform (mkAsmTempEndLabel infoLbl) <> char ':' - else empty - ) + ppWhen (ncgDwarfEnabled config) (pdoc platform (mkAsmTempEndLabel infoLbl) <> char ':') + -- Make sure the info table has the right .loc for the block -- coming right after it. See [Note: Info Offset] infoTableLoc = case instrs of ===================================== docs/users_guide/debug-info.rst ===================================== @@ -24,7 +24,9 @@ useable by most UNIX debugging tools. * ``-g1``: produces stack unwinding records for top-level functions (sufficient for basic backtraces) * ``-g2``: produces stack unwinding records for top-level functions as well as inner blocks (allowing more precise backtraces than with ``-g1``). - * ``-g3``: same as ``-g2``. + * ``-g3``: produces GHC-specific DWARF information for use by more + sophisticated Haskell-aware debugging tools (see :ref:`dwarf-dies` for + details) If ⟨n⟩ is omitted, level 2 is assumed. @@ -266,6 +268,7 @@ In particular GHC produces the following DWARF sections, ``.debug_arange`` Address range information necessary for efficient lookup in debug information. +.. _dwarf_dies: Debugging information entities ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/24a86f09da3426cf1006004bc45d312725280dd5...a2539650cc9c6606c6b50dd5dd96caa0209b408c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/24a86f09da3426cf1006004bc45d312725280dd5...a2539650cc9c6606c6b50dd5dd96caa0209b408c 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 Sun Nov 15 08:37:07 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 15 Nov 2020 03:37:07 -0500 Subject: [Git][ghc/ghc][master] AArch64/arm64 adjustments Message-ID: <5fb0e8b370bee_43133fa6a88a2454678674@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Linker/Dynamic.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Platform.hs - compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs - compiler/GHC/Platform/Regs.hs - compiler/ghc.cabal.in - config.sub - includes/CodeGen.Platform.hs - includes/rts/Flags.h - includes/rts/storage/GC.h - libraries/ghc-boot/GHC/Platform/ArchOS.hs - libraries/ghci/GHCi/InfoTable.hsc - llvm-targets - rts/Adjustor.c - rts/StgCRun.c - rts/linker/elf_plt_aarch64.c - rts/linker/elf_reloc.c - rts/package.conf.in - rts/rts.cabal.in - rts/sm/Storage.c - utils/llvm-targets/gen-data-layout.sh Changes: ===================================== .gitlab-ci.yml ===================================== @@ -528,6 +528,14 @@ validate-x86_64-darwin: tags: - aarch64-linux +.build-aarch64-linux-deb10-llvm: + extends: .build-aarch64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm + tags: + - aarch64-linux + validate-aarch64-linux-deb10: extends: .build-aarch64-linux-deb10 artifacts: ===================================== aclocal.m4 ===================================== @@ -118,7 +118,7 @@ AC_DEFUN([FPTOOLS_SET_PLATFORM_VARS], GHC_CONVERT_OS([$target_os], [$TargetArch], [TargetOS]) fi - GHC_LLVM_TARGET([$target_cpu],[$target_vendor],[$target_os],[LlvmTarget]) + GHC_LLVM_TARGET([$target],[$target_cpu],[$target_vendor],[$target_os],[LlvmTarget]) GHC_SELECT_FILE_EXTENSIONS([$host], [exeext_host], [soext_host]) GHC_SELECT_FILE_EXTENSIONS([$target], [exeext_target], [soext_target]) @@ -218,7 +218,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], test -z "[$]2" || eval "[$]2=\"ArchARM \$ARM_ISA \$ARM_ISA_EXT \$ARM_ABI\"" ;; aarch64) - test -z "[$]2" || eval "[$]2=ArchARM64" + test -z "[$]2" || eval "[$]2=ArchAArch64" ;; alpha) test -z "[$]2" || eval "[$]2=ArchAlpha" @@ -327,9 +327,14 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], AC_LINK_IFELSE( [AC_LANG_PROGRAM([], [__asm__ (".subsections_via_symbols");])], [AC_MSG_RESULT(yes) - TargetHasSubsectionsViaSymbols=YES - AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1], + if test x"$TargetArch" = xaarch64; then + dnl subsections via symbols is busted on arm64 + TargetHasSubsectionsViaSymbols=NO + else + TargetHasSubsectionsViaSymbols=YES + AC_DEFINE([HAVE_SUBSECTIONS_VIA_SYMBOLS],[1], [Define to 1 if Apple-style dead-stripping is supported.]) + fi ], [TargetHasSubsectionsViaSymbols=NO AC_MSG_RESULT(no)]) @@ -1976,7 +1981,7 @@ AC_MSG_CHECKING(for path to top of build tree) # `libraries/base/System/Info.hs`'s documentation. AC_DEFUN([GHC_CONVERT_CPU],[ case "$1" in - aarch64*) + aarch64*|arm64*) $2="aarch64" ;; alpha*) @@ -2058,18 +2063,19 @@ case "$1" in esac ]) -# GHC_LLVM_TARGET(target_cpu, target_vendor, target_os, llvm_target_var) +# GHC_LLVM_TARGET(target, target_cpu, target_vendor, target_os, llvm_target_var) # -------------------------------- # converts the canonicalized target into something llvm can understand AC_DEFUN([GHC_LLVM_TARGET], [ - case "$2-$3" in + llvm_target_cpu=$2 + case "$1" in *-freebsd*-gnueabihf) llvm_target_vendor="unknown" llvm_target_os="freebsd-gnueabihf" ;; - hardfloat-*eabi) + *-hardfloat-*eabi) llvm_target_vendor="unknown" - llvm_target_os="$3""hf" + llvm_target_os="$4""hf" ;; *-mingw32|*-mingw64|*-msys) llvm_target_vendor="unknown" @@ -2080,15 +2086,25 @@ AC_DEFUN([GHC_LLVM_TARGET], [ # turned into just `-linux` and fail to be found # in the `llvm-targets` file. *-android*|*-gnueabi*|*-musleabi*) - GHC_CONVERT_VENDOR([$2],[llvm_target_vendor]) - llvm_target_os="$3" + GHC_CONVERT_VENDOR([$3],[llvm_target_vendor]) + llvm_target_os="$4" + ;; + # apple is a bit about their naming scheme for + # aarch64; and clang on macOS doesn't know that + # aarch64 would be arm64. So for LLVM we'll need + # to call it arm64; while we'll refer to it internally + # as aarch64 for consistency and sanity. + aarch64-apple-*|arm64-apple-*) + llvm_target_cpu="arm64" + GHC_CONVERT_VENDOR([$3],[llvm_target_vendor]) + GHC_CONVERT_OS([$4],[$2],[llvm_target_os]) ;; *) - GHC_CONVERT_VENDOR([$2],[llvm_target_vendor]) - GHC_CONVERT_OS([$3],[$1],[llvm_target_os]) + GHC_CONVERT_VENDOR([$3],[llvm_target_vendor]) + GHC_CONVERT_OS([$4],[$2],[llvm_target_os]) ;; esac - $4="$1-$llvm_target_vendor-$llvm_target_os" + $5="$llvm_target_cpu-$llvm_target_vendor-$llvm_target_os" ]) ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -166,7 +166,7 @@ nativeCodeGen dflags this_mod modLoc h us cmms ArchSPARC64 -> panic "nativeCodeGen: No NCG for SPARC64" ArchS390X -> panic "nativeCodeGen: No NCG for S390X" ArchARM {} -> panic "nativeCodeGen: No NCG for ARM" - ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64" + ArchAArch64 -> panic "nativeCodeGen: No NCG for AArch64" ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha" ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" ArchMipsel -> panic "nativeCodeGen: No NCG for mipsel" @@ -1193,4 +1193,3 @@ initNCGConfig dflags this_mod = NCGConfig , ncgDwarfStripBlockInfo = debugLevel dflags < 2 -- We strip out block information when running with -g0 or -g1. , ncgDwarfSourceNotes = debugLevel dflags >= 3 -- We produce GHC-specific source-note DIEs only with -g3 } - ===================================== compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs ===================================== @@ -115,7 +115,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl ArchSPARC64 -> panic "trivColorable ArchSPARC64" ArchPPC_64 _ -> 15 ArchARM _ _ _ -> panic "trivColorable ArchARM" - ArchARM64 -> panic "trivColorable ArchARM64" + ArchAArch64 -> panic "trivColorable ArchAArch64" ArchAlpha -> panic "trivColorable ArchAlpha" ArchMipseb -> panic "trivColorable ArchMipseb" ArchMipsel -> panic "trivColorable ArchMipsel" @@ -146,7 +146,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus ArchSPARC64 -> panic "trivColorable ArchSPARC64" ArchPPC_64 _ -> 0 ArchARM _ _ _ -> panic "trivColorable ArchARM" - ArchARM64 -> panic "trivColorable ArchARM64" + ArchAArch64 -> panic "trivColorable ArchAArch64" ArchAlpha -> panic "trivColorable ArchAlpha" ArchMipseb -> panic "trivColorable ArchMipseb" ArchMipsel -> panic "trivColorable ArchMipsel" @@ -179,7 +179,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu ArchSPARC64 -> panic "trivColorable ArchSPARC64" ArchPPC_64 _ -> 20 ArchARM _ _ _ -> panic "trivColorable ArchARM" - ArchARM64 -> panic "trivColorable ArchARM64" + ArchAArch64 -> panic "trivColorable ArchAArch64" ArchAlpha -> panic "trivColorable ArchAlpha" ArchMipseb -> panic "trivColorable ArchMipseb" ArchMipsel -> panic "trivColorable ArchMipsel" ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -223,7 +223,7 @@ linearRegAlloc config entry_ids block_live sccs ArchSPARC64 -> panic "linearRegAlloc ArchSPARC64" ArchPPC -> go $ (frInitFreeRegs platform :: PPC.FreeRegs) ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" - ArchARM64 -> panic "linearRegAlloc ArchARM64" + ArchAArch64 -> panic "linearRegAlloc ArchAArch64" ArchPPC_64 _ -> go $ (frInitFreeRegs platform :: PPC.FreeRegs) ArchAlpha -> panic "linearRegAlloc ArchAlpha" ArchMipseb -> panic "linearRegAlloc ArchMipseb" ===================================== compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs ===================================== @@ -78,7 +78,7 @@ maxSpillSlots config = case platformArch (ncgPlatform config) of ArchSPARC -> SPARC.Instr.maxSpillSlots config ArchSPARC64 -> panic "maxSpillSlots ArchSPARC64" ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" - ArchARM64 -> panic "maxSpillSlots ArchARM64" + ArchAArch64 -> panic "maxSpillSlots ArchAArch64" ArchPPC_64 _ -> PPC.Instr.maxSpillSlots config ArchAlpha -> panic "maxSpillSlots ArchAlpha" ArchMipseb -> panic "maxSpillSlots ArchMipseb" ===================================== compiler/GHC/CmmToAsm/Reg/Target.hs ===================================== @@ -48,7 +48,7 @@ targetVirtualRegSqueeze platform ArchSPARC64 -> panic "targetVirtualRegSqueeze ArchSPARC64" ArchPPC_64 _ -> PPC.virtualRegSqueeze ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" - ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64" + ArchAArch64 -> panic "targetVirtualRegSqueeze ArchAArch64" ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha" ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" @@ -67,7 +67,7 @@ targetRealRegSqueeze platform ArchSPARC64 -> panic "targetRealRegSqueeze ArchSPARC64" ArchPPC_64 _ -> PPC.realRegSqueeze ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" - ArchARM64 -> panic "targetRealRegSqueeze ArchARM64" + ArchAArch64 -> panic "targetRealRegSqueeze ArchAArch64" ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha" ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" @@ -85,7 +85,7 @@ targetClassOfRealReg platform ArchSPARC64 -> panic "targetClassOfRealReg ArchSPARC64" ArchPPC_64 _ -> PPC.classOfRealReg ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" - ArchARM64 -> panic "targetClassOfRealReg ArchARM64" + ArchAArch64 -> panic "targetClassOfRealReg ArchAArch64" ArchAlpha -> panic "targetClassOfRealReg ArchAlpha" ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" @@ -103,7 +103,7 @@ targetMkVirtualReg platform ArchSPARC64 -> panic "targetMkVirtualReg ArchSPARC64" ArchPPC_64 _ -> PPC.mkVirtualReg ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" - ArchARM64 -> panic "targetMkVirtualReg ArchARM64" + ArchAArch64 -> panic "targetMkVirtualReg ArchAArch64" ArchAlpha -> panic "targetMkVirtualReg ArchAlpha" ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" @@ -121,7 +121,7 @@ targetRegDotColor platform ArchSPARC64 -> panic "targetRegDotColor ArchSPARC64" ArchPPC_64 _ -> PPC.regDotColor ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" - ArchARM64 -> panic "targetRegDotColor ArchARM64" + ArchAArch64 -> panic "targetRegDotColor ArchAArch64" ArchAlpha -> panic "targetRegDotColor ArchAlpha" ArchMipseb -> panic "targetRegDotColor ArchMipseb" ArchMipsel -> panic "targetRegDotColor ArchMipsel" ===================================== compiler/GHC/CmmToC.hs ===================================== @@ -1158,7 +1158,7 @@ cLoad platform expr rep bewareLoadStoreAlignment ArchMipseb = True bewareLoadStoreAlignment ArchMipsel = True bewareLoadStoreAlignment (ArchARM {}) = True - bewareLoadStoreAlignment ArchARM64 = True + bewareLoadStoreAlignment ArchAArch64 = True bewareLoadStoreAlignment ArchSPARC = True bewareLoadStoreAlignment ArchSPARC64 = True -- Pessimistically assume that they will also cause problems ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3842,8 +3842,8 @@ default_PIC platform = -- This requires PIC on AArch64, and ExternalDynamicRefs on Linux as on top -- of that. Subsequently we expect all code on aarch64/linux (and macOS) to -- be built with -fPIC. - (OSDarwin, ArchARM64) -> [Opt_PIC] - (OSLinux, ArchARM64) -> [Opt_PIC, Opt_ExternalDynamicRefs] + (OSDarwin, ArchAArch64) -> [Opt_PIC] + (OSLinux, ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs] (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release -- (1 May 2013) we need to ===================================== compiler/GHC/Linker/Dynamic.hs ===================================== @@ -179,7 +179,7 @@ linkDynLib dflags0 o_files dep_packages ++ [ Option "-undefined", Option "dynamic_lookup", Option "-single_module" ] - ++ (if platformArch platform == ArchX86_64 + ++ (if platformArch platform `elem` [ ArchX86_64, ArchAArch64 ] then [ ] else [ Option "-Wl,-read_only_relocs,suppress" ]) ++ [ Option "-install_name", Option instName ] ===================================== compiler/GHC/Linker/Static.hs ===================================== @@ -225,9 +225,9 @@ linkBinary' staticLink dflags o_files dep_units = do (platformOS platform == OSDarwin) && case platformArch platform of ArchX86 -> True - ArchX86_64 -> True - ArchARM {} -> True - ArchARM64 -> True + ArchX86_64 -> True + ArchARM {} -> True + ArchAArch64 -> True _ -> False then ["-Wl,-no_compact_unwind"] else []) @@ -339,4 +339,3 @@ exeFileName platform staticLink output_fn else "a.out" where s ext | null (takeExtension s) = s <.> ext | otherwise = s - ===================================== compiler/GHC/Platform.hs ===================================== @@ -109,7 +109,7 @@ platformOS platform = case platformArchOS platform of isARM :: Arch -> Bool isARM (ArchARM {}) = True -isARM ArchARM64 = True +isARM ArchAArch64 = True isARM _ = False -- | This predicate tells us whether the platform is 32-bit. @@ -232,4 +232,3 @@ platformSOExt platform OSDarwin -> "dylib" OSMinGW32 -> "dll" _ -> "so" - ===================================== compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs ===================================== @@ -1,10 +1,9 @@ {-# LANGUAGE CPP #-} -module GHC.Platform.ARM64 where +module GHC.Platform.AArch64 where import GHC.Prelude #define MACHREGS_NO_REGS 0 #define MACHREGS_aarch64 1 #include "../../../includes/CodeGen.Platform.hs" - ===================================== compiler/GHC/Platform/Regs.hs ===================================== @@ -1,4 +1,3 @@ - module GHC.Platform.Regs (callerSaves, activeStgRegs, haveRegBase, globalRegMaybe, freeReg) where @@ -10,7 +9,7 @@ import GHC.Platform import GHC.Platform.Reg import qualified GHC.Platform.ARM as ARM -import qualified GHC.Platform.ARM64 as ARM64 +import qualified GHC.Platform.AArch64 as AArch64 import qualified GHC.Platform.PPC as PPC import qualified GHC.Platform.S390X as S390X import qualified GHC.Platform.SPARC as SPARC @@ -26,12 +25,12 @@ callerSaves platform | platformUnregisterised platform = NoRegs.callerSaves | otherwise = case platformArch platform of - ArchX86 -> X86.callerSaves - ArchX86_64 -> X86_64.callerSaves - ArchS390X -> S390X.callerSaves - ArchSPARC -> SPARC.callerSaves - ArchARM {} -> ARM.callerSaves - ArchARM64 -> ARM64.callerSaves + ArchX86 -> X86.callerSaves + ArchX86_64 -> X86_64.callerSaves + ArchS390X -> S390X.callerSaves + ArchSPARC -> SPARC.callerSaves + ArchARM {} -> ARM.callerSaves + ArchAArch64 -> AArch64.callerSaves arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.callerSaves @@ -48,12 +47,12 @@ activeStgRegs platform | platformUnregisterised platform = NoRegs.activeStgRegs | otherwise = case platformArch platform of - ArchX86 -> X86.activeStgRegs - ArchX86_64 -> X86_64.activeStgRegs - ArchS390X -> S390X.activeStgRegs - ArchSPARC -> SPARC.activeStgRegs - ArchARM {} -> ARM.activeStgRegs - ArchARM64 -> ARM64.activeStgRegs + ArchX86 -> X86.activeStgRegs + ArchX86_64 -> X86_64.activeStgRegs + ArchS390X -> S390X.activeStgRegs + ArchSPARC -> SPARC.activeStgRegs + ArchARM {} -> ARM.activeStgRegs + ArchAArch64 -> AArch64.activeStgRegs arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.activeStgRegs @@ -65,12 +64,12 @@ haveRegBase platform | platformUnregisterised platform = NoRegs.haveRegBase | otherwise = case platformArch platform of - ArchX86 -> X86.haveRegBase - ArchX86_64 -> X86_64.haveRegBase - ArchS390X -> S390X.haveRegBase - ArchSPARC -> SPARC.haveRegBase - ArchARM {} -> ARM.haveRegBase - ArchARM64 -> ARM64.haveRegBase + ArchX86 -> X86.haveRegBase + ArchX86_64 -> X86_64.haveRegBase + ArchS390X -> S390X.haveRegBase + ArchSPARC -> SPARC.haveRegBase + ArchARM {} -> ARM.haveRegBase + ArchAArch64 -> AArch64.haveRegBase arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.haveRegBase @@ -82,12 +81,12 @@ globalRegMaybe platform | platformUnregisterised platform = NoRegs.globalRegMaybe | otherwise = case platformArch platform of - ArchX86 -> X86.globalRegMaybe - ArchX86_64 -> X86_64.globalRegMaybe - ArchS390X -> S390X.globalRegMaybe - ArchSPARC -> SPARC.globalRegMaybe - ArchARM {} -> ARM.globalRegMaybe - ArchARM64 -> ARM64.globalRegMaybe + ArchX86 -> X86.globalRegMaybe + ArchX86_64 -> X86_64.globalRegMaybe + ArchS390X -> S390X.globalRegMaybe + ArchSPARC -> SPARC.globalRegMaybe + ArchARM {} -> ARM.globalRegMaybe + ArchAArch64 -> AArch64.globalRegMaybe arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.globalRegMaybe @@ -99,15 +98,14 @@ freeReg platform | platformUnregisterised platform = NoRegs.freeReg | otherwise = case platformArch platform of - ArchX86 -> X86.freeReg - ArchX86_64 -> X86_64.freeReg - ArchS390X -> S390X.freeReg - ArchSPARC -> SPARC.freeReg - ArchARM {} -> ARM.freeReg - ArchARM64 -> ARM64.freeReg + ArchX86 -> X86.freeReg + ArchX86_64 -> X86_64.freeReg + ArchS390X -> S390X.freeReg + ArchSPARC -> SPARC.freeReg + ArchARM {} -> ARM.freeReg + ArchAArch64 -> AArch64.freeReg arch | arch `elem` [ArchPPC, ArchPPC_64 ELF_V1, ArchPPC_64 ELF_V2] -> PPC.freeReg | otherwise -> NoRegs.freeReg - ===================================== compiler/ghc.cabal.in ===================================== @@ -478,7 +478,7 @@ Library GHC.Parser.Types GHC.Platform GHC.Platform.ARM - GHC.Platform.ARM64 + GHC.Platform.AArch64 GHC.Platform.Constants GHC.Platform.NoRegs GHC.Platform.PPC ===================================== config.sub ===================================== @@ -1,8 +1,8 @@ #! /bin/sh # Configuration validation subroutine script. -# Copyright 1992-2019 Free Software Foundation, Inc. +# Copyright 1992-2020 Free Software Foundation, Inc. -timestamp='2019-01-05' +timestamp='2020-09-08' # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by @@ -67,7 +67,7 @@ Report bugs and patches to ." version="\ GNU config.sub ($timestamp) -Copyright 1992-2019 Free Software Foundation, Inc. +Copyright 1992-2020 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." @@ -124,28 +124,27 @@ case $1 in ;; *-*-*-*) basic_machine=$field1-$field2 - os=$field3-$field4 + basic_os=$field3-$field4 ;; *-*-*) # Ambiguous whether COMPANY is present, or skipped and KERNEL-OS is two # parts maybe_os=$field2-$field3 case $maybe_os in - nto-qnx* | linux-gnu* | linux-android* | linux-dietlibc \ - | linux-newlib* | linux-musl* | linux-uclibc* | uclinux-uclibc* \ + nto-qnx* | linux-* | uclinux-uclibc* \ | uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* \ | netbsd*-eabi* | kopensolaris*-gnu* | cloudabi*-eabi* \ | storm-chaos* | os2-emx* | rtmk-nova*) basic_machine=$field1 - os=$maybe_os + basic_os=$maybe_os ;; android-linux) basic_machine=$field1-unknown - os=linux-android + basic_os=linux-android ;; *) basic_machine=$field1-$field2 - os=$field3 + basic_os=$field3 ;; esac ;; @@ -154,7 +153,7 @@ case $1 in case $field1-$field2 in decstation-3100) basic_machine=mips-dec - os= + basic_os= ;; *-*) # Second component is usually, but not always the OS @@ -162,7 +161,7 @@ case $1 in # Prevent following clause from handling this valid os sun*os*) basic_machine=$field1 - os=$field2 + basic_os=$field2 ;; # Manufacturers dec* | mips* | sequent* | encore* | pc533* | sgi* | sony* \ @@ -175,11 +174,11 @@ case $1 in | microblaze* | sim | cisco \ | oki | wec | wrs | winbond) basic_machine=$field1-$field2 - os= + basic_os= ;; *) basic_machine=$field1 - os=$field2 + basic_os=$field2 ;; esac ;; @@ -191,450 +190,451 @@ case $1 in case $field1 in 386bsd) basic_machine=i386-pc - os=bsd + basic_os=bsd ;; a29khif) basic_machine=a29k-amd - os=udi + basic_os=udi ;; adobe68k) basic_machine=m68010-adobe - os=scout + basic_os=scout ;; alliant) basic_machine=fx80-alliant - os= + basic_os= ;; altos | altos3068) basic_machine=m68k-altos - os= + basic_os= ;; am29k) basic_machine=a29k-none - os=bsd + basic_os=bsd ;; amdahl) basic_machine=580-amdahl - os=sysv + basic_os=sysv ;; amiga) basic_machine=m68k-unknown - os= + basic_os= ;; amigaos | amigados) basic_machine=m68k-unknown - os=amigaos + basic_os=amigaos ;; amigaunix | amix) basic_machine=m68k-unknown - os=sysv4 + basic_os=sysv4 ;; apollo68) basic_machine=m68k-apollo - os=sysv + basic_os=sysv ;; apollo68bsd) basic_machine=m68k-apollo - os=bsd + basic_os=bsd ;; aros) basic_machine=i386-pc - os=aros + basic_os=aros ;; aux) basic_machine=m68k-apple - os=aux + basic_os=aux ;; balance) basic_machine=ns32k-sequent - os=dynix + basic_os=dynix ;; blackfin) basic_machine=bfin-unknown - os=linux + basic_os=linux ;; cegcc) basic_machine=arm-unknown - os=cegcc + basic_os=cegcc ;; convex-c1) basic_machine=c1-convex - os=bsd + basic_os=bsd ;; convex-c2) basic_machine=c2-convex - os=bsd + basic_os=bsd ;; convex-c32) basic_machine=c32-convex - os=bsd + basic_os=bsd ;; convex-c34) basic_machine=c34-convex - os=bsd + basic_os=bsd ;; convex-c38) basic_machine=c38-convex - os=bsd + basic_os=bsd ;; cray) basic_machine=j90-cray - os=unicos + basic_os=unicos ;; crds | unos) basic_machine=m68k-crds - os= + basic_os= ;; da30) basic_machine=m68k-da30 - os= + basic_os= ;; decstation | pmax | pmin | dec3100 | decstatn) basic_machine=mips-dec - os= + basic_os= ;; delta88) basic_machine=m88k-motorola - os=sysv3 + basic_os=sysv3 ;; dicos) basic_machine=i686-pc - os=dicos + basic_os=dicos ;; djgpp) basic_machine=i586-pc - os=msdosdjgpp + basic_os=msdosdjgpp ;; ebmon29k) basic_machine=a29k-amd - os=ebmon + basic_os=ebmon ;; es1800 | OSE68k | ose68k | ose | OSE) basic_machine=m68k-ericsson - os=ose + basic_os=ose ;; gmicro) basic_machine=tron-gmicro - os=sysv + basic_os=sysv ;; go32) basic_machine=i386-pc - os=go32 + basic_os=go32 ;; h8300hms) basic_machine=h8300-hitachi - os=hms + basic_os=hms ;; h8300xray) basic_machine=h8300-hitachi - os=xray + basic_os=xray ;; h8500hms) basic_machine=h8500-hitachi - os=hms + basic_os=hms ;; harris) basic_machine=m88k-harris - os=sysv3 + basic_os=sysv3 ;; - hp300) + hp300 | hp300hpux) basic_machine=m68k-hp + basic_os=hpux ;; hp300bsd) basic_machine=m68k-hp - os=bsd - ;; - hp300hpux) - basic_machine=m68k-hp - os=hpux + basic_os=bsd ;; hppaosf) basic_machine=hppa1.1-hp - os=osf + basic_os=osf ;; hppro) basic_machine=hppa1.1-hp - os=proelf + basic_os=proelf ;; i386mach) basic_machine=i386-mach - os=mach - ;; - vsta) - basic_machine=i386-pc - os=vsta + basic_os=mach ;; isi68 | isi) basic_machine=m68k-isi - os=sysv + basic_os=sysv ;; m68knommu) basic_machine=m68k-unknown - os=linux + basic_os=linux ;; magnum | m3230) basic_machine=mips-mips - os=sysv + basic_os=sysv ;; merlin) basic_machine=ns32k-utek - os=sysv + basic_os=sysv ;; mingw64) basic_machine=x86_64-pc - os=mingw64 + basic_os=mingw64 ;; mingw32) basic_machine=i686-pc - os=mingw32 + basic_os=mingw32 ;; mingw32ce) basic_machine=arm-unknown - os=mingw32ce + basic_os=mingw32ce ;; monitor) basic_machine=m68k-rom68k - os=coff + basic_os=coff ;; morphos) basic_machine=powerpc-unknown - os=morphos + basic_os=morphos ;; moxiebox) basic_machine=moxie-unknown - os=moxiebox + basic_os=moxiebox ;; msdos) basic_machine=i386-pc - os=msdos + basic_os=msdos ;; msys) basic_machine=i686-pc - os=msys + basic_os=msys ;; mvs) basic_machine=i370-ibm - os=mvs + basic_os=mvs ;; nacl) basic_machine=le32-unknown - os=nacl + basic_os=nacl ;; ncr3000) basic_machine=i486-ncr - os=sysv4 + basic_os=sysv4 ;; netbsd386) basic_machine=i386-pc - os=netbsd + basic_os=netbsd ;; netwinder) basic_machine=armv4l-rebel - os=linux + basic_os=linux ;; news | news700 | news800 | news900) basic_machine=m68k-sony - os=newsos + basic_os=newsos ;; news1000) basic_machine=m68030-sony - os=newsos + basic_os=newsos ;; necv70) basic_machine=v70-nec - os=sysv + basic_os=sysv ;; nh3000) basic_machine=m68k-harris - os=cxux + basic_os=cxux ;; nh[45]000) basic_machine=m88k-harris - os=cxux + basic_os=cxux ;; nindy960) basic_machine=i960-intel - os=nindy + basic_os=nindy ;; mon960) basic_machine=i960-intel - os=mon960 + basic_os=mon960 ;; nonstopux) basic_machine=mips-compaq - os=nonstopux + basic_os=nonstopux ;; os400) basic_machine=powerpc-ibm - os=os400 + basic_os=os400 ;; OSE68000 | ose68000) basic_machine=m68000-ericsson - os=ose + basic_os=ose ;; os68k) basic_machine=m68k-none - os=os68k + basic_os=os68k ;; paragon) basic_machine=i860-intel - os=osf + basic_os=osf ;; parisc) basic_machine=hppa-unknown - os=linux + basic_os=linux + ;; + psp) + basic_machine=mipsallegrexel-sony + basic_os=psp ;; pw32) basic_machine=i586-unknown - os=pw32 + basic_os=pw32 ;; rdos | rdos64) basic_machine=x86_64-pc - os=rdos + basic_os=rdos ;; rdos32) basic_machine=i386-pc - os=rdos + basic_os=rdos ;; rom68k) basic_machine=m68k-rom68k - os=coff + basic_os=coff ;; sa29200) basic_machine=a29k-amd - os=udi + basic_os=udi ;; sei) basic_machine=mips-sei - os=seiux + basic_os=seiux ;; sequent) basic_machine=i386-sequent - os= + basic_os= ;; sps7) basic_machine=m68k-bull - os=sysv2 + basic_os=sysv2 ;; st2000) basic_machine=m68k-tandem - os= + basic_os= ;; stratus) basic_machine=i860-stratus - os=sysv4 + basic_os=sysv4 ;; sun2) basic_machine=m68000-sun - os= + basic_os= ;; sun2os3) basic_machine=m68000-sun - os=sunos3 + basic_os=sunos3 ;; sun2os4) basic_machine=m68000-sun - os=sunos4 + basic_os=sunos4 ;; sun3) basic_machine=m68k-sun - os= + basic_os= ;; sun3os3) basic_machine=m68k-sun - os=sunos3 + basic_os=sunos3 ;; sun3os4) basic_machine=m68k-sun - os=sunos4 + basic_os=sunos4 ;; sun4) basic_machine=sparc-sun - os= + basic_os= ;; sun4os3) basic_machine=sparc-sun - os=sunos3 + basic_os=sunos3 ;; sun4os4) basic_machine=sparc-sun - os=sunos4 + basic_os=sunos4 ;; sun4sol2) basic_machine=sparc-sun - os=solaris2 + basic_os=solaris2 ;; sun386 | sun386i | roadrunner) basic_machine=i386-sun - os= + basic_os= ;; sv1) basic_machine=sv1-cray - os=unicos + basic_os=unicos ;; symmetry) basic_machine=i386-sequent - os=dynix + basic_os=dynix ;; t3e) basic_machine=alphaev5-cray - os=unicos + basic_os=unicos ;; t90) basic_machine=t90-cray - os=unicos + basic_os=unicos ;; toad1) basic_machine=pdp10-xkl - os=tops20 + basic_os=tops20 ;; tpf) basic_machine=s390x-ibm - os=tpf + basic_os=tpf ;; udi29k) basic_machine=a29k-amd - os=udi + basic_os=udi ;; ultra3) basic_machine=a29k-nyu - os=sym1 + basic_os=sym1 ;; v810 | necv810) basic_machine=v810-nec - os=none + basic_os=none ;; vaxv) basic_machine=vax-dec - os=sysv + basic_os=sysv ;; vms) basic_machine=vax-dec - os=vms + basic_os=vms + ;; + vsta) + basic_machine=i386-pc + basic_os=vsta ;; vxworks960) basic_machine=i960-wrs - os=vxworks + basic_os=vxworks ;; vxworks68) basic_machine=m68k-wrs - os=vxworks + basic_os=vxworks ;; vxworks29k) basic_machine=a29k-wrs - os=vxworks + basic_os=vxworks ;; xbox) basic_machine=i686-pc - os=mingw32 + basic_os=mingw32 ;; ymp) basic_machine=ymp-cray - os=unicos + basic_os=unicos ;; *) basic_machine=$1 - os= + basic_os= ;; esac ;; @@ -686,17 +686,17 @@ case $basic_machine in bluegene*) cpu=powerpc vendor=ibm - os=cnk + basic_os=cnk ;; decsystem10* | dec10*) cpu=pdp10 vendor=dec - os=tops10 + basic_os=tops10 ;; decsystem20* | dec20*) cpu=pdp10 vendor=dec - os=tops20 + basic_os=tops20 ;; delta | 3300 | motorola-3300 | motorola-delta \ | 3300-motorola | delta-motorola) @@ -706,7 +706,7 @@ case $basic_machine in dpx2*) cpu=m68k vendor=bull - os=sysv3 + basic_os=sysv3 ;; encore | umax | mmax) cpu=ns32k @@ -715,7 +715,7 @@ case $basic_machine in elxsi) cpu=elxsi vendor=elxsi - os=${os:-bsd} + basic_os=${basic_os:-bsd} ;; fx2800) cpu=i860 @@ -728,7 +728,7 @@ case $basic_machine in h3050r* | hiux*) cpu=hppa1.1 vendor=hitachi - os=hiuxwe2 + basic_os=hiuxwe2 ;; hp3k9[0-9][0-9] | hp9[0-9][0-9]) cpu=hppa1.0 @@ -771,36 +771,36 @@ case $basic_machine in i*86v32) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv32 + basic_os=sysv32 ;; i*86v4*) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv4 + basic_os=sysv4 ;; i*86v) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv + basic_os=sysv ;; i*86sol2) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=solaris2 + basic_os=solaris2 ;; j90 | j90-cray) cpu=j90 vendor=cray - os=${os:-unicos} + basic_os=${basic_os:-unicos} ;; iris | iris4d) cpu=mips vendor=sgi - case $os in + case $basic_os in irix*) ;; *) - os=irix4 + basic_os=irix4 ;; esac ;; @@ -811,26 +811,26 @@ case $basic_machine in *mint | mint[0-9]* | *MiNT | *MiNT[0-9]*) cpu=m68k vendor=atari - os=mint + basic_os=mint ;; news-3600 | risc-news) cpu=mips vendor=sony - os=newsos + basic_os=newsos ;; next | m*-next) cpu=m68k vendor=next - case $os in + case $basic_os in openstep*) ;; nextstep*) ;; ns2*) - os=nextstep2 + basic_os=nextstep2 ;; *) - os=nextstep3 + basic_os=nextstep3 ;; esac ;; @@ -841,12 +841,12 @@ case $basic_machine in op50n-* | op60c-*) cpu=hppa1.1 vendor=oki - os=proelf + basic_os=proelf ;; pa-hitachi) cpu=hppa1.1 vendor=hitachi - os=hiuxwe2 + basic_os=hiuxwe2 ;; pbd) cpu=sparc @@ -883,12 +883,12 @@ case $basic_machine in sde) cpu=mipsisa32 vendor=sde - os=${os:-elf} + basic_os=${basic_os:-elf} ;; simso-wrs) cpu=sparclite vendor=wrs - os=vxworks + basic_os=vxworks ;; tower | tower-32) cpu=m68k @@ -905,7 +905,7 @@ case $basic_machine in w89k-*) cpu=hppa1.1 vendor=winbond - os=proelf + basic_os=proelf ;; none) cpu=none @@ -958,11 +958,11 @@ case $cpu-$vendor in # some cases the only manufacturer, in others, it is the most popular. craynv-unknown) vendor=cray - os=${os:-unicosmp} + basic_os=${basic_os:-unicosmp} ;; c90-unknown | c90-cray) vendor=cray - os=${os:-unicos} + basic_os=${Basic_os:-unicos} ;; fx80-unknown) vendor=alliant @@ -1006,7 +1006,7 @@ case $cpu-$vendor in dpx20-unknown | dpx20-bull) cpu=rs6000 vendor=bull - os=${os:-bosx} + basic_os=${basic_os:-bosx} ;; # Here we normalize CPU types irrespective of the vendor @@ -1015,7 +1015,7 @@ case $cpu-$vendor in ;; blackfin-*) cpu=bfin - os=linux + basic_os=linux ;; c54x-*) cpu=tic54x @@ -1028,7 +1028,7 @@ case $cpu-$vendor in ;; e500v[12]-*) cpu=powerpc - os=$os"spe" + basic_os=${basic_os}"spe" ;; mips3*-*) cpu=mips64 @@ -1038,7 +1038,7 @@ case $cpu-$vendor in ;; m68knommu-*) cpu=m68k - os=linux + basic_os=linux ;; m9s12z-* | m68hcs12z-* | hcs12z-* | s12z-*) cpu=s12z @@ -1048,7 +1048,7 @@ case $cpu-$vendor in ;; parisc-*) cpu=hppa - os=linux + basic_os=linux ;; pentium-* | p5-* | k5-* | k6-* | nexgen-* | viac3-*) cpu=i586 @@ -1104,11 +1104,14 @@ case $cpu-$vendor in xscale-* | xscalee[bl]-*) cpu=`echo "$cpu" | sed 's/^xscale/arm/'` ;; + arm64-*) + cpu=aarch64 + ;; # Recognize the canonical CPU Types that limit and/or modify the # company names they are paired with. cr16-*) - os=${os:-elf} + basic_os=${basic_os:-elf} ;; crisv32-* | etraxfs*-*) cpu=crisv32 @@ -1119,7 +1122,7 @@ case $cpu-$vendor in vendor=axis ;; crx-*) - os=${os:-elf} + basic_os=${basic_os:-elf} ;; neo-tandem) cpu=neo @@ -1141,16 +1144,12 @@ case $cpu-$vendor in cpu=nsx vendor=tandem ;; - s390-*) - cpu=s390 - vendor=ibm - ;; - s390x-*) - cpu=s390x - vendor=ibm + mipsallegrexel-sony) + cpu=mipsallegrexel + vendor=sony ;; tile*-*) - os=${os:-linux-gnu} + basic_os=${basic_os:-linux-gnu} ;; *) @@ -1167,12 +1166,12 @@ case $cpu-$vendor in | am33_2.0 \ | amdgcn \ | arc | arceb \ - | arm | arm[lb]e | arme[lb] | armv* \ + | arm | arm[lb]e | arme[lb] | armv* \ | avr | avr32 \ | asmjs \ | ba \ | be32 | be64 \ - | bfin | bs2000 \ + | bfin | bpf | bs2000 \ | c[123]* | c30 | [cjt]90 | c4x \ | c8051 | clipper | craynv | csky | cydra \ | d10v | d30v | dlx | dsp16xx \ @@ -1232,6 +1231,7 @@ case $cpu-$vendor in | pyramid \ | riscv | riscv32 | riscv64 \ | rl78 | romp | rs6000 | rx \ + | s390 | s390x \ | score \ | sh | shl \ | sh[1234] | sh[24]a | sh[24]ae[lb] | sh[23]e | she[lb] | sh[lb]e \ @@ -1278,8 +1278,43 @@ esac # Decode manufacturer-specific aliases for certain operating systems. -if [ x$os != x ] +if test x$basic_os != x then + +# First recognize some ad-hoc caes, or perhaps split kernel-os, or else just +# set os. +case $basic_os in + gnu/linux*) + kernel=linux + os=`echo $basic_os | sed -e 's|gnu/linux|gnu|'` + ;; + nto-qnx*) + kernel=nto + os=`echo $basic_os | sed -e 's|nto-qnx|qnx|'` + ;; + *-*) + # shellcheck disable=SC2162 + IFS="-" read kernel os <&2 - exit 1 + # No normalization, but not necessarily accepted, that comes below. ;; esac + else # Here we handle the default operating systems that come with various machines. @@ -1533,6 +1493,7 @@ else # will signal an error saying that MANUFACTURER isn't an operating # system, and we'll never get to this point. +kernel= case $cpu-$vendor in score-*) os=elf @@ -1544,7 +1505,8 @@ case $cpu-$vendor in os=riscix1.2 ;; arm*-rebel) - os=linux + kernel=linux + os=gnu ;; arm*-semi) os=aout @@ -1710,84 +1672,169 @@ case $cpu-$vendor in os=none ;; esac + fi +# Now, validate our (potentially fixed-up) OS. +case $os in + # Sometimes we do "kernel-abi", so those need to count as OSes. + musl* | newlib* | uclibc*) + ;; + # Likewise for "kernel-libc" + eabi | eabihf | gnueabi | gnueabihf) + ;; + # Now accept the basic system types. + # The portable systems comes first. + # Each alternative MUST end in a * to match a version number. + gnu* | android* | bsd* | mach* | minix* | genix* | ultrix* | irix* \ + | *vms* | esix* | aix* | cnk* | sunos | sunos[34]* \ + | hpux* | unos* | osf* | luna* | dgux* | auroraux* | solaris* \ + | sym* | plan9* | psp* | sim* | xray* | os68k* | v88r* \ + | hiux* | abug | nacl* | netware* | windows* \ + | os9* | macos* | osx* | ios* \ + | mpw* | magic* | mmixware* | mon960* | lnews* \ + | amigaos* | amigados* | msdos* | newsos* | unicos* | aof* \ + | aos* | aros* | cloudabi* | sortix* | twizzler* \ + | nindy* | vxsim* | vxworks* | ebmon* | hms* | mvs* \ + | clix* | riscos* | uniplus* | iris* | isc* | rtu* | xenix* \ + | mirbsd* | netbsd* | dicos* | openedition* | ose* \ + | bitrig* | openbsd* | solidbsd* | libertybsd* | os108* \ + | ekkobsd* | freebsd* | riscix* | lynxos* | os400* \ + | bosx* | nextstep* | cxux* | aout* | elf* | oabi* \ + | ptx* | coff* | ecoff* | winnt* | domain* | vsta* \ + | udi* | lites* | ieee* | go32* | aux* | hcos* \ + | chorusrdb* | cegcc* | glidix* \ + | cygwin* | msys* | pe* | moss* | proelf* | rtems* \ + | midipix* | mingw32* | mingw64* | mint* \ + | uxpv* | beos* | mpeix* | udk* | moxiebox* \ + | interix* | uwin* | mks* | rhapsody* | darwin* \ + | openstep* | oskit* | conix* | pw32* | nonstopux* \ + | storm-chaos* | tops10* | tenex* | tops20* | its* \ + | os2* | vos* | palmos* | uclinux* | nucleus* | morphos* \ + | scout* | superux* | sysv* | rtmk* | tpf* | windiss* \ + | powermax* | dnix* | nx6 | nx7 | sei* | dragonfly* \ + | skyos* | haiku* | rdos* | toppers* | drops* | es* \ + | onefs* | tirtos* | phoenix* | fuchsia* | redox* | bme* \ + | midnightbsd* | amdhsa* | unleashed* | emscripten* | wasi* \ + | nsk* | powerunix* | genode* | zvmoe* | qnx* ) + ;; + # This one is extra strict with allowed versions + sco3.2v2 | sco3.2v[4-9]* | sco5v6*) + # Don't forget version if it is 3.2v4 or newer. + ;; + none) + ;; + *) + echo Invalid configuration \`"$1"\': OS \`"$os"\' not recognized 1>&2 + exit 1 + ;; +esac + +# As a final step for OS-related things, validate the OS-kernel combination +# (given a valid OS), if there is a kernel. +case $kernel-$os in + linux-gnu* | linux-dietlibc* | linux-android* | linux-newlib* | linux-musl* | linux-uclibc* ) + ;; + -dietlibc* | -newlib* | -musl* | -uclibc* ) + # These are just libc implementations, not actual OSes, and thus + # require a kernel. + echo "Invalid configuration \`$1': libc \`$os' needs explicit kernel." 1>&2 + exit 1 + ;; + kfreebsd*-gnu* | kopensolaris*-gnu*) + ;; + nto-qnx*) + ;; + *-eabi* | *-gnueabi*) + ;; + -*) + # Blank kernel with real OS is always fine. + ;; + *-*) + echo "Invalid configuration \`$1': Kernel \`$kernel' not known to work with OS \`$os'." 1>&2 + exit 1 + ;; +esac + # Here we handle the case where we know the os, and the CPU type, but not the # manufacturer. We pick the logical manufacturer. case $vendor in unknown) - case $os in - riscix*) + case $cpu-$os in + *-riscix*) vendor=acorn ;; - sunos*) + *-sunos*) vendor=sun ;; - cnk*|-aix*) + *-cnk* | *-aix*) vendor=ibm ;; - beos*) + *-beos*) vendor=be ;; - hpux*) + *-hpux*) vendor=hp ;; - mpeix*) + *-mpeix*) vendor=hp ;; - hiux*) + *-hiux*) vendor=hitachi ;; - unos*) + *-unos*) vendor=crds ;; - dgux*) + *-dgux*) vendor=dg ;; - luna*) + *-luna*) vendor=omron ;; - genix*) + *-genix*) vendor=ns ;; - clix*) + *-clix*) vendor=intergraph ;; - mvs* | opened*) + *-mvs* | *-opened*) + vendor=ibm + ;; + *-os400*) vendor=ibm ;; - os400*) + s390-* | s390x-*) vendor=ibm ;; - ptx*) + *-ptx*) vendor=sequent ;; - tpf*) + *-tpf*) vendor=ibm ;; - vxsim* | vxworks* | windiss*) + *-vxsim* | *-vxworks* | *-windiss*) vendor=wrs ;; - aux*) + *-aux*) vendor=apple ;; - hms*) + *-hms*) vendor=hitachi ;; - mpw* | macos*) + *-mpw* | *-macos*) vendor=apple ;; - *mint | mint[0-9]* | *MiNT | MiNT[0-9]*) + *-*mint | *-mint[0-9]* | *-*MiNT | *-MiNT[0-9]*) vendor=atari ;; - vos*) + *-vos*) vendor=stratus ;; esac ;; esac -echo "$cpu-$vendor-$os" +echo "$cpu-$vendor-${kernel:+$kernel-}$os" exit # Local variables: ===================================== includes/CodeGen.Platform.hs ===================================== @@ -94,7 +94,7 @@ import GHC.Platform.Reg # define zmm14 30 # define zmm15 31 --- Note: these are only needed for ARM/ARM64 because globalRegMaybe is now used in CmmSink.hs. +-- Note: these are only needed for ARM/AArch64 because globalRegMaybe is now used in CmmSink.hs. -- Since it's only used to check 'isJust', the actual values don't matter, thus -- I'm not sure if these are the correct numberings. -- Normally, the register names are just stringified as part of the REG() macro @@ -1096,4 +1096,3 @@ freeReg _ = True freeReg = panic "freeReg not defined for this platform" #endif - ===================================== includes/rts/Flags.h ===================================== @@ -199,6 +199,8 @@ typedef struct _CONCURRENT_FLAGS { * When linkerAlwaysPic is true, the runtime linker assume that all object * files were compiled with -fPIC -fexternal-dynamic-refs and load them * anywhere in the address space. + * Note that there is no 32bit darwin system we can realistically expect to + * run on or compile for. */ #if defined(darwin_HOST_OS) || defined(aarch64_HOST_ARCH) #define DEFAULT_LINKER_ALWAYS_PIC true ===================================== includes/rts/storage/GC.h ===================================== @@ -202,7 +202,7 @@ typedef void* AdjustorExecutable; AdjustorWritable allocateExec(W_ len, AdjustorExecutable *exec_addr); void flushExec(W_ len, AdjustorExecutable exec_addr); -#if defined(ios_HOST_OS) +#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) AdjustorWritable execToWritable(AdjustorExecutable exec); #endif void freeExec (AdjustorExecutable p); ===================================== libraries/ghc-boot/GHC/Platform/ArchOS.hs ===================================== @@ -41,7 +41,7 @@ data Arch | ArchSPARC | ArchSPARC64 | ArchARM ArmISA [ArmISAExt] ArmABI - | ArchARM64 + | ArchAArch64 | ArchAlpha | ArchMipseb | ArchMipsel @@ -130,7 +130,7 @@ stringEncodeArch = \case ArchARM ARMv5 _ _ -> "armv5" ArchARM ARMv6 _ _ -> "armv6" ArchARM ARMv7 _ _ -> "armv7" - ArchARM64 -> "aarch64" + ArchAArch64 -> "aarch64" ArchAlpha -> "alpha" ArchMipseb -> "mipseb" ArchMipsel -> "mipsel" ===================================== libraries/ghci/GHCi/InfoTable.hsc ===================================== @@ -69,7 +69,7 @@ data Arch = ArchSPARC | ArchX86_64 | ArchAlpha | ArchARM - | ArchARM64 + | ArchAArch64 | ArchPPC64 | ArchPPC64LE | ArchS390X @@ -102,7 +102,7 @@ mArch = #elif defined(arm_HOST_ARCH) Just ArchARM #elif defined(aarch64_HOST_ARCH) - Just ArchARM64 + Just ArchAArch64 #elif defined(powerpc64_HOST_ARCH) Just ArchPPC64 #elif defined(powerpc64le_HOST_ARCH) @@ -214,7 +214,7 @@ mkJumpToAddr' platform a = case platform of , 0x11, 0xff, 0x2f, 0xe1 , byte0 w32, byte1 w32, byte2 w32, byte3 w32] - ArchARM64 { } -> + ArchAArch64 { } -> -- Generates: -- -- ldr x1, label ===================================== llvm-targets ===================================== @@ -1,7 +1,7 @@ -[("i386-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) -,("i686-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) -,("x86_64-unknown-windows", ("e-m:w-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+soft-float -fp16 -vfp2 -vfp2sp -vfp2d16 -vfp2d16sp -vfp3 -vfp3sp -vfp3d16 -vfp3d16sp -vfp4 -vfp4sp -vfp4d16 -vfp4d16sp -fp-armv8 -fp-armv8sp -fp-armv8d16 -fp-armv8d16sp -fullfp16 -neon -crypto -dotprod -fp16fml -fp64 -d32 -fpregs +strict-align")) +[("i386-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("i686-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("x86_64-unknown-windows", ("e-m:w-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+strict-align")) ,("arm-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("arm-unknown-linux-musleabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("armv6-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1136jf-s", "+strict-align")) @@ -21,31 +21,32 @@ ,("aarch64-unknown-linux-gnu", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("aarch64-unknown-linux-musl", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("aarch64-unknown-linux", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i386-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux-musl", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux-android", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16")) -,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) +,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("x86_64-unknown-linux-gnu", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-musl", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-android", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16")) +,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) ,("aarch64-unknown-linux-android", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) +,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) ,("powerpc64le-unknown-linux-gnu", ("e-m:e-i64:64-n32:64", "ppc64le", "")) ,("powerpc64le-unknown-linux-musl", ("e-m:e-i64:64-n32:64", "ppc64le", "+secure-plt")) ,("powerpc64le-unknown-linux", ("e-m:e-i64:64-n32:64", "ppc64le", "")) ,("s390x-ibm-linux", ("E-m:e-i1:8:16-i8:8:16-i64:64-f128:64-a:8:16-n32:64", "z10", "")) -,("i386-apple-darwin", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) -,("x86_64-apple-darwin", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) -,("armv7-apple-ios", ("e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) -,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("i386-apple-ios", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) -,("x86_64-apple-ios", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) -,("amd64-portbld-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", "")) +,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", "")) +,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "vortex", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) +,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) +,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes")) +,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) +,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) +,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("aarch64-unknown-freebsd", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("armv6-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("armv7-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+strict-align")) ===================================== rts/Adjustor.c ===================================== @@ -99,7 +99,7 @@ freeHaskellFunctionPtr(void* ptr) { ffi_closure *cl; -#if defined(ios_HOST_OS) +#if defined(ios_HOST_OS) || defined(darwin_HOST_OS) cl = execToWritable(ptr); #else cl = (ffi_closure*)ptr; ===================================== rts/StgCRun.c ===================================== @@ -932,7 +932,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { "br %1\n\t" ".globl " STG_RETURN "\n\t" -#if !defined(ios_HOST_OS) +#if !defined(ios_HOST_OS) && !defined(darwin_HOST_OS) ".type " STG_RETURN ", %%function\n" #endif STG_RETURN ":\n\t" @@ -941,7 +941,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { */ "add sp, sp, %3\n\t" /* - * Return the new register table, taking it from Stg's R1 (ARM64's R22). + * Return the new register table, taking it from Stg's R1 (AArch64's R22). */ "mov %0, x22\n\t" /* ===================================== rts/linker/elf_plt_aarch64.c ===================================== @@ -46,8 +46,8 @@ bool needStubForRelaAarch64(Elf_Rela * rela) { bool makeStubAarch64(Stub * s) { // We (the linker) may corrupt registers x16 (IP0) and x17 (IP1) [AAPCS64] - // and the condition flags, according to the "ELF for the ARM64 - // Architecture". + // and the condition flags, according to the "ELF for the ARM 64-bit + // Architecture (AArch64)". // // [Special purpose regs] // X16 and X17 are IP0 and IP1, intra-procedure-call temporary registers. ===================================== rts/linker/elf_reloc.c ===================================== @@ -4,7 +4,7 @@ #if defined(OBJFORMAT_ELF) -/* we currently only use this abstraction for elf/arm64 */ +/* we currently only use this abstraction for elf/aarch64 */ #if defined(aarch64_HOST_ARCH) bool ===================================== rts/package.conf.in ===================================== @@ -318,7 +318,7 @@ ld-options: , "-Wl,-search_paths_first" #endif -#if defined(darwin_HOST_OS) && !defined(x86_64_HOST_ARCH) +#if defined(darwin_HOST_OS) && !defined(x86_64_HOST_ARCH) && !defined(aarch64_HOST_ARCH) , "-read_only_relocs", "warning" #endif ===================================== rts/rts.cabal.in ===================================== @@ -398,7 +398,7 @@ library if os(osx) ld-options: "-Wl,-search_paths_first" - if !arch(x86_64) + if !arch(x86_64) && !arch(aarch64) ld-options: -read_only_relocs warning cmm-sources: Apply.cmm ===================================== rts/sm/Storage.c ===================================== @@ -30,7 +30,7 @@ #include "GC.h" #include "Evac.h" #include "NonMoving.h" -#if defined(ios_HOST_OS) +#if defined(ios_HOST_OS) || defined(darwin_HOST_OS) #include "Hash.h" #endif @@ -1648,7 +1648,7 @@ StgWord calcTotalCompactW (void) should be modified to use allocateExec instead of VirtualAlloc. ------------------------------------------------------------------------- */ -#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) +#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) #include #endif @@ -1679,7 +1679,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) /* x86 doesn't need to do anything, so just suppress some warnings. */ (void)len; (void)exec_addr; -#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) +#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); #elif defined(__clang__) @@ -1734,7 +1734,7 @@ void freeExec (AdjustorExecutable addr) RELEASE_SM_LOCK } -#elif defined(ios_HOST_OS) +#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) static HashTable* allocatedExecs; ===================================== utils/llvm-targets/gen-data-layout.sh ===================================== @@ -84,9 +84,12 @@ TARGETS=( # macOS "i386-apple-darwin" "x86_64-apple-darwin" + "arm64-apple-darwin" # iOS - "armv7-apple-ios arm64-apple-ios" - "i386-apple-ios x86_64-apple-ios" + "armv7-apple-ios" + "arm64-apple-ios" + "i386-apple-ios" + "x86_64-apple-ios" ######################### # FreeBSD View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8887102fc4ed8ed1089c1aafd19bab424ad706f3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8887102fc4ed8ed1089c1aafd19bab424ad706f3 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 Sun Nov 15 08:36:27 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 15 Nov 2020 03:36:27 -0500 Subject: [Git][ghc/ghc][master] 2 commits: Name (tc)SplitForAll- functions more consistently Message-ID: <5fb0e88bf0034_43133fa6ae658f446762ec@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Flatten.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Validity.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2539650cc9c6606c6b50dd5dd96caa0209b408c...645444af9eb185684c750c95e4740d301352b2b9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a2539650cc9c6606c6b50dd5dd96caa0209b408c...645444af9eb185684c750c95e4740d301352b2b9 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 Sun Nov 15 08:37:39 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 15 Nov 2020 03:37:39 -0500 Subject: [Git][ghc/ghc][master] ghc-bin: Build with eventlogging by default Message-ID: <5fb0e8d373258_43133fa68f2210f868204e@gitlab.haskell.org.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 1 changed file: - ghc/ghc-bin.cabal.in Changes: ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -91,6 +91,8 @@ Executable ghc if flag(threaded) ghc-options: -threaded + ghc-options: -eventlog + Other-Extensions: CPP NondecreasingIndentation View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc644b1a643128041cfec25db84e417851e28bab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc644b1a643128041cfec25db84e417851e28bab 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 Sun Nov 15 12:39:27 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sun, 15 Nov 2020 07:39:27 -0500 Subject: [Git][ghc/ghc][wip/T18914] 29 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fb1217f95d23_4313b34578c69449a@gitlab.haskell.org.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - e3ad23ab by Ryan Scott at 2020-11-15T07:38:49-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). I also made `HsCoreTy` a type synonym instead of a newtype, as making it a distinct data type wasn't buying us much. * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22458bc95dc916a8ed93a431c5d2552b133257ee...e3ad23abd9f554df383eef9cd293505911b58ac2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22458bc95dc916a8ed93a431c5d2552b133257ee...e3ad23abd9f554df383eef9cd293505911b58ac2 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 Sun Nov 15 15:50:36 2020 From: gitlab at gitlab.haskell.org (Alan Zimmerman) Date: Sun, 15 Nov 2020 10:50:36 -0500 Subject: [Git][ghc/ghc][wip/az/exactprint] 162 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fb14e4cd5863_43133fa6aeda0130707350@gitlab.haskell.org.mail> Alan Zimmerman pushed to branch wip/az/exactprint at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - cd03fb98 by Alan Zimmerman at 2020-11-15T15:42:48+00:00 Proof of Concept implementation of in-tree API Annotations This MR introduces a possible machinery to introduce API Annotations into the TTG extension points. It is intended to be a concrete example for discussion. It still needs to process comments. Remove LHsLocalBinds Fix up after rebasing to bring in XRec Main thing is to make type instance XRec (GhcPass p) a = GenLocated (Anno a) a type family Anno a = b But this has massive implications. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3eafc77103486f4b39ca2db6083532f03f7f5e7e...cd03fb98f81d87c62077b65e0c4d10fa4f92ebd7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3eafc77103486f4b39ca2db6083532f03f7f5e7e...cd03fb98f81d87c62077b65e0c4d10fa4f92ebd7 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 Sun Nov 15 16:08:28 2020 From: gitlab at gitlab.haskell.org (Sven Tennie) Date: Sun, 15 Nov 2020 11:08:28 -0500 Subject: [Git][ghc/ghc][wip/stack_cloning] Assure that cloned RET_BIG closures are valid (#18741) Message-ID: <5fb1527c1a07d_43133fa67e7ca1f0708932@gitlab.haskell.org.mail> Sven Tennie pushed to branch wip/stack_cloning at Glasgow Haskell Compiler / GHC Commits: c34fe9ab by Sven Tennie at 2020-11-15T17:08:05+01:00 Assure that cloned RET_BIG closures are valid (#18741) - - - - - 3 changed files: - testsuite/tests/rts/all.T - + testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs - testsuite/tests/rts/cloneStackLib.c Changes: ===================================== testsuite/tests/rts/all.T ===================================== @@ -421,5 +421,6 @@ test('T15427', normal, compile_and_run, ['']) test('cloneMyStack', [extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c']) test('cloneMyStack2', ignore_stdout, compile_and_run, ['']) +test('cloneMyStack_retBigStackFrame', [extra_files(['cloneStackLib.c']), ignore_stdout], compile_and_run, ['cloneStackLib.c']) test('cloneThreadStack', [only_ways(['threaded1']), extra_ways(['threaded1']), extra_files(['cloneStackLib.c'])], compile_and_run, ['cloneStackLib.c -threaded']) ===================================== testsuite/tests/rts/cloneMyStack_retBigStackFrame.hs ===================================== @@ -0,0 +1,42 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnliftedFFITypes #-} + +module Main where + +import Control.Concurrent +import Data.IORef +import GHC.IO.Unsafe +import GHC.Prim (StackSnapshot#) +import GHC.Stack.CloneStack +import System.Mem + +foreign import ccall "expectSixtyFourOnesInRetBigFrame" expectSixtyFourOnesInRetBigFrame :: StackSnapshot# -> IO () + +cloneStack_returnInt :: IORef (Maybe StackSnapshot) -> Int +cloneStack_returnInt ioRef = unsafePerformIO $ do + stackSnapshot <- cloneMyStack + writeIORef ioRef (Just stackSnapshot) + return 42 + +main :: IO () +main = do + stackRef <- newIORef Nothing + + bigFun (cloneStack_returnInt stackRef) 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 + + Just (StackSnapshot stackSnapshot) <- readIORef stackRef + + -- Ensure no old data is found. + performMajorGC + + expectSixtyFourOnesInRetBigFrame stackSnapshot + + return () + +bigFun !a1 a2 a3 a4 a5 a6 a7 a8 a9 a10 a11 a12 a13 a14 a15 a16 a17 a18 a19 a20 a21 a22 a23 a24 a25 a26 a27 a28 a29 a30 a31 a32 a33 a34 a35 a36 a37 a38 a39 a40 a41 a42 a43 a44 a45 a46 a47 a48 a49 a50 a51 a52 a53 a54 a55 a56 a57 a58 a59 a60 a61 a62 a63 a64 a65 = + do + print $ a1 + a2 + a3 + a4 + a5 + a6 + a7 + a8 + a9 + a10 + a11 + a12 + a13 + a14 + a15 + a16 + a17 + a18 + a19 + a20 + a21 + a22 + a23 + a24 + a25 + a26 + a27 + a28 + a29 + a30 + a31 + a32 + a33 + a34 + a35 + a36 + a37 + a38 + a39 + a40 + a41 + a42 + a43 + a44 + a45 + a46 + a47 + a48 + a49 + a50 + a51 + a52 + a53 + a54 + a55 + a56 + a57 + a58 + a59 + a60 + a61 + a62 + a63 + a64 + a65 + + return () ===================================== testsuite/tests/rts/cloneStackLib.c ===================================== @@ -1,6 +1,7 @@ #include "Rts.h" #include "RtsAPI.h" #include "rts/Messages.h" +#include void expectStacksToBeEqual(StgStack *clonedStack, StgTSO *tso) { @@ -53,3 +54,58 @@ void expectClosureTypes(StgStack *stack, unsigned int types[], size_t typesSize) } } } + +// Count all (#I 1) closures of the RET_BIG closure's payload. +static int countOnes(StgPtr spBottom, StgPtr payload, + StgLargeBitmap *large_bitmap, uint32_t size) { + StgWord bmp; + uint32_t i, j; + int ones = 0; + + i = 0; + for (bmp = 0; i < size; bmp++) { + StgWord bitmap = large_bitmap->bitmap[bmp]; + j = 0; + for (; i < size && j < BITS_IN(W_); j++, i++, bitmap >>= 1) { + if ((bitmap & 1) == 0) { + const StgClosure *closure = UNTAG_CLOSURE((StgClosure *)payload[i]); + const StgInfoTable *info = get_itbl(closure); + + switch (info->type) { + case CONSTR_0_1: { + StgConInfoTable *con_info = get_con_itbl(closure); + if (strcmp(GET_CON_DESC(con_info), "ghc-prim:GHC.Types.I#") == 0 && + closure->payload[0] == 1) { + ones++; + } + break; + } + default: { + break; + } + } + } + } + } + + return ones; +} + +void expectSixtyFourOnesInRetBigFrame(StgStack *stack) { + StgPtr sp = stack->sp; + StgPtr spBottom = stack->stack + stack->stack_size; + + for (; sp < spBottom; sp += stack_frame_sizeW((StgClosure *)sp)) { + const StgInfoTable *info = get_itbl((StgClosure *)sp); + + if (info->type == RET_BIG) { + StgLargeBitmap *bitmap = GET_LARGE_BITMAP(info); + int ones = countOnes(spBottom, (StgPtr)((StgClosure *)sp)->payload, + bitmap, bitmap->size); + + if (ones != 64) { + barf("Expected 64 ones, got %i!", ones); + } + } + } +} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c34fe9ab19a868ffcef8e6fe7927ef0ebd1f7126 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c34fe9ab19a868ffcef8e6fe7927ef0ebd1f7126 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 Mon Nov 16 00:17:40 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Sun, 15 Nov 2020 19:17:40 -0500 Subject: [Git][ghc/ghc][wip/T18599] rework projection syntax Message-ID: <5fb1c524863bd_43133fa6a82fd5447350bb@gitlab.haskell.org.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: f3ac563e by Shayne Fletcher at 2020-11-15T19:17:09-05:00 rework projection syntax - - - - - 7 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -493,15 +493,14 @@ data HsExpr p -- langauge extensions is enabled. -- e.g. .x = Projection { - -- proj_ext=noExtField, proj_rhs=Nothing, proj_fIELD=x, proj_projection = \z -> z.x + -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x -- }, -- .x.y = Projection { - -- proj_ext=noExtField, proj_rhs=Just .x, proj_fIELD=y, proj_projection = (\z -> z.y) . (\z -> z.x) + -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) -- } | Projection { proj_ext :: XProjection p - , proj_rhs :: Maybe (LHsExpr p) - , proj_fIELD :: Located FastString + , proj_fIELDS :: [Located FastString] , proj_projection :: LHsExpr p -- Equivalent 'getField' term. } @@ -1255,10 +1254,8 @@ ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field, gf_getField = _}) = ppr fexp <> dot <> ppr field -ppr_expr (Projection { proj_rhs = maybeRhs, proj_fIELD = field, proj_projection = _}) - = case maybeRhs of - Nothing -> dot <> ppr field - Just e -> ppr e <> dot <> ppr field +ppr_expr (Projection { proj_fIELDS = _, proj_projection = _}) + = undefined {- TODO: implement this -} ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) @@ -1415,9 +1412,8 @@ hsExprNeedsParens p = go go (RecordCon{}) = False go (HsRecFld{}) = False - -- Not entirely clear about these. - go (GetField{}) = False - go (Projection{}) = False + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. go (XExpr x) | GhcTc <- ghcPass @p ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1165,9 +1165,7 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where GetField _ expr _ _ -> [ toHie expr ] - Projection _ maybeExpr _ _ -> - [ toHie maybeExpr - ] + Projection _ _ _ -> [] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -2754,7 +2754,12 @@ aexp2 :: { ECP } ((mop $1:fst $2) ++ [mcp $3]) } -- This case is only possible when 'RecordDotSyntax' is enabled. - | '(' projection ')' { ecpFromExp $2 } + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> @@ -2804,13 +2809,13 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } -projection :: { LHsExpr GhcPs } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } projection -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer : projection TIGHT_INFIX_PROJ field - {% ams (mkProjection (comb3 $1 $2 $3) (Just $1) $3) [mj AnnDot $2] } - | PREFIX_PROJ field - {% ams (mkProjection (comb2 $1 $2) Nothing $2) [mj AnnDot $1] } + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -3009,17 +3009,33 @@ zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) --- mkProj rhs fIELD calculates a projection. --- e.g. .x = mkProj Nothing x = \z -> z.x = \z -> (getField @fIELD x) --- .x.y = mkProj Just(.x) y = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) -mkProj :: Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs -mkProj rhs fIELD = - let body = mkGet zVar fIELD - grhs = noLoc $ GRHS noExtField [] body - ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) - m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} - lhs = mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) in - maybe lhs (mkParen . mkOpApp lhs circ) rhs +-- mkProj' fIELDS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @fIELD x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (fIELD : fIELDS) = foldl' f (proj fIELD) fIELDS + where + f acc fIELD = (mkParen . mkOpApp (proj fIELD) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- -- mkProj rhs fIELD calculates a projection. +-- -- e.g. .x = mkProj Nothing x = \z -> z.x = \z -> (getField @fIELD x) +-- -- .x.y = mkProj Just(.x) y = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +-- mkProj :: Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs +-- mkProj rhs fIELD = +-- let body = mkGet zVar fIELD +-- grhs = noLoc $ GRHS noExtField [] body +-- ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) +-- m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} +-- lhs = mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) in +-- maybe lhs (mkParen . mkOpApp lhs circ) rhs -- mkGet arg fIELD calcuates a get_field @fIELD arg expression. -- e.g. z.x = mkGet z x = get_field @x z @@ -3038,15 +3054,24 @@ mkGetField loc arg fIELD = , gf_getField = mkGet arg fIELD } -mkProjection :: SrcSpan -> Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs -mkProjection loc maybeRhs fIELD = +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible happened" +mkProjection loc fIELDS = L loc Projection { proj_ext = noExtField - , proj_rhs = maybeRhs - , proj_fIELD = fIELD - , proj_projection = mkProj maybeRhs fIELD + , proj_fIELDS = fIELDS + , proj_projection = mkProj fIELDS } +-- mkProjection :: SrcSpan -> Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs +-- mkProjection loc maybeRhs fIELD = +-- L loc Projection { +-- proj_ext = noExtField +-- , proj_rhs = maybeRhs +-- , proj_fIELD = fIELD +-- , proj_projection = mkProj maybeRhs fIELD +-- } + -- mkSet a fIELD b calculates a set_field @fIELD expression. -- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -218,14 +218,9 @@ rnExpr (GetField x e f g) ; return (GetField x e' f g', fv) } -rnExpr (Projection x e f p) - = do { e' <- case e of - Nothing -> pure Nothing - Just expr -> do - (e', _) <- rnLExpr expr - pure (Just e') - ; (p', fv) <- rnLExpr p - ; return (Projection x e' f p', fv) +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) } ------------------------------------------ ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1037,7 +1037,7 @@ tcExpr (ArithSeq _ witness seq) res_ty ************************************************************************ -} tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty -tcExpr (Projection _ _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty {- ************************************************************************ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -500,7 +500,7 @@ exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e -exprCtOrigin (Projection _ _ _ _) = SectionOrigin +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3ac563e1070bd00b66ebc017a490489c7b54f8e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3ac563e1070bd00b66ebc017a490489c7b54f8e 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 Mon Nov 16 02:31:25 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Sun, 15 Nov 2020 21:31:25 -0500 Subject: [Git][ghc/ghc][wip/T18857] 19 commits: testsuite: Add testcase for #18733 Message-ID: <5fb1e47d68adb_43133fa698f2e6fc741961@gitlab.haskell.org.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - af445b07 by Ben Gamari at 2020-11-16T02:28:47+00:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' Fixes #18857. - - - - - 660eb5b0 by Ben Gamari at 2020-11-16T02:28:47+00:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - b4adb002 by Ben Gamari at 2020-11-16T02:31:09+00:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 5aded170 by Ben Gamari at 2020-11-16T02:31:13+00:00 hadrian: Don't use -fllvm to bootstrap under LLVM flavour Previously Hadrian's LLVM build flavours would use `-fllvm` for all invocations, even those to stage0 GHC. This meant that we needed to keep two LLVM versions around in all of the CI images. Moreover, it differed from the behavior of the old make build system's llvm flavours. Change this to reflect the behavior of the `make` build system, using `-fllvm` only with the stage1 and stage2 compilers. - - - - - f7afd6fe by Moritz Angermann at 2020-11-16T02:31:13+00:00 fixup ShortText - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Session.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3c7f5854d0c5c84de0cf735b511402539a243e72...f7afd6fe76a8d2b365e68557b7c495567a49745c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3c7f5854d0c5c84de0cf735b511402539a243e72...f7afd6fe76a8d2b365e68557b7c495567a49745c 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 Mon Nov 16 13:17:22 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Mon, 16 Nov 2020 08:17:22 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] 15 commits: testsuite: Add testcase for #18733 Message-ID: <5fb27be2d7f2b_43133fa67e9e9648793520@gitlab.haskell.org.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - c675efff by Daniel Rogozin at 2020-11-16T16:16:58+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5dfd431ae079977e4bc065252ea46354ec677eed...c675efff7e9ee02b4913b65adf8ab36145b4e8a1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5dfd431ae079977e4bc065252ea46354ec677eed...c675efff7e9ee02b4913b65adf8ab36145b4e8a1 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 Mon Nov 16 19:40:43 2020 From: gitlab at gitlab.haskell.org (Leif Metcalf) Date: Mon, 16 Nov 2020 14:40:43 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/leif/stg-ttg Message-ID: <5fb2d5bb89b08_43133fa68c91824c838218@gitlab.haskell.org.mail> Leif Metcalf pushed new branch wip/leif/stg-ttg at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/leif/stg-ttg 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 Mon Nov 16 20:16:09 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 16 Nov 2020 15:16:09 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] fix regression Message-ID: <5fb2de091d44d_43133fa68efcfbc48415a8@gitlab.haskell.org.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: aabd8a4c by Sebastian Graf at 2020-11-16T21:16:02+01:00 fix regression - - - - - 3 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -78,12 +78,12 @@ dmdAnalTopBind env (NonRec id rhs) = ( extendAnalEnv TopLevel env id sig , NonRec (setIdStrictness id sig) rhs') where - ( _, sig, rhs') = dmdAnalRhsLetDown Nothing env cleanEvalDmd id rhs + ( _, sig, rhs') = dmdAnalRhsLetDown Nothing env topSubDmd id rhs dmdAnalTopBind env (Rec pairs) = (env', Rec pairs') where - (env', _, pairs') = dmdFix TopLevel env cleanEvalDmd pairs + (env', _, pairs') = dmdFix TopLevel env topSubDmd pairs -- We get two iterations automatically -- c.f. the NonRec case above @@ -263,7 +263,7 @@ dmdAnal' env dmd (Case scrut case_bndr ty [(DataAlt dc, bndrs, rhs)]) dmdAnal' env dmd (Case scrut case_bndr ty alts) = let -- Case expression with multiple alternatives (alt_tys, alts') = mapAndUnzip (dmdAnalAlt env dmd case_bndr) alts - (scrut_ty, scrut') = dmdAnal env cleanEvalDmd scrut + (scrut_ty, scrut') = dmdAnal env topSubDmd scrut (alt_ty, case_bndr') = annotateBndr env (foldr lubDmdType botDmdType alt_tys) case_bndr -- NB: Base case is botDmdType, for empty case alternatives -- This is a unit for lubDmdType, and the right result @@ -668,7 +668,7 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs -- a call demand of @rhs_arity@ -- See Historical Note [Product demands for function body] mkRhsDmd :: AnalEnv -> Arity -> CoreExpr -> SubDemand -mkRhsDmd _env rhs_arity _rhs = mkCallDmds rhs_arity cleanEvalDmd +mkRhsDmd _env rhs_arity _rhs = mkCallDmds rhs_arity topSubDmd -- | If given the (local, non-recursive) let-bound 'Id', 'useLetUp' determines -- whether we should process the binding up (body before rhs) or down (rhs ===================================== compiler/GHC/Core/Opt/SpecConstr.hs ===================================== @@ -1724,7 +1724,7 @@ calcSpecStrictness fn qvars pats go env _ _ = env go_one :: DmdEnv -> Demand -> CoreExpr -> DmdEnv - go_one env d (Var v) = extendVarEnv_C plusDmd env v d + go_one env d (Var v) = extendVarEnv_C plusDmd env v d go_one env (_n :* cd) e -- NB: _n does not have to be strict | (Var _, args) <- collectArgs e , Just ds <- viewProd (length args) cd ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -17,7 +17,7 @@ module GHC.Types.Demand ( -- * Demands Card(..), Demand(..), SubDemand(Prod), mkProd, viewProd, -- ** Algebra - absDmd, topDmd, botDmd, seqDmd, + absDmd, topDmd, botDmd, seqDmd, topSubDmd, -- *** Least upper bound lubCard, lubDmd, lubSubDmd, -- *** Plus @@ -29,7 +29,7 @@ module GHC.Types.Demand ( isAbsDmd, isUsedOnceDmd, isStrUsedDmd, isTopDmd, isSeqDmd, isWeakDmd, -- ** Special demands - evalDmd, cleanEvalDmd, cleanEvalProdDmd, + evalDmd, -- *** Demands used in PrimOp signatures lazyApply1Dmd, lazyApply2Dmd, strictOnceApply1Dmd, strictManyApply1Dmd, -- ** Other @Demand@ operations @@ -311,7 +311,7 @@ polyDmd C_10 = C_10 :* poly10 -- 'SubDemand's when possible. Note that this degrades boxity information! E.g. a -- polymorphic demand will never unbox. mkProd :: [Demand] -> SubDemand -mkProd [] = botSubDmd +mkProd [] = seqSubDmd mkProd ds@(n:*sd : _) | want_to_simplify n, all (== polyDmd n) ds = sd | otherwise = Prod ds @@ -456,13 +456,7 @@ isWeakDmd dmd@(n :* _) = not (isStrict n) && is_plus_idem_dmd dmd is_plus_idem_sub_dmd (Call n _) = is_plus_idem_card n -- See Note [Call demands are relative] evalDmd :: Demand -evalDmd = C_1N :* cleanEvalDmd - -cleanEvalDmd :: SubDemand -cleanEvalDmd = topSubDmd - -cleanEvalProdDmd :: Arity -> SubDemand -cleanEvalProdDmd n = Prod (replicate n topDmd) +evalDmd = C_1N :* topSubDmd -- | First argument of 'GHC.Exts.maskAsyncExceptions#': @SCS(U)@. -- Called exactly once. @@ -558,7 +552,9 @@ addCaseBndrDmd (n :* sd) alt_dmds | isAbs n = alt_dmds | otherwise = zipWith plusDmd ds alt_dmds -- fuse ds! where - Just ds = viewProd (length alt_dmds) sd -- Guaranteed not to be a call + sd' | isStrict n = sd + | otherwise = multSubDmd C_01 sd + Just ds = viewProd (length alt_dmds) sd' -- Guaranteed not to be a call argsOneShots :: StrictSig -> Arity -> [[OneShotInfo]] -- ^ See Note [Computing one-shot info] @@ -578,7 +574,7 @@ argsOneShots (StrictSig (DmdType _ arg_ds _)) n_val_args argOneShots :: Demand -- ^ depending on saturation -> [OneShotInfo] -- ^ See Note [Computing one-shot info] -argOneShots (_ :* sd) = go sd +argOneShots (n :* sd) = go (multSubDmd n sd) -- See Note [Call demands are relative] where go (Call n sd) | isUsedOnce n = OneShotLam : go sd View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aabd8a4cb01328e8b885c9a3608a229a69c295ff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aabd8a4cb01328e8b885c9a3608a229a69c295ff 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 Tue Nov 17 03:34:36 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 16 Nov 2020 22:34:36 -0500 Subject: [Git][ghc/ghc][wip/T18857] Fixup SymbolExtras Message-ID: <5fb344cca8996_73a83fb01fdb03d073149@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: a2bc2220 by Moritz Angermann at 2020-11-17T03:33:50+00:00 Fixup SymbolExtras - - - - - 4 changed files: - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/SymbolExtras.c - rts/linker/elf_reloc_aarch64.c Changes: ===================================== rts/LinkerInternals.h ===================================== @@ -141,7 +141,7 @@ typedef struct _Segment { int n_sections; } Segment; -#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif ===================================== rts/linker/Elf.c ===================================== @@ -940,7 +940,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1867,6 +1867,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1940,6 +1941,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/SymbolExtras.c ===================================== @@ -140,7 +140,12 @@ void ocProtectExtras(ObjectCode* oc) * non-executable. */ } else if (USE_CONTIGUOUS_MMAP || RtsFlags.MiscFlags.linkerAlwaysPic) { - mmapForLinkerMarkExecutable(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); + // XXX I'm not sure how this is supposed to work. + // XXX + // XXX oc->symbol_extras would need to be assigned on page boundaries, and mmaped + // XXX but this is not guaranteed in any form or fashion? + // XXX + // mmapForLinkerMarkExecutable(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); } else { /* * The symbol extras were allocated via m32. They will be protected when ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a2bc22207f09d8fc8837f2f33452f85d0d4ed688 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a2bc22207f09d8fc8837f2f33452f85d0d4ed688 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 Tue Nov 17 04:28:25 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 16 Nov 2020 23:28:25 -0500 Subject: [Git][ghc/ghc][wip/T18857] fixup ShortText & SymbolExtras Message-ID: <5fb35169c8826_73a8caf2ccc749d7@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 047ee59e by Moritz Angermann at 2020-11-17T04:28:05+00:00 fixup ShortText & SymbolExtras - - - - - 5 changed files: - libraries/ghc-boot/GHC/Data/ShortText.hs - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/SymbolExtras.c - rts/linker/elf_reloc_aarch64.c Changes: ===================================== libraries/ghc-boot/GHC/Data/ShortText.hs ===================================== @@ -1,6 +1,22 @@ -{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-} +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} - +-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore. +-- LLVM based GHC's fail to compile memcmp ffi calls. These end up as memcmp$def in the llvm ir, however we +-- don't have any prototypes and subsequently the llvm toolchain chokes on them. Since 7fdcce6d, we use +-- ShortText for the package database. This however introduces this very module; which through inlining ends +-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in +-- the memcmp call we choke on. +-- +-- The solution thusly is to force late binding via the linker instead of inlining when comping with the +-- bootstrap compiler. This will produce a slower (slightly less optimised) stage1 compiler only. +-- +-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion. +-- +-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler, +-- we can drop this code as well. +#if GHC_STAGE < 1 +{-# OPTIONS_GHC -fignore-interface-pragmas #-} +#endif -- | -- An Unicode string for internal GHC use. Meant to replace String -- in places where being a lazy linked is not very useful and a more ===================================== rts/LinkerInternals.h ===================================== @@ -141,7 +141,7 @@ typedef struct _Segment { int n_sections; } Segment; -#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif ===================================== rts/linker/Elf.c ===================================== @@ -940,7 +940,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1867,6 +1867,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1940,6 +1941,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/SymbolExtras.c ===================================== @@ -140,7 +140,12 @@ void ocProtectExtras(ObjectCode* oc) * non-executable. */ } else if (USE_CONTIGUOUS_MMAP || RtsFlags.MiscFlags.linkerAlwaysPic) { - mmapForLinkerMarkExecutable(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); + // XXX I'm not sure how this is supposed to work. + // XXX + // XXX oc->symbol_extras would need to be assigned on page boundaries, and mmaped + // XXX but this is not guaranteed in any form or fashion? + // XXX + // mmapForLinkerMarkExecutable(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); } else { /* * The symbol extras were allocated via m32. They will be protected when ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/047ee59e16d54893fd49ef15f9527ddfa9d7757a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/047ee59e16d54893fd49ef15f9527ddfa9d7757a 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 Tue Nov 17 06:59:19 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 17 Nov 2020 01:59:19 -0500 Subject: [Git][ghc/ghc][wip/T18857] Filter stdout/stderr Message-ID: <5fb374c7ef4c_73a83fb01e5e35b8803e2@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 86623421 by Moritz Angermann at 2020-11-17T06:59:09+00:00 Filter stdout/stderr - - - - - 1 changed file: - testsuite/driver/testlib.py Changes: ===================================== testsuite/driver/testlib.py ===================================== @@ -2216,6 +2216,10 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2286,6 +2290,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/866234216353eb87ba5fa5e9fccaf747c88bcab3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/866234216353eb87ba5fa5e9fccaf747c88bcab3 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 Tue Nov 17 12:56:48 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 17 Nov 2020 07:56:48 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 121 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fb3c89094ffc_73a83fb035cf1064112493@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - a790f638 by Andreas Klebinger at 2020-11-17T07:56:46-05:00 Use validate flavour for all CI builds - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbe06772f588f4bfd1973ea3b25d1be62b884e6f...a790f6383932f16f5ea97ec8406b9d2b2f33e7fa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbe06772f588f4bfd1973ea3b25d1be62b884e6f...a790f6383932f16f5ea97ec8406b9d2b2f33e7fa 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 Tue Nov 17 13:07:46 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 17 Nov 2020 08:07:46 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] Use validate flavour for all CI builds Message-ID: <5fb3cb2298a79_73a8148241c8112669@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: 78d9f2ef by Andreas Klebinger at 2020-11-17T14:06:32+01:00 Use validate flavour for all CI builds - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78d9f2ef6e1838f268dae9a2828c7d5665d5204a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/78d9f2ef6e1838f268dae9a2828c7d5665d5204a 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 Tue Nov 17 14:31:00 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 17 Nov 2020 09:31:00 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 15 commits: testsuite: Add testcase for #18733 Message-ID: <5fb3dea43e043_73a83faf74735d6c116429@gitlab.mail> Moritz Angermann pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 28945480 by Moritz Angermann at 2020-11-17T09:30:58-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e0989e1c4c4e4249fbc1bf4e920625585f191689...289454805db43f70ce4ae9999a010e2fba082519 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e0989e1c4c4e4249fbc1bf4e920625585f191689...289454805db43f70ce4ae9999a010e2fba082519 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 Tue Nov 17 15:46:49 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 17 Nov 2020 10:46:49 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Comments, etc., from Friday Message-ID: <5fb3f0694a92d_73a83fb01f78e4481224a8@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: f2bbcc40 by Richard Eisenberg at 2020-11-17T10:46:37-05:00 Comments, etc., from Friday - - - - - 4 changed files: - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs Changes: ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -1244,6 +1244,7 @@ data BindFlag | Skolem -- This type variable is a skolem constant -- Don't bind it; it only matches itself + -- These variables are SurelyApart from other types deriving Eq {- ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -2520,26 +2520,27 @@ Wrinkles: must be sure to kick out any such CIrredCan constraints that mention coercion holes when those holes get filled in, so that the unification step can now proceed. - (2a) We must now absolutely make sure to kick out any constraints that - mention a newly-filled-in coercion hole -- if there are no more - remaining coercion holes. This is done in - kickOutAfterFillingCoercionHole. The extra check that there are no - more remaining holes avoids needless work when rewriting evidence - (which fills coercion holes) and aids efficiency. It also can avoid - a loop in the solver that would otherwise arise in this case: + (2a) We must now kick out any constraints that mention a newly-filled-in + coercion hole, but only if there are no more remaining coercion + holes. This is done in kickOutAfterFillingCoercionHole. The extra + check that there are no more remaining holes avoids needless work + when rewriting evidence (which fills coercion holes) and aids + efficiency. + + Moreover, kicking out when there are remaining unfilled holes can + cause a loop in the solver in this case: [W] w1 :: (ty1 :: F a) ~ (ty2 :: s) After canonicalisation, we discover that this equality is heterogeneous. So we emit [W] co_abc :: F a ~ s and preserve the original as - [W] w2 :: (ty1 |> co_abc) ~ ty2 - Then, co_abc comes becomes the work item. It gets swapped back - and forth, as it goes through canEqTyVarFunEq. We thus get + [W] w2 :: (ty1 |> co_abc) ~ ty2 (blocked on co_abc) + Then, co_abc comes becomes the work item. It gets swapped in + canEqCanLHS2 and then back again in canEqTyVarFunEq. We thus get co_abc := sym co_abd, and then co_abd := sym co_abe, with [W] co_abe :: F a ~ s - right back where we started. (At this point, we're in canEqCanLHSFinish, - so we're not looping.) But all this filling in would, - naively, cause w2 to be kicked out. Which, when it got processed, + This process has filled in co_abc. Suppose w2 were kicked out. + When it gets processed, would get this whole chain going again. The solution is to kick out a blocked constraint only when the result of filling in the blocking coercion involves no further blocking coercions. ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -1780,9 +1780,9 @@ kick_out_rewritable new_fr new_lhs kick_out_for_completeness -- (K3) and Note [K3: completeness of solving] = case (eq_rel, new_lhs) of - (NomEq, _) -> rhs_ty `eqType` canEqLHSType new_lhs - (ReprEq, TyVarLHS new_tv) -> isTyVarHead new_tv rhs_ty - (ReprEq, TyFamLHS new_tf new_tf_args) + (NomEq, _) -> rhs_ty `eqType` canEqLHSType new_lhs -- (K3a) + (ReprEq, TyVarLHS new_tv) -> isTyVarHead new_tv rhs_ty -- (K3b) + (ReprEq, TyFamLHS new_tf new_tf_args) -- (K3b) | Just (rhs_tc, rhs_tc_args) <- tcSplitTyConApp_maybe rhs_ty , tcEqTyConApps new_tf new_tf_args rhs_tc rhs_tc_args -> True ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -1176,6 +1176,12 @@ data ImplicStatus -- See Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad, -- which also explains why we need three options here. Also, see -- Note [Suppress redundant givens during error reporting] in GHC.Tc.Errors +-- +-- Stops floating | Suppresses Givens in errors +-- ----------------------------------------------- +-- NoGivenEqs NO | YES +-- LocalGivenEqs NO | NO +-- MaybeGivenEqs YES | NO data HasGivenEqs = NoGivenEqs -- definitely no given equalities | LocalGivenEqs -- might have Given equalities that affect only local skolems View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2bbcc402adb211c78cf185e0cda194e6f8d87b1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2bbcc402adb211c78cf185e0cda194e6f8d87b1 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 Tue Nov 17 17:59:55 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Tue, 17 Nov 2020 12:59:55 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-debug_partial_tso_stack_decode Message-ID: <5fb40f9b258bf_73a83faf76941b0413661d@gitlab.mail> David Eichmann pushed new branch wip/ghc-debug_partial_tso_stack_decode at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-debug_partial_tso_stack_decode 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 Tue Nov 17 18:18:18 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 17 Nov 2020 13:18:18 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/rts_inlining Message-ID: <5fb413ea4bf7e_73a814a8590813945e@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/rts_inlining at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/rts_inlining 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 Tue Nov 17 18:19:32 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 17 Nov 2020 13:19:32 -0500 Subject: [Git][ghc/ghc][wip/andreask/rts_inlining] RTS: Fix failed inlining of copy_tag. Message-ID: <5fb41434cf8d3_73a83fb015bd3cd81396e4@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/rts_inlining at Glasgow Haskell Compiler / GHC Commits: 1f0e5cef by Andreas Klebinger at 2020-11-17T19:19:00+01:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc refused to inline copy_tag into evacuate. To fix this we no set the always_inline attribute for copy and copy_tag to force inlining. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - 2 changed files: - includes/Rts.h - rts/sm/Evac.c Changes: ===================================== includes/Rts.h ===================================== @@ -46,6 +46,11 @@ extern "C" { # define STATIC_DEBUG static #endif +// Fine grained inlining control helpers. +#define ALWAYS_INLINE __attribute__((always_inline)) +#define NOINLINE __attribute__((noinline)) + + #include "rts/Types.h" #include "rts/Time.h" ===================================== rts/sm/Evac.c ===================================== @@ -58,7 +58,7 @@ #define MAX_THUNK_SELECTOR_DEPTH 16 static void eval_thunk_selector (StgClosure **q, StgSelector *p, bool); -STATIC_DEBUG void evacuate_large(StgPtr p); +NOINLINE static void evacuate_large(StgPtr p); /* ----------------------------------------------------------------------------- Allocate some space in which to copy an object. @@ -135,7 +135,7 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) -------------------------------------------------------------------------- */ /* size is in words */ -STATIC_DEBUG GNUC_ATTR_HOT void +ALWAYS_INLINE STATIC_DEBUG GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -283,7 +283,7 @@ spin: /* Copy wrappers that don't tag the closure after copying */ -STATIC_DEBUG GNUC_ATTR_HOT void +ALWAYS_INLINE GNUC_ATTR_HOT static inline void copy(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no) { @@ -301,7 +301,7 @@ copy(StgClosure **p, const StgInfoTable *info, that has been evacuated, or unset otherwise. -------------------------------------------------------------------------- */ -static void +NOINLINE static void evacuate_large(StgPtr p) { bdescr *bd; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f0e5cefcb432f0845003263ba46de211eeb6bc4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f0e5cefcb432f0845003263ba46de211eeb6bc4 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 Tue Nov 17 18:20:54 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 17 Nov 2020 13:20:54 -0500 Subject: [Git][ghc/ghc][wip/andreask/rts_inlining] 2 commits: Rename STATIC_INLINE to STATIC_DEBUG. Message-ID: <5fb41486f4ad_73a814adf82c1426bb@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/rts_inlining at Glasgow Haskell Compiler / GHC Commits: 677c5eab by Andreas Klebinger at 2020-11-17T19:20:38+01:00 Rename STATIC_INLINE to STATIC_DEBUG. STATIC_INLINE by default neither makes functions static nor does it mark them as inline. Even worse STATIC_INLINE *never* makes a function more likely to inline. But makes functions with an inline pragma *less* likely to inline by adding a static keyword if debugging is enabled. If you think this is quite confusing then that's because it is. I renamed this attribute to STATIC_DEBUG. This might not be a lot clearer at first thight, but I hope at least people won't wonder why something called *_INLINE doesn't make things inline in the future. - - - - - 2faaae9a by Andreas Klebinger at 2020-11-17T19:20:38+01:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc refused to inline copy_tag into evacuate. To fix this we no set the always_inline attribute for copy and copy_tag to force inlining. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - 27 changed files: - compiler/cbits/genSym.c - includes/Rts.h - includes/Stg.h - rts/Capability.c - rts/FileLock.c - rts/Hash.c - rts/Interpreter.c - rts/LdvProfile.c - rts/Printer.c - rts/ProfHeap.c - rts/RetainerProfile.c - rts/RetainerSet.c - rts/RtsFlags.c - rts/Schedule.c - rts/StableName.c - rts/StablePtr.c - rts/StaticPtrTable.c - rts/StgPrimFloat.c - rts/TraverseHeap.c - rts/sm/BlockAlloc.c - rts/sm/CNF.c - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/MBlock.c - rts/sm/NonMovingMark.c - rts/sm/Scav.c - rts/sm/Storage.c Changes: ===================================== compiler/cbits/genSym.c ===================================== @@ -8,7 +8,7 @@ static HsInt GenSymInc = 1; #define UNIQUE_BITS (sizeof (HsInt) * 8 - UNIQUE_TAG_BITS) #define UNIQUE_MASK ((1ULL << UNIQUE_BITS) - 1) -STATIC_INLINE void checkUniqueRange(HsInt u STG_UNUSED) { +STATIC_DEBUG void checkUniqueRange(HsInt u STG_UNUSED) { #if DEBUG // Uh oh! We will overflow next time a unique is requested. assert(u != UNIQUE_MASK); ===================================== includes/Rts.h ===================================== @@ -37,12 +37,20 @@ extern "C" { #include "HsFFI.h" #include "RtsAPI.h" -// Turn off inlining when debugging - it obfuscates things +// Functions with "static inline" behave just like as if they had no +// keywords for the purpose of inlining. +// So we can use this to make a inline function less likely to inline +// when debugging. Helpful since inlining obfuscates things #if defined(DEBUG) -# undef STATIC_INLINE -# define STATIC_INLINE static +# undef STATIC_DEBUG +# define STATIC_DEBUG static #endif +// Fine grained inlining control helpers. +#define ALWAYS_INLINE __attribute__((always_inline)) +#define NOINLINE __attribute__((noinline)) + + #include "rts/Types.h" #include "rts/Time.h" ===================================== includes/Stg.h ===================================== @@ -128,7 +128,7 @@ /* * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) - * STATIC_INLINE is for inline functions in source files + * STATIC_DEBUG is for inline functions in source files * EXTERN_INLINE is for functions that we want to inline sometimes * (we also compile a static version of the function; see Inlines.c) */ @@ -140,7 +140,7 @@ // The problem, however, is with 'extern inline' whose semantics significantly // differs between gnu90 and C99 #define INLINE_HEADER static inline -#define STATIC_INLINE static inline +#define STATIC_DEBUG static inline // Figure out whether `__attributes__((gnu_inline))` is needed // to force gnu90-style 'external inline' semantics. ===================================== rts/Capability.c ===================================== @@ -81,7 +81,7 @@ Capability * rts_unsafeGetMyCapability (void) } #if defined(THREADED_RTS) -STATIC_INLINE bool +STATIC_DEBUG bool globalWorkToDo (void) { return RELAXED_LOAD(&sched_state) >= SCHED_INTERRUPTING @@ -199,7 +199,7 @@ anySparks (void) * -------------------------------------------------------------------------- */ #if defined(THREADED_RTS) -STATIC_INLINE void +STATIC_DEBUG void newReturningTask (Capability *cap, Task *task) { ASSERT_LOCK_HELD(&cap->lock); @@ -218,7 +218,7 @@ newReturningTask (Capability *cap, Task *task) ASSERT_RETURNING_TASKS(cap,task); } -STATIC_INLINE Task * +STATIC_DEBUG Task * popReturningTask (Capability *cap) { ASSERT_LOCK_HELD(&cap->lock); ===================================== rts/FileLock.c ===================================== @@ -34,14 +34,14 @@ static HashTable *key_hash; static Mutex file_lock_mutex; #endif -STATIC_INLINE int cmpLocks(StgWord w1, StgWord w2) +STATIC_DEBUG int cmpLocks(StgWord w1, StgWord w2) { Lock *l1 = (Lock *)w1; Lock *l2 = (Lock *)w2; return (l1->device == l2->device && l1->inode == l2->inode); } -STATIC_INLINE int hashLock(const HashTable *table, StgWord w) +STATIC_DEBUG int hashLock(const HashTable *table, StgWord w) { Lock *l = (Lock *)w; StgWord key = l->inode ^ (l->inode >> 32) ^ l->device ^ (l->device >> 32); ===================================== rts/Hash.c ===================================== @@ -99,13 +99,13 @@ hashStr(const HashTable *table, StgWord w) return bucket; } -STATIC_INLINE int +STATIC_DEBUG int compareWord(StgWord key1, StgWord key2) { return (key1 == key2); } -STATIC_INLINE int +STATIC_DEBUG int compareStr(StgWord key1, StgWord key2) { return (strcmp((char *)key1, (char *)key2) == 0); @@ -116,7 +116,7 @@ compareStr(StgWord key1, StgWord key2) * Allocate a new segment of the dynamically growing hash table. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void allocSegment(HashTable *table, int segment) { table->dir[segment] = stgMallocBytes(HSEGSIZE * sizeof(HashList *), @@ -130,7 +130,7 @@ allocSegment(HashTable *table, int segment) * by @table->split@ is affected by the expansion. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void expand(HashTable *table, HashFunction f) { int oldsegment; @@ -186,7 +186,7 @@ expand(HashTable *table, HashFunction f) return; } -STATIC_INLINE void* +STATIC_DEBUG void* lookupHashTable_inlined(const HashTable *table, StgWord key, HashFunction f, CompareFunction cmp) { @@ -310,7 +310,7 @@ freeHashList (HashTable *table, HashList *hl) table->freeList = hl; } -STATIC_INLINE void +STATIC_DEBUG void insertHashTable_inlined(HashTable *table, StgWord key, const void *data, HashFunction f) { @@ -358,7 +358,7 @@ insertStrHashTable(StrHashTable *table, const char * key, const void *data) insertHashTable_inlined(&table->table, (StgWord) key, data, hashStr); } -STATIC_INLINE void* +STATIC_DEBUG void* removeHashTable_inlined(HashTable *table, StgWord key, const void *data, HashFunction f, CompareFunction cmp) { ===================================== rts/Interpreter.c ===================================== @@ -145,7 +145,7 @@ #define SpW(n) (*(StgWord*)(Sp_plusW(n))) #define SpB(n) (*(StgWord*)(Sp_plusB(n))) -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr allocate_NONUPD (Capability *cap, int n_words) { return allocate(cap, stg_max(sizeofW(StgHeader)+MIN_PAYLOAD_SIZE, n_words)); @@ -243,7 +243,7 @@ void interp_shutdown ( void ) // Build a zero-argument PAP with the current CCS // See Note [Evaluating functions with profiling] in Apply.cmm // -STATIC_INLINE +STATIC_DEBUG StgClosure * newEmptyPAP (Capability *cap, StgClosure *tagged_obj, // a FUN or a BCO uint32_t arity) @@ -260,7 +260,7 @@ StgClosure * newEmptyPAP (Capability *cap, // Make an exact copy of a PAP, except that we combine the current CCS with the // CCS in the PAP. See Note [Evaluating functions with profiling] in Apply.cmm // -STATIC_INLINE +STATIC_DEBUG StgClosure * copyPAP (Capability *cap, StgPAP *oldpap) { uint32_t size = PAP_sizeW(oldpap->n_args); ===================================== rts/LdvProfile.c ===================================== @@ -58,7 +58,7 @@ bool isInherentlyUsed( StgHalfWord closure_type ) * closure. Returns the size of the closure, including the profiling * header portion, so that the caller can find the next closure. * ----------------------------------------------------------------------- */ -STATIC_INLINE uint32_t +STATIC_DEBUG uint32_t processHeapClosureForDead( const StgClosure *c ) { uint32_t size; ===================================== rts/Printer.c ===================================== @@ -58,7 +58,7 @@ void printObj( StgClosure *obj ) printClosure(obj); } -STATIC_INLINE void +STATIC_DEBUG void printStdObjHdr( const StgClosure *obj, char* tag ) { debugBelch("%s(",tag); ===================================== rts/ProfHeap.c ===================================== @@ -66,7 +66,7 @@ static const char *saved_locale = NULL; static locale_t prof_locale = 0, saved_locale = 0; #endif -STATIC_INLINE void +STATIC_DEBUG void init_prof_locale( void ) { #if !defined(mingw32_HOST_OS) @@ -80,7 +80,7 @@ init_prof_locale( void ) #endif } -STATIC_INLINE void +STATIC_DEBUG void free_prof_locale( void ) { #if !defined(mingw32_HOST_OS) @@ -91,7 +91,7 @@ free_prof_locale( void ) #endif } -STATIC_INLINE void +STATIC_DEBUG void set_prof_locale( void ) { #if defined(mingw32_HOST_OS) @@ -103,7 +103,7 @@ set_prof_locale( void ) #endif } -STATIC_INLINE void +STATIC_DEBUG void restore_locale( void ) { #if defined(mingw32_HOST_OS) @@ -154,7 +154,7 @@ typedef struct _counter { struct _counter *next; } counter; -STATIC_INLINE void +STATIC_DEBUG void initLDVCtr( counter *ctr ) { ctr->c.ldv.prim = 0; @@ -248,7 +248,7 @@ closureIdentity( const StgClosure *p ) * Profiling type predicates * ----------------------------------------------------------------------- */ #if defined(PROFILING) -STATIC_INLINE bool +STATIC_DEBUG bool doingLDVProfiling( void ) { return (RtsFlags.ProfFlags.doHeapProfile == HEAP_BY_LDV @@ -344,7 +344,7 @@ LDV_recordDead( const StgClosure *c, uint32_t size ) * Initialize censuses[era]; * ----------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void initEra(Census *census) { // N.B. When not LDV profiling we reinitialise the same Census over @@ -368,7 +368,7 @@ initEra(Census *census) census->drag_total = 0; } -STATIC_INLINE void +STATIC_DEBUG void freeEra(Census *census) { arenaFree(census->arena); ===================================== rts/RetainerProfile.c ===================================== @@ -113,7 +113,7 @@ endRetainerProfiling( void ) * In addition we mark all mutable objects as a retainers, the reason for * that decision is lost in time. * -------------------------------------------------------------------------- */ -STATIC_INLINE bool +STATIC_DEBUG bool isRetainer( const StgClosure *c ) { switch (get_itbl(c)->type) { @@ -231,7 +231,7 @@ isRetainer( const StgClosure *c ) * Invariants: * *c must be a retainer. * -------------------------------------------------------------------------- */ -STATIC_INLINE retainer +STATIC_DEBUG retainer getRetainerFrom( StgClosure *c ) { ASSERT(isRetainer(c)); @@ -246,7 +246,7 @@ getRetainerFrom( StgClosure *c ) * c != NULL * s != NULL * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void associate( StgClosure *c, RetainerSet *s ) { // StgWord has the same size as pointers, so the following type ===================================== rts/RetainerSet.c ===================================== @@ -51,7 +51,7 @@ RetainerSet rs_MANY = { /* ----------------------------------------------------------------------------- * calculate the size of a RetainerSet structure * -------------------------------------------------------------------------- */ -STATIC_INLINE size_t +STATIC_DEBUG size_t sizeofRetainerSet( int elems ) { return (sizeof(RetainerSet) + elems * sizeof(retainer)); ===================================== rts/RtsFlags.c ===================================== @@ -586,7 +586,7 @@ char** getUTF8Args(int* argc) } #endif -STATIC_INLINE bool strequal(const char *a, const char * b) +STATIC_DEBUG bool strequal(const char *a, const char * b) { return(strcmp(a, b) == 0); } ===================================== rts/Schedule.c ===================================== @@ -636,7 +636,7 @@ scheduleFindWork (Capability **pcap) } #if defined(THREADED_RTS) -STATIC_INLINE bool +STATIC_DEBUG bool shouldYieldCapability (Capability *cap, Task *task, bool didGcLast) { // we need to yield this capability to someone else if.. @@ -2400,7 +2400,7 @@ deleteAllThreads () Locks required: sched_mutex -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void suspendTask (Capability *cap, Task *task) { InCall *incall; @@ -2416,7 +2416,7 @@ suspendTask (Capability *cap, Task *task) cap->n_suspended_ccalls++; } -STATIC_INLINE void +STATIC_DEBUG void recoverSuspendedTask (Capability *cap, Task *task) { InCall *incall; ===================================== rts/StableName.c ===================================== @@ -55,7 +55,7 @@ stableNameUnlock(void) * Initialising the table * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void initSnEntryFreeList(snEntry *table, uint32_t n, snEntry *free) { snEntry *p; ===================================== rts/StablePtr.c ===================================== @@ -138,7 +138,7 @@ stablePtrUnlock(void) * Initialising the table * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void initSpEntryFreeList(spEntry *table, uint32_t n, spEntry *free) { spEntry *p; @@ -245,7 +245,7 @@ exitStablePtrTable(void) #endif } -STATIC_INLINE void +STATIC_DEBUG void freeSpEntry(spEntry *sp) { RELAXED_STORE(&sp->addr, (P_)stable_ptr_free); ===================================== rts/StaticPtrTable.c ===================================== @@ -21,14 +21,14 @@ static Mutex spt_lock; #endif /// Hash function for the SPT. -STATIC_INLINE int hashFingerprint(const HashTable *table, StgWord key) { +STATIC_DEBUG int hashFingerprint(const HashTable *table, StgWord key) { const StgWord64* ptr = (StgWord64*) key; // Take half of the key to compute the hash. return hashWord(table, *(ptr + 1)); } /// Comparison function for the SPT. -STATIC_INLINE int compareFingerprint(StgWord a, StgWord b) { +STATIC_DEBUG int compareFingerprint(StgWord a, StgWord b) { const StgWord64* ptra = (StgWord64*) a; const StgWord64* ptrb = (StgWord64*) b; return *ptra == *ptrb && *(ptra + 1) == *(ptrb + 1); ===================================== rts/StgPrimFloat.c ===================================== @@ -51,7 +51,7 @@ /** #15271: Some large ratios are converted into double incorrectly. * This occurs when StgInt has 64 bits and C int has 32 bits, where wrapping * occurs and an incorrect signed value is passed into ldexp */ -STATIC_INLINE int +STATIC_DEBUG int truncExponent(I_ e) { #if INT_MAX < STG_INT_MAX ===================================== rts/TraverseHeap.c ===================================== @@ -137,7 +137,7 @@ static inline void debug(const char *s, ...) * Invariants: * currentStack->link == s. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void newStackBlock( traverseState *ts, bdescr *bd ) { ts->currentStack = bd; @@ -152,7 +152,7 @@ newStackBlock( traverseState *ts, bdescr *bd ) * Invariants: * s->link == currentStack. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void returnToOldStack( traverseState *ts, bdescr *bd ) { ts->currentStack = bd; @@ -207,7 +207,7 @@ getTraverseStackMaxSize(traverseState *ts) /** * Returns true if the whole stack is empty. **/ -STATIC_INLINE bool +STATIC_DEBUG bool isEmptyWorkStack( traverseState *ts ) { return (ts->firstStack == ts->currentStack) && ts->stackTop == ts->stackLimit; @@ -235,7 +235,7 @@ traverseWorkStackBlocks(traverseState *ts) * * payload[] begins with ptrs pointers followed by non-pointers. */ -STATIC_INLINE void +STATIC_DEBUG void init_ptrs( stackPos *info, uint32_t ptrs, StgPtr payload ) { info->type = posTypePtrs; @@ -247,7 +247,7 @@ init_ptrs( stackPos *info, uint32_t ptrs, StgPtr payload ) /** * Find the next object from *info. */ -STATIC_INLINE StgClosure * +STATIC_DEBUG StgClosure * find_ptrs( stackPos *info ) { if (info->next.ptrs.pos < info->next.ptrs.ptrs) { @@ -260,7 +260,7 @@ find_ptrs( stackPos *info ) /** * Initializes *info from SRT information stored in *infoTable. */ -STATIC_INLINE void +STATIC_DEBUG void init_srt_fun( stackPos *info, const StgFunInfoTable *infoTable ) { info->type = posTypeSRT; @@ -271,7 +271,7 @@ init_srt_fun( stackPos *info, const StgFunInfoTable *infoTable ) } } -STATIC_INLINE void +STATIC_DEBUG void init_srt_thunk( stackPos *info, const StgThunkInfoTable *infoTable ) { info->type = posTypeSRT; @@ -285,7 +285,7 @@ init_srt_thunk( stackPos *info, const StgThunkInfoTable *infoTable ) /** * Find the next object from *info. */ -STATIC_INLINE StgClosure * +STATIC_DEBUG StgClosure * find_srt( stackPos *info ) { StgClosure *c; @@ -378,7 +378,7 @@ traversePushClosure(traverseState *ts, StgClosure *c, StgClosure *cp, stackData * Note: When pushing onto the stack we only really push one 'stackElement' * representing all children onto the stack. See traversePop() */ -STATIC_INLINE void +STATIC_DEBUG void traversePushChildren(traverseState *ts, StgClosure *c, stackData data, StgClosure **first_child) { stackElement se; @@ -667,7 +667,7 @@ popStackElement(traverseState *ts) { * * It is okay to call this function even when the work-stack is empty. */ -STATIC_INLINE void +STATIC_DEBUG void traversePop(traverseState *ts, StgClosure **c, StgClosure **cp, stackData *data) { stackElement *se; @@ -914,7 +914,7 @@ traverseLargeBitmap (traverseState *ts, StgPtr p, StgLargeBitmap *large_bitmap, } } -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr traverseSmallBitmap (traverseState *ts, StgPtr p, uint32_t size, StgWord bitmap, StgClosure *c, stackData data) { @@ -1051,7 +1051,7 @@ traversePushStack(traverseState *ts, StgClosure *cp, stackData data, /** * Call traversePushClosure for each of the children of a PAP/AP */ -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr traversePAP (traverseState *ts, StgClosure *pap, /* NOT tagged */ stackData data, ===================================== rts/sm/BlockAlloc.c ===================================== @@ -188,7 +188,7 @@ void initBlockAllocator(void) Accounting -------------------------------------------------------------------------- */ -STATIC_INLINE +STATIC_DEBUG void recordAllocatedBlocks(uint32_t node, uint32_t n) { n_alloc_blocks += n; @@ -198,7 +198,7 @@ void recordAllocatedBlocks(uint32_t node, uint32_t n) } } -STATIC_INLINE +STATIC_DEBUG void recordFreedBlocks(uint32_t node, uint32_t n) { ASSERT(n_alloc_blocks >= n); @@ -210,13 +210,13 @@ void recordFreedBlocks(uint32_t node, uint32_t n) Allocation -------------------------------------------------------------------------- */ -STATIC_INLINE bdescr * +STATIC_DEBUG bdescr * tail_of (bdescr *bd) { return bd + bd->blocks - 1; } -STATIC_INLINE void +STATIC_DEBUG void initGroup(bdescr *head) { head->free = head->start; @@ -248,7 +248,7 @@ initGroup(bdescr *head) #endif // log base 2 (floor), needs to support up to (2^NUM_FREE_LISTS)-1 -STATIC_INLINE uint32_t +STATIC_DEBUG uint32_t log_2(W_ n) { ASSERT(n > 0 && n < (1< 0 && n < (1<free < bd->start + BLOCK_SIZE_W * BLOCKS_PER_MBLOCK @@ -645,7 +645,7 @@ StgWord shouldCompact (StgCompactNFData *str, StgClosure *p) -------------------------------------------------------------------------- */ #if defined(DEBUG) -STATIC_INLINE void +STATIC_DEBUG void check_object_in_compact (StgCompactNFData *str, StgClosure *p) { bdescr *bd; @@ -780,7 +780,7 @@ void verifyCompact (StgCompactNFData *str USED_IF_DEBUG) Fixing up pointers -------------------------------------------------------------------------- */ -STATIC_INLINE bool +STATIC_DEBUG bool any_needs_fixup(StgCompactNFDataBlock *block) { // ->next pointers are always valid, even if some blocks were @@ -824,7 +824,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) } #endif -STATIC_INLINE StgCompactNFDataBlock * +STATIC_DEBUG StgCompactNFDataBlock * find_pointer(StgWord *fixup_table, uint32_t count, StgClosure *q) { StgWord address = (W_)q; ===================================== rts/sm/Compact.c ===================================== @@ -31,8 +31,8 @@ // Turn off inlining when debugging - it obfuscates things #if defined(DEBUG) -# undef STATIC_INLINE -# define STATIC_INLINE static +# undef STATIC_DEBUG +# define STATIC_DEBUG static #endif /* ---------------------------------------------------------------------------- @@ -69,13 +69,13 @@ pointer. ------------------------------------------------------------------------- */ -STATIC_INLINE W_ +STATIC_DEBUG W_ UNTAG_PTR(W_ p) { return p & ~TAG_MASK; } -STATIC_INLINE W_ +STATIC_DEBUG W_ GET_PTR_TAG(W_ p) { return p & TAG_MASK; @@ -124,7 +124,7 @@ get_iptr_tag(StgInfoTable *iptr) } } -STATIC_INLINE void +STATIC_DEBUG void thread (StgClosure **p) { StgClosure *q0 = *p; @@ -155,9 +155,9 @@ thread_root (void *user STG_UNUSED, StgClosure **p) // This version of thread() takes a (void *), used to circumvent // warnings from gcc about pointer punning and strict aliasing. -STATIC_INLINE void thread_ (void *p) { thread((StgClosure **)p); } +STATIC_DEBUG void thread_ (void *p) { thread((StgClosure **)p); } -STATIC_INLINE void +STATIC_DEBUG void unthread( const P_ p, W_ free, W_ tag ) { W_ q = *p; @@ -193,7 +193,7 @@ loop: // The info pointer is also tagged with the appropriate pointer tag // for this closure, which should be attached to the pointer // subsequently passed to unthread(). -STATIC_INLINE StgInfoTable* +STATIC_DEBUG StgInfoTable* get_threaded_info( P_ p ) { W_ q = (W_)GET_INFO(UNTAG_CLOSURE((StgClosure *)p)); @@ -217,7 +217,7 @@ loop: // A word-aligned memmove will be faster for small objects than libc's or gcc's. // Remember, the two regions *might* overlap, but: to <= from. -STATIC_INLINE void +STATIC_DEBUG void move(P_ to, P_ from, W_ size) { for(; size > 0; --size) { @@ -263,7 +263,7 @@ thread_static( StgClosure* p ) } } -STATIC_INLINE void +STATIC_DEBUG void thread_large_bitmap( P_ p, StgLargeBitmap *large_bitmap, W_ size ) { W_ b = 0; @@ -283,7 +283,7 @@ thread_large_bitmap( P_ p, StgLargeBitmap *large_bitmap, W_ size ) } } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_small_bitmap (P_ p, W_ size, W_ bitmap) { while (size > 0) { @@ -297,7 +297,7 @@ thread_small_bitmap (P_ p, W_ size, W_ bitmap) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_arg_block (StgFunInfoTable *fun_info, StgClosure **args) { W_ bitmap; @@ -395,7 +395,7 @@ thread_stack(P_ p, P_ stack_end) } } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_PAP_payload (StgClosure *fun, StgClosure **payload, W_ size) { StgFunInfoTable *fun_info = @@ -427,7 +427,7 @@ thread_PAP_payload (StgClosure *fun, StgClosure **payload, W_ size) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_PAP (StgPAP *pap) { P_ p = thread_PAP_payload(pap->fun, pap->payload, pap->n_args); @@ -435,7 +435,7 @@ thread_PAP (StgPAP *pap) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_AP (StgAP *ap) { P_ p = thread_PAP_payload(ap->fun, ap->payload, ap->n_args); @@ -443,7 +443,7 @@ thread_AP (StgAP *ap) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_AP_STACK (StgAP_STACK *ap) { thread(&ap->fun); @@ -618,7 +618,7 @@ update_fwd_large( bdescr *bd ) } // ToDo: too big to inline -static /* STATIC_INLINE */ P_ +static /* STATIC_DEBUG */ P_ thread_obj (const StgInfoTable *info, P_ p) { switch (info->type) { ===================================== rts/sm/Evac.c ===================================== @@ -58,14 +58,14 @@ #define MAX_THUNK_SELECTOR_DEPTH 16 static void eval_thunk_selector (StgClosure **q, StgSelector *p, bool); -STATIC_INLINE void evacuate_large(StgPtr p); +NOINLINE static void evacuate_large(StgPtr p); /* ----------------------------------------------------------------------------- Allocate some space in which to copy an object. -------------------------------------------------------------------------- */ /* size is in words */ -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr alloc_for_copy (uint32_t size, uint32_t gen_no) { ASSERT(gen_no < RtsFlags.GcFlags.generations); @@ -135,7 +135,7 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) -------------------------------------------------------------------------- */ /* size is in words */ -STATIC_INLINE GNUC_ATTR_HOT void +ALWAYS_INLINE STATIC_DEBUG GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -194,7 +194,7 @@ copy_tag(StgClosure **p, const StgInfoTable *info, } #if defined(PARALLEL_GC) && !defined(PROFILING) -STATIC_INLINE void +STATIC_DEBUG void copy_tag_nolock(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -283,7 +283,7 @@ spin: /* Copy wrappers that don't tag the closure after copying */ -STATIC_INLINE GNUC_ATTR_HOT void +ALWAYS_INLINE GNUC_ATTR_HOT static inline void copy(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no) { @@ -301,7 +301,7 @@ copy(StgClosure **p, const StgInfoTable *info, that has been evacuated, or unset otherwise. -------------------------------------------------------------------------- */ -static void +NOINLINE static void evacuate_large(StgPtr p) { bdescr *bd; @@ -383,7 +383,7 @@ evacuate_large(StgPtr p) - link_field must be STATIC_LINK(q) ------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void evacuate_static_object (StgClosure **link_field, StgClosure *q) { if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving)) { @@ -422,7 +422,7 @@ evacuate_static_object (StgClosure **link_field, StgClosure *q) It is assumed that objects in the struct live in the same generation as the struct itself all the time. ------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void evacuate_compact (StgPtr p) { StgCompactNFData *str; ===================================== rts/sm/MBlock.c ===================================== @@ -440,7 +440,7 @@ markHeapUnalloced(void *p) #if SIZEOF_VOID_P == 4 -STATIC_INLINE +STATIC_DEBUG void * mapEntryToMBlock(uint32_t i) { return (void *)((StgWord)i << MBLOCK_SHIFT); ===================================== rts/sm/NonMovingMark.c ===================================== @@ -419,7 +419,7 @@ void nonmovingFinishFlush(Task *task) * Pushing to either the mark queue or remembered set *********************************************************/ -STATIC_INLINE void +STATIC_DEBUG void push (MarkQueue *q, const MarkQueueEnt *ent) { // Are we at the end of the block? @@ -670,7 +670,7 @@ void updateRemembSetPushClosure_(StgRegTable *reg, struct StgClosure_ *p) updateRemembSetPushClosure(regTableToCapability(reg), p); } -STATIC_INLINE bool needs_upd_rem_set_mark(StgClosure *p) +STATIC_DEBUG bool needs_upd_rem_set_mark(StgClosure *p) { // TODO: Deduplicate with mark_closure bdescr *bd = Bdescr((StgPtr) p); @@ -690,7 +690,7 @@ STATIC_INLINE bool needs_upd_rem_set_mark(StgClosure *p) } /* Set the mark bit; only to be called *after* we have fully marked the closure */ -STATIC_INLINE void finish_upd_rem_set_mark(StgClosure *p) +STATIC_DEBUG void finish_upd_rem_set_mark(StgClosure *p) { bdescr *bd = Bdescr((StgPtr) p); if (bd->flags & BF_LARGE) { ===================================== rts/sm/Scav.c ===================================== @@ -284,7 +284,7 @@ static StgPtr scavenge_mut_arr_ptrs_marked (StgMutArrPtrs *a) return (StgPtr)a + mut_arr_ptrs_sizeW(a); } -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) { while (size > 0) { @@ -303,7 +303,7 @@ scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) in PAPs. -------------------------------------------------------------------------- */ -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr scavenge_arg_block (const StgFunInfoTable *fun_info, StgClosure **args) { StgPtr p; @@ -331,7 +331,7 @@ scavenge_arg_block (const StgFunInfoTable *fun_info, StgClosure **args) return p; } -STATIC_INLINE GNUC_ATTR_HOT StgPtr +STATIC_DEBUG GNUC_ATTR_HOT StgPtr scavenge_PAP_payload (StgClosure *fun, StgClosure **payload, StgWord size) { StgPtr p; ===================================== rts/sm/Storage.c ===================================== @@ -439,7 +439,7 @@ freeStorage (bool free_heap) -------------------------------------------------------------------------- */ -STATIC_INLINE StgInd * +STATIC_DEBUG StgInd * lockCAF (StgRegTable *reg, StgIndStatic *caf) { const StgInfoTable *orig_info; @@ -690,7 +690,7 @@ allocNursery (uint32_t node, bdescr *tail, W_ blocks) return &bd[0]; } -STATIC_INLINE void +STATIC_DEBUG void assignNurseryToCapability (Capability *cap, uint32_t n) { ASSERT(n < n_nurseries); @@ -899,7 +899,7 @@ move_STACK (StgStack *src, StgStack *dest) dest->sp = (StgPtr)dest->sp + diff; } -STATIC_INLINE void +STATIC_DEBUG void accountAllocation(Capability *cap, W_ n) { TICK_ALLOC_HEAP_NOCTR(WDS(n)); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f0e5cefcb432f0845003263ba46de211eeb6bc4...2faaae9a23369b3206f574e944d832df40476b94 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1f0e5cefcb432f0845003263ba46de211eeb6bc4...2faaae9a23369b3206f574e944d832df40476b94 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 Tue Nov 17 20:43:19 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 17 Nov 2020 15:43:19 -0500 Subject: [Git][ghc/ghc][wip/andreask/rts_inlining] 2 commits: Rename STATIC_INLINE to STATIC_DEBUG. Message-ID: <5fb435e784e02_73a8652847815703b@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/rts_inlining at Glasgow Haskell Compiler / GHC Commits: 6f0377b4 by Andreas Klebinger at 2020-11-17T21:42:28+01:00 Rename STATIC_INLINE to STATIC_DEBUG. STATIC_INLINE by default neither makes functions static nor does it mark them as inline. Even worse STATIC_INLINE *never* makes a function more likely to inline. But makes functions with an inline pragma *less* likely to inline by adding a static keyword if debugging is enabled. If you think this is quite confusing then that's because it is. I renamed this attribute to STATIC_DEBUG. This might not be a lot clearer at first thight, but I hope at least people won't wonder why something called *_INLINE doesn't make things inline in the future. - - - - - 408837f3 by Andreas Klebinger at 2020-11-17T21:42:58+01:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc refused to inline copy_tag into evacuate. To fix this we no set the always_inline attribute for copy and copy_tag to force inlining. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - 27 changed files: - compiler/cbits/genSym.c - includes/Rts.h - includes/Stg.h - rts/Capability.c - rts/FileLock.c - rts/Hash.c - rts/Interpreter.c - rts/LdvProfile.c - rts/Printer.c - rts/ProfHeap.c - rts/RetainerProfile.c - rts/RetainerSet.c - rts/RtsFlags.c - rts/Schedule.c - rts/StableName.c - rts/StablePtr.c - rts/StaticPtrTable.c - rts/StgPrimFloat.c - rts/TraverseHeap.c - rts/sm/BlockAlloc.c - rts/sm/CNF.c - rts/sm/Compact.c - rts/sm/Evac.c - rts/sm/MBlock.c - rts/sm/NonMovingMark.c - rts/sm/Scav.c - rts/sm/Storage.c Changes: ===================================== compiler/cbits/genSym.c ===================================== @@ -8,7 +8,7 @@ static HsInt GenSymInc = 1; #define UNIQUE_BITS (sizeof (HsInt) * 8 - UNIQUE_TAG_BITS) #define UNIQUE_MASK ((1ULL << UNIQUE_BITS) - 1) -STATIC_INLINE void checkUniqueRange(HsInt u STG_UNUSED) { +STATIC_DEBUG void checkUniqueRange(HsInt u STG_UNUSED) { #if DEBUG // Uh oh! We will overflow next time a unique is requested. assert(u != UNIQUE_MASK); ===================================== includes/Rts.h ===================================== @@ -37,12 +37,22 @@ extern "C" { #include "HsFFI.h" #include "RtsAPI.h" -// Turn off inlining when debugging - it obfuscates things +// Functions with "static inline" behave just like as if they had no +// keywords for the purpose of inlining. +// So we can use this to make a inline function less likely to inline +// when debugging. See also the gcc manual on inlining. Currently at +// https://gcc.gnu.org/onlinedocs/gcc-10.2.0/gcc/Inline.html#Inline +// This can be helpful since inlining obfuscates things. #if defined(DEBUG) -# undef STATIC_INLINE -# define STATIC_INLINE static +# undef STATIC_DEBUG +# define STATIC_DEBUG static #endif +// Fine grained inlining control helpers. +#define ALWAYS_INLINE __attribute__((always_inline)) +#define NOINLINE __attribute__((noinline)) + + #include "rts/Types.h" #include "rts/Time.h" ===================================== includes/Stg.h ===================================== @@ -128,7 +128,7 @@ /* * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) - * STATIC_INLINE is for inline functions in source files + * STATIC_DEBUG is for inline functions in source files * EXTERN_INLINE is for functions that we want to inline sometimes * (we also compile a static version of the function; see Inlines.c) */ @@ -140,7 +140,7 @@ // The problem, however, is with 'extern inline' whose semantics significantly // differs between gnu90 and C99 #define INLINE_HEADER static inline -#define STATIC_INLINE static inline +#define STATIC_DEBUG static inline // Figure out whether `__attributes__((gnu_inline))` is needed // to force gnu90-style 'external inline' semantics. ===================================== rts/Capability.c ===================================== @@ -81,7 +81,7 @@ Capability * rts_unsafeGetMyCapability (void) } #if defined(THREADED_RTS) -STATIC_INLINE bool +STATIC_DEBUG bool globalWorkToDo (void) { return RELAXED_LOAD(&sched_state) >= SCHED_INTERRUPTING @@ -199,7 +199,7 @@ anySparks (void) * -------------------------------------------------------------------------- */ #if defined(THREADED_RTS) -STATIC_INLINE void +STATIC_DEBUG void newReturningTask (Capability *cap, Task *task) { ASSERT_LOCK_HELD(&cap->lock); @@ -218,7 +218,7 @@ newReturningTask (Capability *cap, Task *task) ASSERT_RETURNING_TASKS(cap,task); } -STATIC_INLINE Task * +STATIC_DEBUG Task * popReturningTask (Capability *cap) { ASSERT_LOCK_HELD(&cap->lock); ===================================== rts/FileLock.c ===================================== @@ -34,14 +34,14 @@ static HashTable *key_hash; static Mutex file_lock_mutex; #endif -STATIC_INLINE int cmpLocks(StgWord w1, StgWord w2) +STATIC_DEBUG int cmpLocks(StgWord w1, StgWord w2) { Lock *l1 = (Lock *)w1; Lock *l2 = (Lock *)w2; return (l1->device == l2->device && l1->inode == l2->inode); } -STATIC_INLINE int hashLock(const HashTable *table, StgWord w) +STATIC_DEBUG int hashLock(const HashTable *table, StgWord w) { Lock *l = (Lock *)w; StgWord key = l->inode ^ (l->inode >> 32) ^ l->device ^ (l->device >> 32); ===================================== rts/Hash.c ===================================== @@ -99,13 +99,13 @@ hashStr(const HashTable *table, StgWord w) return bucket; } -STATIC_INLINE int +STATIC_DEBUG int compareWord(StgWord key1, StgWord key2) { return (key1 == key2); } -STATIC_INLINE int +STATIC_DEBUG int compareStr(StgWord key1, StgWord key2) { return (strcmp((char *)key1, (char *)key2) == 0); @@ -116,7 +116,7 @@ compareStr(StgWord key1, StgWord key2) * Allocate a new segment of the dynamically growing hash table. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void allocSegment(HashTable *table, int segment) { table->dir[segment] = stgMallocBytes(HSEGSIZE * sizeof(HashList *), @@ -130,7 +130,7 @@ allocSegment(HashTable *table, int segment) * by @table->split@ is affected by the expansion. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void expand(HashTable *table, HashFunction f) { int oldsegment; @@ -186,7 +186,7 @@ expand(HashTable *table, HashFunction f) return; } -STATIC_INLINE void* +STATIC_DEBUG void* lookupHashTable_inlined(const HashTable *table, StgWord key, HashFunction f, CompareFunction cmp) { @@ -310,7 +310,7 @@ freeHashList (HashTable *table, HashList *hl) table->freeList = hl; } -STATIC_INLINE void +STATIC_DEBUG void insertHashTable_inlined(HashTable *table, StgWord key, const void *data, HashFunction f) { @@ -358,7 +358,7 @@ insertStrHashTable(StrHashTable *table, const char * key, const void *data) insertHashTable_inlined(&table->table, (StgWord) key, data, hashStr); } -STATIC_INLINE void* +STATIC_DEBUG void* removeHashTable_inlined(HashTable *table, StgWord key, const void *data, HashFunction f, CompareFunction cmp) { ===================================== rts/Interpreter.c ===================================== @@ -145,7 +145,7 @@ #define SpW(n) (*(StgWord*)(Sp_plusW(n))) #define SpB(n) (*(StgWord*)(Sp_plusB(n))) -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr allocate_NONUPD (Capability *cap, int n_words) { return allocate(cap, stg_max(sizeofW(StgHeader)+MIN_PAYLOAD_SIZE, n_words)); @@ -243,7 +243,7 @@ void interp_shutdown ( void ) // Build a zero-argument PAP with the current CCS // See Note [Evaluating functions with profiling] in Apply.cmm // -STATIC_INLINE +STATIC_DEBUG StgClosure * newEmptyPAP (Capability *cap, StgClosure *tagged_obj, // a FUN or a BCO uint32_t arity) @@ -260,7 +260,7 @@ StgClosure * newEmptyPAP (Capability *cap, // Make an exact copy of a PAP, except that we combine the current CCS with the // CCS in the PAP. See Note [Evaluating functions with profiling] in Apply.cmm // -STATIC_INLINE +STATIC_DEBUG StgClosure * copyPAP (Capability *cap, StgPAP *oldpap) { uint32_t size = PAP_sizeW(oldpap->n_args); ===================================== rts/LdvProfile.c ===================================== @@ -58,7 +58,7 @@ bool isInherentlyUsed( StgHalfWord closure_type ) * closure. Returns the size of the closure, including the profiling * header portion, so that the caller can find the next closure. * ----------------------------------------------------------------------- */ -STATIC_INLINE uint32_t +STATIC_DEBUG uint32_t processHeapClosureForDead( const StgClosure *c ) { uint32_t size; ===================================== rts/Printer.c ===================================== @@ -58,7 +58,7 @@ void printObj( StgClosure *obj ) printClosure(obj); } -STATIC_INLINE void +STATIC_DEBUG void printStdObjHdr( const StgClosure *obj, char* tag ) { debugBelch("%s(",tag); ===================================== rts/ProfHeap.c ===================================== @@ -66,7 +66,7 @@ static const char *saved_locale = NULL; static locale_t prof_locale = 0, saved_locale = 0; #endif -STATIC_INLINE void +STATIC_DEBUG void init_prof_locale( void ) { #if !defined(mingw32_HOST_OS) @@ -80,7 +80,7 @@ init_prof_locale( void ) #endif } -STATIC_INLINE void +STATIC_DEBUG void free_prof_locale( void ) { #if !defined(mingw32_HOST_OS) @@ -91,7 +91,7 @@ free_prof_locale( void ) #endif } -STATIC_INLINE void +STATIC_DEBUG void set_prof_locale( void ) { #if defined(mingw32_HOST_OS) @@ -103,7 +103,7 @@ set_prof_locale( void ) #endif } -STATIC_INLINE void +STATIC_DEBUG void restore_locale( void ) { #if defined(mingw32_HOST_OS) @@ -154,7 +154,7 @@ typedef struct _counter { struct _counter *next; } counter; -STATIC_INLINE void +STATIC_DEBUG void initLDVCtr( counter *ctr ) { ctr->c.ldv.prim = 0; @@ -248,7 +248,7 @@ closureIdentity( const StgClosure *p ) * Profiling type predicates * ----------------------------------------------------------------------- */ #if defined(PROFILING) -STATIC_INLINE bool +STATIC_DEBUG bool doingLDVProfiling( void ) { return (RtsFlags.ProfFlags.doHeapProfile == HEAP_BY_LDV @@ -344,7 +344,7 @@ LDV_recordDead( const StgClosure *c, uint32_t size ) * Initialize censuses[era]; * ----------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void initEra(Census *census) { // N.B. When not LDV profiling we reinitialise the same Census over @@ -368,7 +368,7 @@ initEra(Census *census) census->drag_total = 0; } -STATIC_INLINE void +STATIC_DEBUG void freeEra(Census *census) { arenaFree(census->arena); ===================================== rts/RetainerProfile.c ===================================== @@ -113,7 +113,7 @@ endRetainerProfiling( void ) * In addition we mark all mutable objects as a retainers, the reason for * that decision is lost in time. * -------------------------------------------------------------------------- */ -STATIC_INLINE bool +STATIC_DEBUG bool isRetainer( const StgClosure *c ) { switch (get_itbl(c)->type) { @@ -231,7 +231,7 @@ isRetainer( const StgClosure *c ) * Invariants: * *c must be a retainer. * -------------------------------------------------------------------------- */ -STATIC_INLINE retainer +STATIC_DEBUG retainer getRetainerFrom( StgClosure *c ) { ASSERT(isRetainer(c)); @@ -246,7 +246,7 @@ getRetainerFrom( StgClosure *c ) * c != NULL * s != NULL * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void associate( StgClosure *c, RetainerSet *s ) { // StgWord has the same size as pointers, so the following type ===================================== rts/RetainerSet.c ===================================== @@ -51,7 +51,7 @@ RetainerSet rs_MANY = { /* ----------------------------------------------------------------------------- * calculate the size of a RetainerSet structure * -------------------------------------------------------------------------- */ -STATIC_INLINE size_t +STATIC_DEBUG size_t sizeofRetainerSet( int elems ) { return (sizeof(RetainerSet) + elems * sizeof(retainer)); ===================================== rts/RtsFlags.c ===================================== @@ -586,7 +586,7 @@ char** getUTF8Args(int* argc) } #endif -STATIC_INLINE bool strequal(const char *a, const char * b) +STATIC_DEBUG bool strequal(const char *a, const char * b) { return(strcmp(a, b) == 0); } ===================================== rts/Schedule.c ===================================== @@ -636,7 +636,7 @@ scheduleFindWork (Capability **pcap) } #if defined(THREADED_RTS) -STATIC_INLINE bool +STATIC_DEBUG bool shouldYieldCapability (Capability *cap, Task *task, bool didGcLast) { // we need to yield this capability to someone else if.. @@ -2400,7 +2400,7 @@ deleteAllThreads () Locks required: sched_mutex -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void suspendTask (Capability *cap, Task *task) { InCall *incall; @@ -2416,7 +2416,7 @@ suspendTask (Capability *cap, Task *task) cap->n_suspended_ccalls++; } -STATIC_INLINE void +STATIC_DEBUG void recoverSuspendedTask (Capability *cap, Task *task) { InCall *incall; ===================================== rts/StableName.c ===================================== @@ -55,7 +55,7 @@ stableNameUnlock(void) * Initialising the table * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void initSnEntryFreeList(snEntry *table, uint32_t n, snEntry *free) { snEntry *p; ===================================== rts/StablePtr.c ===================================== @@ -138,7 +138,7 @@ stablePtrUnlock(void) * Initialising the table * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void initSpEntryFreeList(spEntry *table, uint32_t n, spEntry *free) { spEntry *p; @@ -245,7 +245,7 @@ exitStablePtrTable(void) #endif } -STATIC_INLINE void +STATIC_DEBUG void freeSpEntry(spEntry *sp) { RELAXED_STORE(&sp->addr, (P_)stable_ptr_free); ===================================== rts/StaticPtrTable.c ===================================== @@ -21,14 +21,14 @@ static Mutex spt_lock; #endif /// Hash function for the SPT. -STATIC_INLINE int hashFingerprint(const HashTable *table, StgWord key) { +STATIC_DEBUG int hashFingerprint(const HashTable *table, StgWord key) { const StgWord64* ptr = (StgWord64*) key; // Take half of the key to compute the hash. return hashWord(table, *(ptr + 1)); } /// Comparison function for the SPT. -STATIC_INLINE int compareFingerprint(StgWord a, StgWord b) { +STATIC_DEBUG int compareFingerprint(StgWord a, StgWord b) { const StgWord64* ptra = (StgWord64*) a; const StgWord64* ptrb = (StgWord64*) b; return *ptra == *ptrb && *(ptra + 1) == *(ptrb + 1); ===================================== rts/StgPrimFloat.c ===================================== @@ -51,7 +51,7 @@ /** #15271: Some large ratios are converted into double incorrectly. * This occurs when StgInt has 64 bits and C int has 32 bits, where wrapping * occurs and an incorrect signed value is passed into ldexp */ -STATIC_INLINE int +STATIC_DEBUG int truncExponent(I_ e) { #if INT_MAX < STG_INT_MAX ===================================== rts/TraverseHeap.c ===================================== @@ -137,7 +137,7 @@ static inline void debug(const char *s, ...) * Invariants: * currentStack->link == s. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void newStackBlock( traverseState *ts, bdescr *bd ) { ts->currentStack = bd; @@ -152,7 +152,7 @@ newStackBlock( traverseState *ts, bdescr *bd ) * Invariants: * s->link == currentStack. * -------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void returnToOldStack( traverseState *ts, bdescr *bd ) { ts->currentStack = bd; @@ -207,7 +207,7 @@ getTraverseStackMaxSize(traverseState *ts) /** * Returns true if the whole stack is empty. **/ -STATIC_INLINE bool +STATIC_DEBUG bool isEmptyWorkStack( traverseState *ts ) { return (ts->firstStack == ts->currentStack) && ts->stackTop == ts->stackLimit; @@ -235,7 +235,7 @@ traverseWorkStackBlocks(traverseState *ts) * * payload[] begins with ptrs pointers followed by non-pointers. */ -STATIC_INLINE void +STATIC_DEBUG void init_ptrs( stackPos *info, uint32_t ptrs, StgPtr payload ) { info->type = posTypePtrs; @@ -247,7 +247,7 @@ init_ptrs( stackPos *info, uint32_t ptrs, StgPtr payload ) /** * Find the next object from *info. */ -STATIC_INLINE StgClosure * +STATIC_DEBUG StgClosure * find_ptrs( stackPos *info ) { if (info->next.ptrs.pos < info->next.ptrs.ptrs) { @@ -260,7 +260,7 @@ find_ptrs( stackPos *info ) /** * Initializes *info from SRT information stored in *infoTable. */ -STATIC_INLINE void +STATIC_DEBUG void init_srt_fun( stackPos *info, const StgFunInfoTable *infoTable ) { info->type = posTypeSRT; @@ -271,7 +271,7 @@ init_srt_fun( stackPos *info, const StgFunInfoTable *infoTable ) } } -STATIC_INLINE void +STATIC_DEBUG void init_srt_thunk( stackPos *info, const StgThunkInfoTable *infoTable ) { info->type = posTypeSRT; @@ -285,7 +285,7 @@ init_srt_thunk( stackPos *info, const StgThunkInfoTable *infoTable ) /** * Find the next object from *info. */ -STATIC_INLINE StgClosure * +STATIC_DEBUG StgClosure * find_srt( stackPos *info ) { StgClosure *c; @@ -378,7 +378,7 @@ traversePushClosure(traverseState *ts, StgClosure *c, StgClosure *cp, stackData * Note: When pushing onto the stack we only really push one 'stackElement' * representing all children onto the stack. See traversePop() */ -STATIC_INLINE void +STATIC_DEBUG void traversePushChildren(traverseState *ts, StgClosure *c, stackData data, StgClosure **first_child) { stackElement se; @@ -667,7 +667,7 @@ popStackElement(traverseState *ts) { * * It is okay to call this function even when the work-stack is empty. */ -STATIC_INLINE void +STATIC_DEBUG void traversePop(traverseState *ts, StgClosure **c, StgClosure **cp, stackData *data) { stackElement *se; @@ -914,7 +914,7 @@ traverseLargeBitmap (traverseState *ts, StgPtr p, StgLargeBitmap *large_bitmap, } } -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr traverseSmallBitmap (traverseState *ts, StgPtr p, uint32_t size, StgWord bitmap, StgClosure *c, stackData data) { @@ -1051,7 +1051,7 @@ traversePushStack(traverseState *ts, StgClosure *cp, stackData data, /** * Call traversePushClosure for each of the children of a PAP/AP */ -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr traversePAP (traverseState *ts, StgClosure *pap, /* NOT tagged */ stackData data, ===================================== rts/sm/BlockAlloc.c ===================================== @@ -188,7 +188,7 @@ void initBlockAllocator(void) Accounting -------------------------------------------------------------------------- */ -STATIC_INLINE +STATIC_DEBUG void recordAllocatedBlocks(uint32_t node, uint32_t n) { n_alloc_blocks += n; @@ -198,7 +198,7 @@ void recordAllocatedBlocks(uint32_t node, uint32_t n) } } -STATIC_INLINE +STATIC_DEBUG void recordFreedBlocks(uint32_t node, uint32_t n) { ASSERT(n_alloc_blocks >= n); @@ -210,13 +210,13 @@ void recordFreedBlocks(uint32_t node, uint32_t n) Allocation -------------------------------------------------------------------------- */ -STATIC_INLINE bdescr * +STATIC_DEBUG bdescr * tail_of (bdescr *bd) { return bd + bd->blocks - 1; } -STATIC_INLINE void +STATIC_DEBUG void initGroup(bdescr *head) { head->free = head->start; @@ -248,7 +248,7 @@ initGroup(bdescr *head) #endif // log base 2 (floor), needs to support up to (2^NUM_FREE_LISTS)-1 -STATIC_INLINE uint32_t +STATIC_DEBUG uint32_t log_2(W_ n) { ASSERT(n > 0 && n < (1< 0 && n < (1<free < bd->start + BLOCK_SIZE_W * BLOCKS_PER_MBLOCK @@ -645,7 +645,7 @@ StgWord shouldCompact (StgCompactNFData *str, StgClosure *p) -------------------------------------------------------------------------- */ #if defined(DEBUG) -STATIC_INLINE void +STATIC_DEBUG void check_object_in_compact (StgCompactNFData *str, StgClosure *p) { bdescr *bd; @@ -780,7 +780,7 @@ void verifyCompact (StgCompactNFData *str USED_IF_DEBUG) Fixing up pointers -------------------------------------------------------------------------- */ -STATIC_INLINE bool +STATIC_DEBUG bool any_needs_fixup(StgCompactNFDataBlock *block) { // ->next pointers are always valid, even if some blocks were @@ -824,7 +824,7 @@ spew_failing_pointer(StgWord *fixup_table, uint32_t count, StgWord address) } #endif -STATIC_INLINE StgCompactNFDataBlock * +STATIC_DEBUG StgCompactNFDataBlock * find_pointer(StgWord *fixup_table, uint32_t count, StgClosure *q) { StgWord address = (W_)q; ===================================== rts/sm/Compact.c ===================================== @@ -31,8 +31,8 @@ // Turn off inlining when debugging - it obfuscates things #if defined(DEBUG) -# undef STATIC_INLINE -# define STATIC_INLINE static +# undef STATIC_DEBUG +# define STATIC_DEBUG static #endif /* ---------------------------------------------------------------------------- @@ -69,13 +69,13 @@ pointer. ------------------------------------------------------------------------- */ -STATIC_INLINE W_ +STATIC_DEBUG W_ UNTAG_PTR(W_ p) { return p & ~TAG_MASK; } -STATIC_INLINE W_ +STATIC_DEBUG W_ GET_PTR_TAG(W_ p) { return p & TAG_MASK; @@ -124,7 +124,7 @@ get_iptr_tag(StgInfoTable *iptr) } } -STATIC_INLINE void +STATIC_DEBUG void thread (StgClosure **p) { StgClosure *q0 = *p; @@ -155,9 +155,9 @@ thread_root (void *user STG_UNUSED, StgClosure **p) // This version of thread() takes a (void *), used to circumvent // warnings from gcc about pointer punning and strict aliasing. -STATIC_INLINE void thread_ (void *p) { thread((StgClosure **)p); } +STATIC_DEBUG void thread_ (void *p) { thread((StgClosure **)p); } -STATIC_INLINE void +STATIC_DEBUG void unthread( const P_ p, W_ free, W_ tag ) { W_ q = *p; @@ -193,7 +193,7 @@ loop: // The info pointer is also tagged with the appropriate pointer tag // for this closure, which should be attached to the pointer // subsequently passed to unthread(). -STATIC_INLINE StgInfoTable* +STATIC_DEBUG StgInfoTable* get_threaded_info( P_ p ) { W_ q = (W_)GET_INFO(UNTAG_CLOSURE((StgClosure *)p)); @@ -217,7 +217,7 @@ loop: // A word-aligned memmove will be faster for small objects than libc's or gcc's. // Remember, the two regions *might* overlap, but: to <= from. -STATIC_INLINE void +STATIC_DEBUG void move(P_ to, P_ from, W_ size) { for(; size > 0; --size) { @@ -263,7 +263,7 @@ thread_static( StgClosure* p ) } } -STATIC_INLINE void +STATIC_DEBUG void thread_large_bitmap( P_ p, StgLargeBitmap *large_bitmap, W_ size ) { W_ b = 0; @@ -283,7 +283,7 @@ thread_large_bitmap( P_ p, StgLargeBitmap *large_bitmap, W_ size ) } } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_small_bitmap (P_ p, W_ size, W_ bitmap) { while (size > 0) { @@ -297,7 +297,7 @@ thread_small_bitmap (P_ p, W_ size, W_ bitmap) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_arg_block (StgFunInfoTable *fun_info, StgClosure **args) { W_ bitmap; @@ -395,7 +395,7 @@ thread_stack(P_ p, P_ stack_end) } } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_PAP_payload (StgClosure *fun, StgClosure **payload, W_ size) { StgFunInfoTable *fun_info = @@ -427,7 +427,7 @@ thread_PAP_payload (StgClosure *fun, StgClosure **payload, W_ size) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_PAP (StgPAP *pap) { P_ p = thread_PAP_payload(pap->fun, pap->payload, pap->n_args); @@ -435,7 +435,7 @@ thread_PAP (StgPAP *pap) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_AP (StgAP *ap) { P_ p = thread_PAP_payload(ap->fun, ap->payload, ap->n_args); @@ -443,7 +443,7 @@ thread_AP (StgAP *ap) return p; } -STATIC_INLINE P_ +STATIC_DEBUG P_ thread_AP_STACK (StgAP_STACK *ap) { thread(&ap->fun); @@ -618,7 +618,7 @@ update_fwd_large( bdescr *bd ) } // ToDo: too big to inline -static /* STATIC_INLINE */ P_ +static /* STATIC_DEBUG */ P_ thread_obj (const StgInfoTable *info, P_ p) { switch (info->type) { ===================================== rts/sm/Evac.c ===================================== @@ -58,14 +58,14 @@ #define MAX_THUNK_SELECTOR_DEPTH 16 static void eval_thunk_selector (StgClosure **q, StgSelector *p, bool); -STATIC_INLINE void evacuate_large(StgPtr p); +NOINLINE static void evacuate_large(StgPtr p); /* ----------------------------------------------------------------------------- Allocate some space in which to copy an object. -------------------------------------------------------------------------- */ /* size is in words */ -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr alloc_for_copy (uint32_t size, uint32_t gen_no) { ASSERT(gen_no < RtsFlags.GcFlags.generations); @@ -135,7 +135,7 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) -------------------------------------------------------------------------- */ /* size is in words */ -STATIC_INLINE GNUC_ATTR_HOT void +ALWAYS_INLINE STATIC_DEBUG GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -194,7 +194,7 @@ copy_tag(StgClosure **p, const StgInfoTable *info, } #if defined(PARALLEL_GC) && !defined(PROFILING) -STATIC_INLINE void +STATIC_DEBUG void copy_tag_nolock(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -283,7 +283,7 @@ spin: /* Copy wrappers that don't tag the closure after copying */ -STATIC_INLINE GNUC_ATTR_HOT void +ALWAYS_INLINE GNUC_ATTR_HOT static inline void copy(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no) { @@ -301,7 +301,7 @@ copy(StgClosure **p, const StgInfoTable *info, that has been evacuated, or unset otherwise. -------------------------------------------------------------------------- */ -static void +NOINLINE static void evacuate_large(StgPtr p) { bdescr *bd; @@ -383,7 +383,7 @@ evacuate_large(StgPtr p) - link_field must be STATIC_LINK(q) ------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void evacuate_static_object (StgClosure **link_field, StgClosure *q) { if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving)) { @@ -422,7 +422,7 @@ evacuate_static_object (StgClosure **link_field, StgClosure *q) It is assumed that objects in the struct live in the same generation as the struct itself all the time. ------------------------------------------------------------------------- */ -STATIC_INLINE void +STATIC_DEBUG void evacuate_compact (StgPtr p) { StgCompactNFData *str; ===================================== rts/sm/MBlock.c ===================================== @@ -440,7 +440,7 @@ markHeapUnalloced(void *p) #if SIZEOF_VOID_P == 4 -STATIC_INLINE +STATIC_DEBUG void * mapEntryToMBlock(uint32_t i) { return (void *)((StgWord)i << MBLOCK_SHIFT); ===================================== rts/sm/NonMovingMark.c ===================================== @@ -419,7 +419,7 @@ void nonmovingFinishFlush(Task *task) * Pushing to either the mark queue or remembered set *********************************************************/ -STATIC_INLINE void +STATIC_DEBUG void push (MarkQueue *q, const MarkQueueEnt *ent) { // Are we at the end of the block? @@ -670,7 +670,7 @@ void updateRemembSetPushClosure_(StgRegTable *reg, struct StgClosure_ *p) updateRemembSetPushClosure(regTableToCapability(reg), p); } -STATIC_INLINE bool needs_upd_rem_set_mark(StgClosure *p) +STATIC_DEBUG bool needs_upd_rem_set_mark(StgClosure *p) { // TODO: Deduplicate with mark_closure bdescr *bd = Bdescr((StgPtr) p); @@ -690,7 +690,7 @@ STATIC_INLINE bool needs_upd_rem_set_mark(StgClosure *p) } /* Set the mark bit; only to be called *after* we have fully marked the closure */ -STATIC_INLINE void finish_upd_rem_set_mark(StgClosure *p) +STATIC_DEBUG void finish_upd_rem_set_mark(StgClosure *p) { bdescr *bd = Bdescr((StgPtr) p); if (bd->flags & BF_LARGE) { ===================================== rts/sm/Scav.c ===================================== @@ -284,7 +284,7 @@ static StgPtr scavenge_mut_arr_ptrs_marked (StgMutArrPtrs *a) return (StgPtr)a + mut_arr_ptrs_sizeW(a); } -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) { while (size > 0) { @@ -303,7 +303,7 @@ scavenge_small_bitmap (StgPtr p, StgWord size, StgWord bitmap) in PAPs. -------------------------------------------------------------------------- */ -STATIC_INLINE StgPtr +STATIC_DEBUG StgPtr scavenge_arg_block (const StgFunInfoTable *fun_info, StgClosure **args) { StgPtr p; @@ -331,7 +331,7 @@ scavenge_arg_block (const StgFunInfoTable *fun_info, StgClosure **args) return p; } -STATIC_INLINE GNUC_ATTR_HOT StgPtr +STATIC_DEBUG GNUC_ATTR_HOT StgPtr scavenge_PAP_payload (StgClosure *fun, StgClosure **payload, StgWord size) { StgPtr p; ===================================== rts/sm/Storage.c ===================================== @@ -439,7 +439,7 @@ freeStorage (bool free_heap) -------------------------------------------------------------------------- */ -STATIC_INLINE StgInd * +STATIC_DEBUG StgInd * lockCAF (StgRegTable *reg, StgIndStatic *caf) { const StgInfoTable *orig_info; @@ -690,7 +690,7 @@ allocNursery (uint32_t node, bdescr *tail, W_ blocks) return &bd[0]; } -STATIC_INLINE void +STATIC_DEBUG void assignNurseryToCapability (Capability *cap, uint32_t n) { ASSERT(n < n_nurseries); @@ -899,7 +899,7 @@ move_STACK (StgStack *src, StgStack *dest) dest->sp = (StgPtr)dest->sp + diff; } -STATIC_INLINE void +STATIC_DEBUG void accountAllocation(Capability *cap, W_ n) { TICK_ALLOC_HEAP_NOCTR(WDS(n)); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2faaae9a23369b3206f574e944d832df40476b94...408837f38d382dc13dfdbc0174ff7139506d8371 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2faaae9a23369b3206f574e944d832df40476b94...408837f38d382dc13dfdbc0174ff7139506d8371 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 Tue Nov 17 22:49:43 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 17 Nov 2020 17:49:43 -0500 Subject: [Git][ghc/ghc][wip/T18234] 131 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fb4538752286_73a83fb01e52935c16345c@gitlab.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 84ad76d5 by Ben Gamari at 2020-11-17T17:49:31-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 747ed8b2 by Ben Gamari at 2020-11-17T17:49:31-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Data/EnumSet.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51b5386d586fb2bfea8f4ee010019dde935eac82...747ed8b286e3e17d485c2ed3a64519e727e47f3a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51b5386d586fb2bfea8f4ee010019dde935eac82...747ed8b286e3e17d485c2ed3a64519e727e47f3a 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 Tue Nov 17 23:34:02 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 17 Nov 2020 18:34:02 -0500 Subject: [Git][ghc/ghc][wip/T18234] gitlab-ci: Introduce a nightly cross-compilation job Message-ID: <5fb45dea336e_8313fd6c549242064351@gitlab.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: 95d2b07d by Ben Gamari at 2020-11-17T18:27:28-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 2 changed files: - .gitlab-ci.yml - .gitlab/ci.sh Changes: ===================================== .gitlab-ci.yml ===================================== @@ -257,6 +257,30 @@ validate-x86_64-linux-deb9-unreg-hadrian: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +validate-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*cross-compilation.*/' + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build needs: [lint-linters, lint-submods] ===================================== .gitlab/ci.sh ===================================== @@ -37,6 +37,7 @@ Modes: Environment variables: + CROSS_TARGET Triple of cross-compilation target. MSYSTEM (Windows-only) Which platform to build form (MINGW64 or MINGW32). Environment variables determining build configuration of Make system: @@ -104,11 +105,11 @@ function setup_locale() { function mingw_init() { case "$MSYSTEM" in MINGW32) - triple="i386-unknown-mingw32" + target_triple="i386-unknown-mingw32" boot_triple="i386-unknown-mingw32" # triple of bootstrap GHC ;; MINGW64) - triple="x86_64-unknown-mingw32" + target_triple="x86_64-unknown-mingw32" boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC ;; *) @@ -371,8 +372,8 @@ function configure() { end_section "booting" local target_args="" - if [[ -n "$triple" ]]; then - target_args="--target=$triple" + if [[ -n "$target_triple" ]]; then + target_args="--target=$target_triple" fi start_section "configuring" @@ -418,6 +419,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -438,6 +444,11 @@ function build_hadrian() { } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -524,6 +535,11 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95d2b07d218a5ba8865a887f0c19866d90f19c9a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95d2b07d218a5ba8865a887f0c19866d90f19c9a 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 Wed Nov 18 08:59:04 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Wed, 18 Nov 2020 03:59:04 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/amg/renamer-refactor Message-ID: <5fb4e258d7783_831938d1d8983ed@gitlab.mail> Adam Gundry pushed new branch wip/amg/renamer-refactor at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/amg/renamer-refactor 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 Wed Nov 18 09:55:25 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 04:55:25 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18932 Message-ID: <5fb4ef8daec91_8313fd6c538dfc01290cf@gitlab.mail> Sebastian Graf pushed new branch wip/T18932 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18932 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 Wed Nov 18 10:01:25 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 05:01:25 -0500 Subject: [Git][ghc/ghc][wip/con-info] 2 commits: Quality refactoring Message-ID: <5fb4f0f566685_83115cf233412943b@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 4f3e5fe9 by Matthew Pickering at 2020-11-18T09:53:19+00:00 Quality refactoring - - - - - 8ce72ae0 by Matthew Pickering at 2020-11-18T09:59:24+00:00 Revert changes to CoreToStg - - - - - 16 changed files: - compiler/GHC/CoreToStg.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/CoreToStg.hs ===================================== @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP, DeriveFunctor, TupleSections #-} +{-# LANGUAGE CPP, DeriveFunctor #-} -- -- (c) The GRASP/AQUA Project, Glasgow University, 1993-1998 @@ -22,6 +22,7 @@ import GHC.Core.Utils ( exprType, findDefault, isJoinBind , exprIsTickedString_maybe ) import GHC.Core.Opt.Arity ( manifestArity ) import GHC.Stg.Syntax +import GHC.Stg.Debug import GHC.Core.Type import GHC.Types.RepType @@ -33,7 +34,7 @@ import GHC.Core.DataCon import GHC.Types.CostCentre import GHC.Types.Var.Env import GHC.Unit.Module -import GHC.Types.Name ( getName, getOccName, occNameString, nameSrcSpan, isExternalName, nameModule_maybe ) +import GHC.Types.Name ( isExternalName, nameModule_maybe ) import GHC.Types.Basic ( Arity ) import GHC.Builtin.Types ( unboxedUnitDataCon, unitDataConId ) import GHC.Types.Literal @@ -48,16 +49,14 @@ import GHC.Driver.Ppr import GHC.Types.ForeignCall import GHC.Types.Demand ( isUsedOnce ) import GHC.Builtin.PrimOps ( PrimCall(..) ) +import GHC.Types.SrcLoc ( mkGeneralSrcSpan ) import GHC.Builtin.Names ( unsafeEqualityProofName ) -import GHC.Data.Maybe +import Control.Monad (ap) import Data.List.NonEmpty (nonEmpty, toList) -import Control.Monad (when, ap) +import Data.Maybe (fromMaybe) +import Data.Tuple (swap) import qualified Data.Set as Set -import Control.Monad.Trans.RWS -import GHC.Types.Unique.Map -import GHC.Types.SrcLoc -import Control.Applicative -- Note [Live vs free] -- ~~~~~~~~~~~~~~~~~~~ @@ -233,10 +232,15 @@ import Control.Applicative coreToStg :: DynFlags -> Module -> ModLocation -> CoreProgram -> ([StgTopBinding], InfoTableProvMap, CollectedCCs) coreToStg dflags this_mod ml pgm - = (pgm', denv, final_ccs) + = (pgm'', denv, final_ccs) where - (_, denv, (local_ccs, local_cc_stacks), pgm') - = coreTopBindsToStg dflags this_mod ml emptyVarEnv emptyInfoTableProvMap emptyCollectedCCs pgm + (_, (local_ccs, local_cc_stacks), pgm') + = coreTopBindsToStg dflags this_mod emptyVarEnv emptyCollectedCCs pgm + + (!pgm'', !denv) = + if gopt Opt_InfoTableMap dflags + then collectDebugInformation dflags ml pgm' + else (pgm', emptyInfoTableProvMap) prof = WayProf `Set.member` ways dflags @@ -253,49 +257,45 @@ coreToStg dflags this_mod ml pgm coreTopBindsToStg :: DynFlags -> Module - -> ModLocation -> IdEnv HowBound -- environment for the bindings - -> InfoTableProvMap -> CollectedCCs -> CoreProgram - -> (IdEnv HowBound, InfoTableProvMap,CollectedCCs, [StgTopBinding]) + -> (IdEnv HowBound, CollectedCCs, [StgTopBinding]) -coreTopBindsToStg _ _ _ env denv ccs [] - = (env, denv, ccs, []) -coreTopBindsToStg dflags this_mod ml env denv ccs (b:bs) - = (env2, denv2, ccs2, b':bs') +coreTopBindsToStg _ _ env ccs [] + = (env, ccs, []) +coreTopBindsToStg dflags this_mod env ccs (b:bs) + = (env2, ccs2, b':bs') where - (env1, denv1, ccs1, b' ) = - coreTopBindToStg dflags this_mod ml env denv ccs b - (env2, denv2, ccs2, bs') = - coreTopBindsToStg dflags this_mod ml env1 denv1 ccs1 bs + (env1, ccs1, b' ) = + coreTopBindToStg dflags this_mod env ccs b + (env2, ccs2, bs') = + coreTopBindsToStg dflags this_mod env1 ccs1 bs coreTopBindToStg :: DynFlags -> Module - -> ModLocation -> IdEnv HowBound - -> InfoTableProvMap -> CollectedCCs -> CoreBind - -> (IdEnv HowBound, InfoTableProvMap, CollectedCCs, StgTopBinding) + -> (IdEnv HowBound, CollectedCCs, StgTopBinding) -coreTopBindToStg _ _ _ env dcenv ccs (NonRec id e) +coreTopBindToStg _ _ env ccs (NonRec id e) | Just str <- exprIsTickedString_maybe e -- top-level string literal -- See Note [Core top-level string literals] in GHC.Core = let env' = extendVarEnv env id how_bound how_bound = LetBound TopLet 0 - in (env', dcenv, ccs, StgTopStringLit id str) + in (env', ccs, StgTopStringLit id str) -coreTopBindToStg dflags this_mod ml env dcenv ccs (NonRec id rhs) +coreTopBindToStg dflags this_mod env ccs (NonRec id rhs) = let env' = extendVarEnv env id how_bound how_bound = LetBound TopLet $! manifestArity rhs - ((stg_rhs, ccs'), denv) = - initCts dflags ml env dcenv $ + (stg_rhs, ccs') = + initCts dflags env $ coreToTopStgRhs dflags ccs this_mod (id,rhs) bind = StgTopLifted $ StgNonRec id stg_rhs @@ -304,9 +304,9 @@ coreTopBindToStg dflags this_mod ml env dcenv ccs (NonRec id rhs) -- as well as 'id', but that led to a black hole -- where printing the assertion error tripped the -- assertion again! - (env', denv, ccs', bind) + (env', ccs', bind) -coreTopBindToStg dflags this_mod ml env dcenv ccs (Rec pairs) +coreTopBindToStg dflags this_mod env ccs (Rec pairs) = ASSERT( not (null pairs) ) let binders = map fst pairs @@ -316,18 +316,14 @@ coreTopBindToStg dflags this_mod ml env dcenv ccs (Rec pairs) env' = extendVarEnvList env extra_env' -- generate StgTopBindings and CAF cost centres created for CAFs - ((ccs', stg_rhss), dcenv') - = initCts dflags ml env' dcenv $ do - mapAccumLM (\ccs rhs -> do - (rhs', ccs') <- - coreToTopStgRhs dflags ccs this_mod rhs - return (ccs', rhs')) - ccs - pairs - + (ccs', stg_rhss) + = initCts dflags env' $ + mapAccumLM (\ccs rhs -> swap <$> coreToTopStgRhs dflags ccs this_mod rhs) + ccs + pairs bind = StgTopLifted $ StgRec (zip binders stg_rhss) in - (env', dcenv', ccs', bind) + (env', ccs', bind) coreToTopStgRhs :: DynFlags @@ -344,14 +340,6 @@ coreToTopStgRhs dflags ccs this_mod (bndr, rhs) stg_arity = stgRhsArity stg_rhs - ; modLoc <- ctsModLocation - ; let - thisFile = maybe nilFS mkFastString $ ml_hs_file modLoc - best_span = quickSourcePos thisFile new_rhs - ; case stg_rhs of - StgRhsClosure {} -> - recordStgIdPosition bndr best_span (((, occNameString (getOccName bndr))) <$> (srcSpanToRealSrcSpan (nameSrcSpan (getName bndr)))) - _ -> return () ; return (ASSERT2( arity_ok stg_arity, mk_arity_msg stg_arity) stg_rhs, ccs') } where @@ -422,12 +410,12 @@ coreToStgExpr expr@(Lam _ _) return result_expr coreToStgExpr (Tick tick expr) - = do let k = case tick of - HpcTick{} -> id - ProfNote{} -> id - SourceNote ss fp -> withSpan (ss, fp) - Breakpoint{} -> panic "coreToStgExpr: breakpoint should not happen" - expr2 <- k (coreToStgExpr expr) + = do case tick of + HpcTick{} -> return () + ProfNote{} -> return () + SourceNote{} -> return () + Breakpoint{} -> panic "coreToStgExpr: breakpoint should not happen" + expr2 <- coreToStgExpr expr return (StgTick tick expr2) coreToStgExpr (Cast expr _) @@ -552,32 +540,30 @@ coreToStgApp f args ticks = do saturated = f_arity <= n_val_args res_ty = exprType (mkApps (Var f) args) - app <- case idDetails f of + app = case idDetails f of DataConWorkId dc - | saturated -> do - u <- incDc dc - return $ StgConApp dc u args' --(Just u) args' - (dropRuntimeRepArgs (fromMaybe [] (tyConAppArgs_maybe res_ty))) + | saturated -> StgConApp dc Nothing args' + (dropRuntimeRepArgs (fromMaybe [] (tyConAppArgs_maybe res_ty))) -- Some primitive operator that might be implemented as a library call. -- As noted by Note [Eta expanding primops] in GHC.Builtin.PrimOps -- we require that primop applications be saturated. PrimOpId op -> ASSERT( saturated ) - return $ StgOpApp (StgPrimOp op) args' res_ty + StgOpApp (StgPrimOp op) args' res_ty -- A call to some primitive Cmm function. FCallId (CCall (CCallSpec (StaticTarget _ lbl (Just pkgId) True) PrimCallConv _)) -> ASSERT( saturated ) - return $ StgOpApp (StgPrimCallOp (PrimCall lbl pkgId)) args' res_ty + StgOpApp (StgPrimCallOp (PrimCall lbl pkgId)) args' res_ty -- A regular foreign call. FCallId call -> ASSERT( saturated ) - return $ StgOpApp (StgFCallOp call (idType f)) args' res_ty + StgOpApp (StgFCallOp call (idType f)) args' res_ty TickBoxOpId {} -> pprPanic "coreToStg TickBox" $ ppr (f,args') - _other -> return $ StgApp f args' - let + _other -> StgApp f args' + tapp = foldr StgTick app (ticks ++ ticks') -- Forcing these fixes a leak in the code generator, noticed while @@ -613,7 +599,7 @@ coreToStgArgs (arg : args) = do -- Non-type argument (aticks, arg'') = stripStgTicksTop tickishFloatable arg' stg_arg = case arg'' of StgApp v [] -> StgVarArg v - StgConApp con _n [] _ -> StgVarArg (dataConWorkId con) + StgConApp con _ [] _ -> StgVarArg (dataConWorkId con) StgLit lit -> StgLitArg lit _ -> pprPanic "coreToStgArgs" (ppr arg) @@ -695,23 +681,7 @@ coreToStgRhs :: (Id,CoreExpr) coreToStgRhs (bndr, rhs) = do new_rhs <- coreToStgExpr rhs - modLoc <- ctsModLocation - let - thisFile = maybe nilFS mkFastString $ ml_hs_file modLoc - best_span = quickSourcePos thisFile new_rhs - let new_stg_rhs = (mkStgRhs bndr new_rhs) - case new_stg_rhs of - StgRhsClosure {} -> - recordStgIdPosition bndr best_span (((, occNameString (getOccName bndr))) <$> (srcSpanToRealSrcSpan (nameSrcSpan (getName bndr)))) - _ -> return () - return new_stg_rhs - - -quickSourcePos :: FastString -> StgExpr -> Maybe (RealSrcSpan, String) -quickSourcePos cur_mod (StgTick (SourceNote ss m) e) - | srcSpanFile ss == cur_mod = Just (ss, m) - | otherwise = quickSourcePos cur_mod e -quickSourcePos _ _ = Nothing + return (mkStgRhs bndr new_rhs) -- Generate a top-level RHS. Any new cost centres generated for CAFs will be -- appended to `CollectedCCs` argument. @@ -727,13 +697,13 @@ mkTopStgRhs dflags this_mod ccs bndr rhs (toList bndrs) body , ccs ) - | StgConApp con n args _ <- unticked_rhs + | StgConApp con mn args _ <- unticked_rhs , -- Dynamic StgConApps are updatable not (isDllConApp dflags this_mod con args) = -- CorePrep does this right, but just to make sure ASSERT2( not (isUnboxedTupleDataCon con || isUnboxedSumDataCon con) , ppr bndr $$ ppr con $$ ppr args) - ( StgRhsCon dontCareCCS con n args, ccs ) + ( StgRhsCon dontCareCCS con mn ticks args, ccs ) -- Otherwise it's a CAF, see Note [Cost-centre initialization plan]. | gopt Opt_AutoSccsOnIndividualCafs dflags @@ -749,7 +719,7 @@ mkTopStgRhs dflags this_mod ccs bndr rhs , ccs ) where - unticked_rhs = stripStgTicksTopE (not . tickishIsCode) rhs + (ticks, unticked_rhs) = stripStgTicksTop (not . tickishIsCode) rhs upd_flag | isUsedOnce (idDemandInfo bndr) = SingleEntry | otherwise = Updatable @@ -783,15 +753,15 @@ mkStgRhs bndr rhs ReEntrant -- ignored for LNE [] rhs - | StgConApp con mu args _ <- unticked_rhs - = StgRhsCon currentCCS con mu args + | StgConApp con mn args _ <- unticked_rhs + = StgRhsCon currentCCS con mn ticks args | otherwise = StgRhsClosure noExtFieldSilent currentCCS upd_flag [] rhs where - unticked_rhs = stripStgTicksTopE (not . tickishIsCode) rhs + (ticks, unticked_rhs) = stripStgTicksTop (not . tickishIsCode) rhs upd_flag | isUsedOnce (idDemandInfo bndr) = SingleEntry | otherwise = Updatable @@ -857,9 +827,8 @@ isPAP env _ = False newtype CtsM a = CtsM { unCtsM :: DynFlags -- Needed for checking for bad coercions in coreToStgArgs - -> ModLocation -> IdEnv HowBound - -> RWS (Maybe (RealSrcSpan, String)) () InfoTableProvMap a + -> a } deriving (Functor) @@ -895,10 +864,8 @@ data LetInfo -- The std monad functions: -initCts :: DynFlags -> ModLocation -> IdEnv HowBound -> InfoTableProvMap -> CtsM a -> (a, InfoTableProvMap) -initCts dflags ml env u m = - let (a, d, ()) = runRWS (unCtsM m dflags ml env) Nothing u - in (a, d) +initCts :: DynFlags -> IdEnv HowBound -> CtsM a -> a +initCts dflags env m = unCtsM m dflags env @@ -906,14 +873,11 @@ initCts dflags ml env u m = {-# INLINE returnCts #-} returnCts :: a -> CtsM a -returnCts e = CtsM $ \_ _ _ -> return e +returnCts e = CtsM $ \_ _ -> e thenCts :: CtsM a -> (a -> CtsM b) -> CtsM b -thenCts m k = CtsM $ \dflags ml env - -> do - a <- (unCtsM m dflags ml env) - unCtsM (k a) dflags ml env - +thenCts m k = CtsM $ \dflags env + -> unCtsM (k (unCtsM m dflags env)) dflags env instance Applicative CtsM where pure = returnCts @@ -923,49 +887,23 @@ instance Monad CtsM where (>>=) = thenCts instance HasDynFlags CtsM where - getDynFlags = CtsM $ \dflags _ _ -> return dflags + getDynFlags = CtsM $ \dflags _ -> dflags -- Functions specific to this monad: extendVarEnvCts :: [(Id, HowBound)] -> CtsM a -> CtsM a extendVarEnvCts ids_w_howbound expr - = CtsM $ \dflags ml env - -> unCtsM expr dflags ml (extendVarEnvList env ids_w_howbound) + = CtsM $ \dflags env + -> unCtsM expr dflags (extendVarEnvList env ids_w_howbound) lookupVarCts :: Id -> CtsM HowBound -lookupVarCts v = CtsM $ \_ _ env -> return $ lookupBinding env v +lookupVarCts v = CtsM $ \_ env -> lookupBinding env v lookupBinding :: IdEnv HowBound -> Id -> HowBound lookupBinding env v = case lookupVarEnv env v of Just xx -> xx Nothing -> ASSERT2( isGlobalId v, ppr v ) ImportBound -incDc :: DataCon -> CtsM (Maybe Int) -incDc dc | isUnboxedTupleDataCon dc = return Nothing -incDc dc | isUnboxedSumDataCon dc = return Nothing -incDc dc = CtsM $ \dflags _ _ -> if not (gopt Opt_DistinctConstructorTables dflags) then return Nothing else do - env <- get - cc <- ask - let dcMap' = alterUniqMap (maybe (Just [(0, cc)]) (\xs@((k, _):_) -> Just ((k + 1, cc) : xs))) (provDC env) dc - put (env { provDC = dcMap' }) - let r = lookupUniqMap dcMap' dc - return (fst . head <$> r) - -recordStgIdPosition :: Id -> Maybe (RealSrcSpan, String) -> Maybe (RealSrcSpan, String) -> CtsM () -recordStgIdPosition id best_span ss = CtsM $ \dflags _ _ -> when (gopt Opt_InfoTableMap dflags) $ do - cc <- ask - let tyString = showPpr dflags (idType id) - --pprTraceM "recordStgIdPosition" (ppr id $$ ppr cc $$ ppr ss) - case best_span <|> ss <|> cc of - Nothing -> return () - Just (rss, d) -> modify (\env -> env { provClosure = addToUniqMap (provClosure env) (idName id) (tyString, rss, d)}) - -withSpan :: (RealSrcSpan, String) -> CtsM a -> CtsM a -withSpan s (CtsM act) = CtsM (\a b c -> local (const $ Just s) (act a b c)) - -ctsModLocation :: CtsM ModLocation -ctsModLocation = CtsM (\_ ml _ -> return ml) - getAllCAFsCC :: Module -> (CostCentre, CostCentreStack) getAllCAFsCC this_mod = let ===================================== compiler/GHC/Stg/CSE.hs ===================================== @@ -290,8 +290,8 @@ stgCseTopLvlRhs :: InScopeSet -> InStgRhs -> OutStgRhs stgCseTopLvlRhs in_scope (StgRhsClosure ext ccs upd args body) = let body' = stgCseExpr (initEnv in_scope) body in StgRhsClosure ext ccs upd args body' -stgCseTopLvlRhs _ (StgRhsCon ccs dataCon mu args) - = StgRhsCon ccs dataCon mu args +stgCseTopLvlRhs _ (StgRhsCon ccs dataCon mu ticks args) + = StgRhsCon ccs dataCon mu ticks args ------------------------------ -- The actual AST traversal -- @@ -395,7 +395,7 @@ stgCsePairs env0 ((b,e):pairs) -- The RHS of a binding. -- If it is a constructor application, either short-cut it or extend the environment stgCseRhs :: CseEnv -> OutId -> InStgRhs -> (Maybe (OutId, OutStgRhs), CseEnv) -stgCseRhs env bndr (StgRhsCon ccs dataCon mu args) +stgCseRhs env bndr (StgRhsCon ccs dataCon mu ticks args) | Just other_bndr <- envLookup dataCon args' env , not (isWeakLoopBreaker (idOccInfo bndr)) -- See Note [Care with loop breakers] = let env' = addSubst bndr other_bndr env @@ -403,7 +403,7 @@ stgCseRhs env bndr (StgRhsCon ccs dataCon mu args) | otherwise = let env' = addDataCon bndr dataCon args' env -- see note [Case 1: CSEing allocated closures] - pair = (bndr, StgRhsCon ccs dataCon mu args') + pair = (bndr, StgRhsCon ccs dataCon mu ticks args') in (Just pair, env') where args' = substArgs env args ===================================== compiler/GHC/Stg/Debug.hs ===================================== @@ -0,0 +1,137 @@ +{-# LANGUAGE TupleSections #-} +-- This module contains functions which implement +-- the -finfo-table-map and -fdistinct-constructor-tables flags +module GHC.Stg.Debug(collectDebugInformation) where + + +import GHC.Prelude + +import GHC.Core +import GHC.Stg.Syntax + +import GHC.Types.Id +import GHC.Core.DataCon +import GHC.Types.CostCentre +import GHC.Unit.Module +import GHC.Types.Name ( getName, getOccName, occNameString, nameSrcSpan) +import GHC.Data.FastString +import GHC.Driver.Session +import GHC.Driver.Ppr + +import Control.Monad (when) +import Control.Monad.Trans.RWS +import GHC.Types.Unique.Map +import GHC.Types.SrcLoc +import Control.Applicative +import GHC.Utils.Outputable + +data R = R { rDynFlags :: DynFlags, rModLocation :: ModLocation, rSpan :: Maybe (RealSrcSpan, String) } + +type M a = RWS R () InfoTableProvMap a + +withSpan :: (RealSrcSpan, String) -> M a -> M a +withSpan s act = local (\r -> r { rSpan = Just s }) act + +collectDebugInformation :: DynFlags -> ModLocation -> [StgTopBinding] -> ([StgTopBinding], InfoTableProvMap) +collectDebugInformation dflags ml bs = case runRWS (mapM collectTop bs) (R dflags ml Nothing) emptyInfoTableProvMap of + (bs', m, _) -> (bs', m) + +collectTop :: StgTopBinding -> M StgTopBinding +collectTop (StgTopLifted t) = StgTopLifted <$> collectStgBind t +collectTop tb = return tb + +collectStgBind :: StgBinding -> M StgBinding +collectStgBind (StgNonRec bndr rhs) = do + rhs' <- collectStgRhs bndr rhs + return (StgNonRec bndr rhs') +collectStgBind (StgRec pairs) = do + es <- mapM (\(b, e) -> (b,) <$> collectStgRhs b e) pairs + return (StgRec es) + +collectStgRhs :: Id -> StgRhs -> M StgRhs +collectStgRhs bndr (StgRhsClosure ext cc us bs e)= do + e' <- collectExpr e + recordInfo bndr e' + return $ StgRhsClosure ext cc us bs e' +collectStgRhs _bndr (StgRhsCon cc dc _n ticks args) = do + n' <- incDc dc ticks + return (StgRhsCon cc dc n' ticks args) + + +recordInfo :: Id -> StgExpr -> M () +recordInfo bndr new_rhs = do + modLoc <- asks rModLocation + let + thisFile = maybe nilFS mkFastString $ ml_hs_file modLoc + best_span = quickSourcePos thisFile new_rhs + recordStgIdPosition bndr best_span (((, occNameString (getOccName bndr))) <$> (srcSpanToRealSrcSpan (nameSrcSpan (getName bndr)))) + +collectExpr :: StgExpr -> M StgExpr +collectExpr = go + where + go (StgApp occ as) = return $ StgApp occ as + go (StgLit lit) = return $ StgLit lit + go (StgConApp dc _n as tys) = do + n' <- incDc dc [] + return (StgConApp dc n' as tys) + go (StgOpApp op as ty) = return (StgOpApp op as ty) + go (StgLam bs e) = StgLam bs <$> collectExpr e + go (StgCase scrut bndr ty alts) = + StgCase <$> collectExpr scrut <*> pure bndr <*> pure ty <*> mapM collectAlts alts + go (StgLet ext bind body) = do + bind' <- collectStgBind bind + body' <- go body + return (StgLet ext bind' body') + go (StgLetNoEscape ext bind body) = do + bind' <- collectStgBind bind + body' <- go body + return (StgLetNoEscape ext bind' body') + + go (StgTick tick e) = do + let k = case tick of + SourceNote ss fp -> withSpan (ss, fp) + _ -> id + e' <- k (go e) + return (StgTick tick e') + +collectAlts :: StgAlt -> M StgAlt +collectAlts (ac, bs, e) = (ac, bs, ) <$> collectExpr e + + +--runM dflags ml act = runRWS act (dflags, ml) + + +quickSourcePos :: FastString -> StgExpr -> Maybe (RealSrcSpan, String) +quickSourcePos cur_mod (StgTick (SourceNote ss m) e) + | srcSpanFile ss == cur_mod = Just (ss, m) + | otherwise = quickSourcePos cur_mod e +quickSourcePos _ _ = Nothing + +incDc :: DataCon -> [Tickish Id] -> M (Maybe Int) +incDc dc _ | isUnboxedTupleDataCon dc = return Nothing +incDc dc _ | isUnboxedSumDataCon dc = return Nothing +incDc dc ts = do + dflags <- asks rDynFlags + if not (gopt Opt_DistinctConstructorTables dflags) then return Nothing else do + env <- get + mcc <- asks rSpan + let best_span = selectTick ts <|> mcc + let dcMap' = alterUniqMap (maybe (Just [(0, best_span)]) (\xs@((k, _):_) -> Just ((k + 1, best_span) : xs))) (provDC env) dc + put (env { provDC = dcMap' }) + let r = lookupUniqMap dcMap' dc + return (fst . head <$> r) + +selectTick :: [Tickish Id] -> Maybe (RealSrcSpan, String) +selectTick [] = Nothing +selectTick (SourceNote rss d : ts ) = selectTick ts <|> Just (rss, d) + +recordStgIdPosition :: Id -> Maybe (RealSrcSpan, String) -> Maybe (RealSrcSpan, String) -> M () +recordStgIdPosition id best_span ss = do + dflags <- asks rDynFlags + when (gopt Opt_InfoTableMap dflags) $ do + let tyString = showPpr dflags (idType id) + cc <- asks rSpan + pprTraceM "recordStgIdPosition" (ppr id $$ ppr cc $$ ppr best_span $$ ppr ss) + case best_span <|> cc <|> ss of + Nothing -> return () + Just (rss, d) -> modify (\env -> env { provClosure = addToUniqMap (provClosure env) (idName id) (tyString, rss, d)}) ===================================== compiler/GHC/Stg/DepAnal.hs ===================================== @@ -62,7 +62,7 @@ annTopBindingsDeps this_mod bs = zip bs (map top_bind bs) rhs bounds (StgRhsClosure _ _ _ as e) = expr (extendVarSetList bounds as) e - rhs bounds (StgRhsCon _ _ _ as) = + rhs bounds (StgRhsCon _ _ _ _ as) = args bounds as var :: BVs -> Var -> FVs ===================================== compiler/GHC/Stg/FVs.hs ===================================== @@ -159,7 +159,7 @@ rhs env (StgRhsClosure _ ccs uf bndrs body) -- See Note [Tracking local binders] (body', body_fvs) = expr (addLocals bndrs env) body fvs = delDVarSetList body_fvs bndrs -rhs env (StgRhsCon ccs dc mu as) = (StgRhsCon ccs dc mu as, args env as) +rhs env (StgRhsCon ccs dc mu ts as) = (StgRhsCon ccs dc mu ts as, args env as) alt :: Env -> StgAlt -> (CgStgAlt, DIdSet) alt env (con, bndrs, e) = ((con, bndrs, e'), fvs) ===================================== compiler/GHC/Stg/Lift.hs ===================================== @@ -199,9 +199,9 @@ liftRhs -- as lambda binders, discarding all free vars. -> LlStgRhs -> LiftM OutStgRhs -liftRhs mb_former_fvs rhs@(StgRhsCon ccs con mn args) +liftRhs mb_former_fvs rhs@(StgRhsCon ccs con mn ts args) = ASSERT2(isNothing mb_former_fvs, text "Should never lift a constructor" $$ pprStgRhs panicStgPprOpts rhs) - StgRhsCon ccs con mn <$> traverse liftArgs args + StgRhsCon ccs con mn ts <$> traverse liftArgs args liftRhs Nothing (StgRhsClosure _ ccs upd infos body) = -- This RHS wasn't lifted. withSubstBndrs (map binderInfoBndr infos) $ \bndrs' -> ===================================== compiler/GHC/Stg/Lift/Analysis.hs ===================================== @@ -117,7 +117,7 @@ type instance XLet 'LiftLams = Skeleton type instance XLetNoEscape 'LiftLams = Skeleton freeVarsOfRhs :: (XRhsClosure pass ~ DIdSet) => GenStgRhs pass -> DIdSet -freeVarsOfRhs (StgRhsCon _ _ _ args) = mkDVarSet [ id | StgVarArg id <- args ] +freeVarsOfRhs (StgRhsCon _ _ _ _ args) = mkDVarSet [ id | StgVarArg id <- args ] freeVarsOfRhs (StgRhsClosure fvs _ _ _ _) = fvs -- | Captures details of the syntax tree relevant to the cost model, such as @@ -326,8 +326,8 @@ tagSkeletonBinding is_lne body_skel body_arg_occs (StgRec pairs) bndr' = BindsClosure bndr (bndr `elemVarSet` scope_occs) tagSkeletonRhs :: Id -> CgStgRhs -> (Skeleton, IdSet, LlStgRhs) -tagSkeletonRhs _ (StgRhsCon ccs dc mn args) - = (NilSk, mkArgOccs args, StgRhsCon ccs dc mn args) +tagSkeletonRhs _ (StgRhsCon ccs dc mn ts args) + = (NilSk, mkArgOccs args, StgRhsCon ccs dc mn ts args) tagSkeletonRhs bndr (StgRhsClosure fvs ccs upd bndrs body) = (rhs_skel, body_arg_occs, StgRhsClosure fvs ccs upd bndrs' body') where ===================================== compiler/GHC/Stg/Lift/Monad.hs ===================================== @@ -194,9 +194,9 @@ removeRhsCCCS :: GenStgRhs pass -> GenStgRhs pass removeRhsCCCS (StgRhsClosure ext ccs upd bndrs body) | isCurrentCCS ccs = StgRhsClosure ext dontCareCCS upd bndrs body -removeRhsCCCS (StgRhsCon ccs con mu args) +removeRhsCCCS (StgRhsCon ccs con mu ts args) | isCurrentCCS ccs - = StgRhsCon dontCareCCS con mu args + = StgRhsCon dontCareCCS con mu ts args removeRhsCCCS rhs = rhs -- | The analysis monad consists of the following 'RWST' components: ===================================== compiler/GHC/Stg/Lint.hs ===================================== @@ -148,7 +148,7 @@ checkNoCurrentCCS rhs = do StgRhsClosure _ ccs _ _ _ | isCurrentCCS ccs -> addErrL (text "Top-level StgRhsClosure with CurrentCCS" $$ rhs') - StgRhsCon ccs _ _ _ + StgRhsCon ccs _ _ _ _ | isCurrentCCS ccs -> addErrL (text "Top-level StgRhsCon with CurrentCCS" $$ rhs') _ -> return () @@ -163,7 +163,7 @@ lintStgRhs (StgRhsClosure _ _ _ binders expr) addInScopeVars binders $ lintStgExpr expr -lintStgRhs rhs@(StgRhsCon _ con _ args) = do +lintStgRhs rhs@(StgRhsCon _ con _ _ args) = do when (isUnboxedTupleDataCon con || isUnboxedSumDataCon con) $ do opts <- getStgPprOpts addErrL (text "StgRhsCon is an unboxed tuple or sum application" $$ ===================================== compiler/GHC/Stg/Stats.hs ===================================== @@ -125,7 +125,7 @@ statBinding top (StgRec pairs) statRhs :: Bool -> (Id, StgRhs) -> StatEnv -statRhs top (_, StgRhsCon _ _ _ _) +statRhs top (_, StgRhsCon _ _ _ _ _) = countOne (ConstructorBinds top) statRhs top (_, StgRhsClosure _ _ u _ body) ===================================== compiler/GHC/Stg/Syntax.hs ===================================== @@ -437,6 +437,7 @@ important): DataCon -- Constructor. Never an unboxed tuple or sum, as those -- are not allocated. (Maybe Int) + [Tickish Id] [StgArg] -- Args -- | Used as a data type index for the stgSyn AST @@ -483,7 +484,7 @@ stgRhsArity :: StgRhs -> Int stgRhsArity (StgRhsClosure _ _ _ bndrs _) = ASSERT( all isId bndrs ) length bndrs -- The arity never includes type parameters, but they should have gone by now -stgRhsArity (StgRhsCon _ _ _ _) = 0 +stgRhsArity (StgRhsCon _ _ _ _ _) = 0 {- ************************************************************************ @@ -818,5 +819,5 @@ pprStgRhs opts rhs = case rhs of ]) 4 (pprStgExpr opts body) - StgRhsCon cc con mid args - -> hcat [ ppr cc, space, ppr mid, ppr con, text "! ", brackets (sep (map pprStgArg args))] + StgRhsCon cc con mid ticks args + -> hcat [ ppr cc, space, ppr mid, ppr ticks, ppr con, text "! ", brackets (sep (map pprStgArg args))] ===================================== compiler/GHC/Stg/Unarise.hs ===================================== @@ -293,9 +293,9 @@ unariseRhs rho (StgRhsClosure ext ccs update_flag args expr) expr' <- unariseExpr rho' expr return (StgRhsClosure ext ccs update_flag args1 expr') -unariseRhs rho (StgRhsCon ccs con mu args) +unariseRhs rho (StgRhsCon ccs con mu ts args) = ASSERT(not (isUnboxedTupleDataCon con || isUnboxedSumDataCon con)) - return (StgRhsCon ccs con mu (unariseConArgs rho args)) + return (StgRhsCon ccs con mu ts (unariseConArgs rho args)) -------------------------------------------------------------------------------- ===================================== compiler/GHC/StgToCmm.hs ===================================== @@ -198,7 +198,7 @@ cgTopBinding dflags (StgTopStringLit id str) = do cgTopRhs :: DynFlags -> RecFlag -> Id -> CgStgRhs -> (CgIdInfo, FCode ()) -- The Id is passed along for setting up a binding... -cgTopRhs dflags _rec bndr (StgRhsCon _cc con mn args) +cgTopRhs dflags _rec bndr (StgRhsCon _cc con mn _ts args) = cgTopRhsCon dflags bndr con mn (assertNonVoidStgArgs args) -- con args are always non-void, -- see Note [Post-unarisation invariants] in GHC.Stg.Unarise ===================================== compiler/GHC/StgToCmm/Bind.hs ===================================== @@ -205,7 +205,7 @@ cgRhs :: Id -- (see above) ) -cgRhs id (StgRhsCon cc con mn args) +cgRhs id (StgRhsCon cc con mn _ts args) = withNewTickyCounterCon (idName id) con $ buildDynCon id mn True cc con (assertNonVoidStgArgs args) -- con args are always non-void, ===================================== compiler/GHC/StgToCmm/Expr.hs ===================================== @@ -158,7 +158,7 @@ cgLetNoEscapeRhsBody -> FCode (CgIdInfo, FCode ()) cgLetNoEscapeRhsBody local_cc bndr (StgRhsClosure _ cc _upd args body) = cgLetNoEscapeClosure bndr local_cc cc (nonVoidIds args) body -cgLetNoEscapeRhsBody local_cc bndr (StgRhsCon cc con mn args) +cgLetNoEscapeRhsBody local_cc bndr (StgRhsCon cc con mn _ts args) = cgLetNoEscapeClosure bndr local_cc cc [] (StgConApp con mn args (pprPanic "cgLetNoEscapeRhsBody" $ text "StgRhsCon doesn't have type args")) ===================================== compiler/ghc.cabal.in ===================================== @@ -511,6 +511,7 @@ Library GHC.Settings.Constants GHC.Settings.IO GHC.Stg.CSE + GHC.Stg.Debug GHC.Stg.DepAnal GHC.Stg.FVs GHC.Stg.Lift View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a6ef34bb20b9adda775954039a7c69a84535751e...8ce72ae05f126285579a6d228c44bd6dedbee71e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a6ef34bb20b9adda775954039a7c69a84535751e...8ce72ae05f126285579a6d228c44bd6dedbee71e 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 Wed Nov 18 10:42:08 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 05:42:08 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Improvements Message-ID: <5fb4fa80c0a59_8311598c1901360c1@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: c7ca7abe by Matthew Pickering at 2020-11-18T10:17:51+00:00 Improvements - - - - - fb41817c by Matthew Pickering at 2020-11-18T10:30:31+00:00 refactoring - - - - - 129de9a0 by Matthew Pickering at 2020-11-18T10:41:19+00:00 new module - - - - - 19 changed files: - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Stg/Debug.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/CostCentre.hs - + compiler/GHC/Types/IPE.hs - compiler/ghc.cabal.in - includes/rts/Flags.h - includes/rts/IPE.h - includes/rts/prof/CCS.h - libraries/base/GHC/Stack/CCS.hsc - rts/ProfHeap.c - rts/Trace.c Changes: ===================================== compiler/GHC/CoreToStg.hs ===================================== @@ -47,6 +47,7 @@ import GHC.Driver.Session import GHC.Platform.Ways import GHC.Driver.Ppr import GHC.Types.ForeignCall +import GHC.Types.IPE import GHC.Types.Demand ( isUsedOnce ) import GHC.Builtin.PrimOps ( PrimCall(..) ) import GHC.Types.SrcLoc ( mkGeneralSrcSpan ) ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -51,6 +51,7 @@ import GHC.Unit.Finder ( mkStubPaths ) import GHC.Types.SrcLoc import GHC.Types.CostCentre +import GHC.Types.IPE import GHC.Types.ForeignStubs import GHC.Types.Unique.Supply ( mkSplitUniqSupply ) ===================================== compiler/GHC/Driver/Hooks.hs ===================================== @@ -46,6 +46,7 @@ import GHC.Types.Id import GHC.Types.SrcLoc import GHC.Types.Basic import GHC.Types.CostCentre +import GHC.Types.IPE import GHC.Types.Meta import GHC.Types.HpcInfo ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -173,6 +173,7 @@ import GHC.Types.ForeignStubs import GHC.Types.Var.Env ( emptyTidyEnv ) import GHC.Types.Fixity.Env import GHC.Types.CostCentre +import GHC.Types.IPE import GHC.Types.Unique.Supply import GHC.Types.SourceFile import GHC.Types.SrcLoc @@ -1468,6 +1469,8 @@ hscGenHardCode hsc_env cgguts location output_filename = do | otherwise = empty ------------------ Code generation ------------------ + -- This IORef records which info tables are used during + -- code generation. lref <- newIORef [] -- The back-end is streamed: each top-level function goes -- from Stg all the way to asm before dealing with the next ===================================== compiler/GHC/Stg/Debug.hs ===================================== @@ -11,7 +11,7 @@ import GHC.Stg.Syntax import GHC.Types.Id import GHC.Core.DataCon -import GHC.Types.CostCentre +import GHC.Types.IPE import GHC.Unit.Module import GHC.Types.Name ( getName, getOccName, occNameString, nameSrcSpan) import GHC.Data.FastString ===================================== compiler/GHC/StgToCmm.hs ===================================== @@ -39,6 +39,7 @@ import GHC.Cmm.Graph import GHC.Stg.Syntax import GHC.Types.CostCentre +import GHC.Types.IPE import GHC.Types.HpcInfo import GHC.Types.Id import GHC.Types.Id.Info ===================================== compiler/GHC/StgToCmm/DataCon.hs ===================================== @@ -189,7 +189,7 @@ buildDynCon' _ binder mn actually_bound ccs con args ; profile <- getProfile ; let platform = profilePlatform profile (tot_wds, ptr_wds, args_w_offsets) - = mkVirtConstrOffsets profile (addArgReps args) + = mkVirtConstrOffsets profile (addArgReps args) nonptr_wds = tot_wds - ptr_wds info_tbl = mkDataConInfoTable profile con ((modu,) <$> mn) False ptr_wds nonptr_wds @@ -310,8 +310,6 @@ precomputedStaticConInfo_maybe dflags binder con [] | isNullaryRepDataCon con = Just $ litIdInfo (targetPlatform dflags) binder (mkConLFInfo con) (CmmLabel (mkClosureLabel (dataConName con) NoCafRefs)) - -- = Just $ litIdInfo dflags binder (mkConLFInfo con) - -- (CmmLabel (mkClosureLabel (idName binder) NoCafRefs)) precomputedStaticConInfo_maybe dflags binder con [arg] -- Int/Char values with existing closures in the RTS | intClosure || charClosure ===================================== compiler/GHC/StgToCmm/Expr.hs ===================================== @@ -82,7 +82,7 @@ cgExpr (StgOpApp (StgPrimOp DataToTagOp) [StgVarArg a] _res_ty) = do cgExpr (StgOpApp op args ty) = cgOpApp op args ty cgExpr (StgConApp con mn args _)= cgConApp con mn args -cgExpr (StgTick t e) = cgTick t (cgExpr e) +cgExpr (StgTick t e) = cgTick t >> cgExpr e cgExpr (StgLit lit) = do cmm_lit <- cgLit lit emitReturn [CmmLit cmm_lit] @@ -1084,12 +1084,12 @@ emitEnter fun = do -- | Generate Cmm code for a tick. Depending on the type of Tickish, -- this will either generate actual Cmm instrumentation code, or -- simply pass on the annotation as a @CmmTickish at . -cgTick :: Tickish Id -> FCode a -> FCode a -cgTick tick k +cgTick :: Tickish Id -> FCode () +cgTick tick = do { platform <- getPlatform ; case tick of - ProfNote cc t p -> emitSetCCC cc t p >> k - HpcTick m n -> emit (mkTickBox platform m n) >> k - SourceNote s n -> emitTick (SourceNote s n) >> k - _other -> k + ProfNote cc t p -> emitSetCCC cc t p + HpcTick m n -> emit (mkTickBox platform m n) + SourceNote s n -> emitTick (SourceNote s n) + _other -> return () } ===================================== compiler/GHC/StgToCmm/Prof.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Cmm.Utils import GHC.Cmm.CLabel import GHC.Types.CostCentre +import GHC.Types.IPE import GHC.Data.FastString import GHC.Unit.Module as Module import GHC.Utils.Outputable @@ -344,7 +345,6 @@ bumpSccCount platform ccs = addToMem (rEP_CostCentreStack_scc_count platform) (cmmOffsetB platform ccs (pc_OFFSET_CostCentreStack_scc_count (platformConstants platform))) 1 - ----------------------------------------------------------------------------- -- -- Lag/drag/void stuff ===================================== compiler/GHC/StgToCmm/Utils.hs ===================================== @@ -81,6 +81,7 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Types.RepType import GHC.Types.CostCentre +import GHC.Types.IPE import Data.ByteString (ByteString) import qualified Data.ByteString.Char8 as BS8 ===================================== compiler/GHC/Types/CostCentre.hs ===================================== @@ -2,7 +2,6 @@ module GHC.Types.CostCentre ( CostCentre(..), CcName, CCFlavour(..), -- All abstract except to friend: ParseIface.y - DCMap, ClosureMap, InfoTableProvMap(..), emptyInfoTableProvMap, CostCentreStack, CollectedCCs, emptyCollectedCCs, collectCC, currentCCS, dontCareCCS, @@ -31,8 +30,6 @@ import GHC.Utils.Outputable import GHC.Types.SrcLoc import GHC.Data.FastString import GHC.Types.CostCentre.State -import GHC.Core.DataCon -import GHC.Types.Unique.Map import Data.Data @@ -190,16 +187,6 @@ data CostCentreStack deriving (Eq, Ord) -- needed for Ord on CLabel -type DCMap = UniqMap DataCon [(Int, Maybe (RealSrcSpan, String))] - -type ClosureMap = UniqMap Name (String, RealSrcSpan, String) - -data InfoTableProvMap = InfoTableProvMap - { provDC :: DCMap - , provClosure :: ClosureMap } - -emptyInfoTableProvMap :: InfoTableProvMap -emptyInfoTableProvMap = InfoTableProvMap emptyUniqMap emptyUniqMap -- synonym for triple which describes the cost centre info in the generated -- code for a module. ===================================== compiler/GHC/Types/IPE.hs ===================================== @@ -0,0 +1,21 @@ +module GHC.Types.IPE(DCMap, ClosureMap, InfoTableProvMap(..) + , emptyInfoTableProvMap) where + +import GHC.Prelude + +import GHC.Types.Name +import GHC.Types.SrcLoc + +import GHC.Core.DataCon +import GHC.Types.Unique.Map + +type DCMap = UniqMap DataCon [(Int, Maybe (RealSrcSpan, String))] + +type ClosureMap = UniqMap Name (String, RealSrcSpan, String) + +data InfoTableProvMap = InfoTableProvMap + { provDC :: DCMap + , provClosure :: ClosureMap } + +emptyInfoTableProvMap :: InfoTableProvMap +emptyInfoTableProvMap = InfoTableProvMap emptyUniqMap emptyUniqMap \ No newline at end of file ===================================== compiler/ghc.cabal.in ===================================== @@ -624,6 +624,7 @@ Library GHC.Types.ForeignStubs GHC.Types.HpcInfo GHC.Types.Id + GHC.Types.IPE GHC.Types.Id.Info GHC.Types.Id.Make GHC.Types.Literal ===================================== includes/rts/Flags.h ===================================== @@ -132,16 +132,16 @@ typedef struct _COST_CENTRE_FLAGS { /* See Note [Synchronization of flags and base APIs] */ typedef struct _PROFILING_FLAGS { uint32_t doHeapProfile; -# define NO_HEAP_PROFILING 0 /* N.B. Used as indexes into arrays */ -# define HEAP_BY_CCS 1 -# define HEAP_BY_MOD 2 -# define HEAP_BY_DESCR 4 -# define HEAP_BY_TYPE 5 +# define NO_HEAP_PROFILING 0 /* N.B. Used as indexes into arrays */ +# define HEAP_BY_CCS 1 +# define HEAP_BY_MOD 2 +# define HEAP_BY_DESCR 4 +# define HEAP_BY_TYPE 5 # define HEAP_BY_RETAINER 6 # define HEAP_BY_LDV 7 # define HEAP_BY_CLOSURE_TYPE 8 -# define HEAP_BY_INFO_TABLE 9 +# define HEAP_BY_INFO_TABLE 9 Time heapProfileInterval; /* time between samples */ uint32_t heapProfileIntervalTicks; /* ticks between samples (derived) */ ===================================== includes/rts/IPE.h ===================================== @@ -13,5 +13,23 @@ #pragma once + +typedef struct InfoProv_{ + char * table_name; + char * closure_desc; + char * ty_desc; + char * label; + char * module; + char * srcloc; +} InfoProv; + +typedef struct InfoProvEnt_ { + StgInfoTable * info; + InfoProv prov; + struct InfoProvEnt_ *link; +} InfoProvEnt; + +extern InfoProvEnt * RTS_VAR(IPE_LIST); // registered IP list + void registerInfoProvList(InfoProvEnt **cc_list); -InfoProvEnt * lookupIPE(StgInfoTable *info); \ No newline at end of file +InfoProvEnt * lookupIPE(StgInfoTable *info); ===================================== includes/rts/prof/CCS.h ===================================== @@ -73,20 +73,6 @@ typedef struct CostCentreStack_ { } CostCentreStack; -typedef struct InfoProv_{ - char * table_name; - char * closure_desc; - char * ty_desc; - char * label; - char * module; - char * srcloc; -} InfoProv; - -typedef struct InfoProvEnt_ { - StgInfoTable * info; - InfoProv prov; - struct InfoProvEnt_ *link; -} InfoProvEnt; /* ----------------------------------------------------------------------------- @@ -193,7 +179,6 @@ void enterFunCCS (StgRegTable *reg, CostCentreStack *); CostCentre *mkCostCentre (char *label, char *module, char *srcloc); extern CostCentre * RTS_VAR(CC_LIST); // registered CC list -extern InfoProvEnt * RTS_VAR(IPE_LIST); // registered IP list /* ----------------------------------------------------------------------------- * Declaring Cost Centres & Cost Centre Stacks. ===================================== libraries/base/GHC/Stack/CCS.hsc ===================================== @@ -149,8 +149,7 @@ getIPE obj = IO $ \s -> (## s', addr ##) -> (## s', Ptr addr ##) ipeProv :: Ptr InfoProvEnt -> Ptr InfoProv -ipeProv p = p `plusPtr` 8 --(#offsetof InfoProvEnt, prov) -- TODO, offset is to the "prov" field but not sure how to express this - -- (# sizeOf * StgInfoTable) +ipeProv p = (#ptr InfoProvEnt, prov) p ipName, ipDesc, ipLabel, ipModule, ipSrcLoc, ipTyDesc :: Ptr InfoProv -> IO CString ipName p = (# peek InfoProv, table_name) p ===================================== rts/ProfHeap.c ===================================== @@ -961,8 +961,6 @@ dumpCensus( Census *census ) break; case HEAP_BY_INFO_TABLE: fprintf(hp_file, "%p", ctr->identity); - // TODO now all the types in this mode are just THUNK closures so - // don't really need to add any more info char str[100]; sprintf(str, "%p", ctr->identity); traceHeapProfSampleString(0, str, count * sizeof(W_)); ===================================== rts/Trace.c ===================================== @@ -663,7 +663,6 @@ void traceHeapProfCostCentre(StgWord32 ccID, } } - // This one is for .hp samples void traceHeapProfSampleCostCentre(StgWord8 profile_id, CostCentreStack *stack, StgWord residency) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8ce72ae05f126285579a6d228c44bd6dedbee71e...129de9a0aa783114fbeabf557d3591d75f0aec0c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8ce72ae05f126285579a6d228c44bd6dedbee71e...129de9a0aa783114fbeabf557d3591d75f0aec0c 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 Wed Nov 18 11:04:11 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 06:04:11 -0500 Subject: [Git][ghc/ghc][wip/con-info] 5 commits: Description of primop Message-ID: <5fb4ffab8c81e_8313fd6c367a17c13829a@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: b4252889 by Matthew Pickering at 2020-11-18T10:43:48+00:00 Description of primop - - - - - f40529dd by Matthew Pickering at 2020-11-18T10:53:07+00:00 clean - - - - - 652a274b by Matthew Pickering at 2020-11-18T10:59:06+00:00 Return - - - - - 15e73efa by Matthew Pickering at 2020-11-18T11:00:46+00:00 clean - - - - - d9332454 by Matthew Pickering at 2020-11-18T11:03:58+00:00 clean - - - - - 6 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -3009,7 +3009,9 @@ section "Info Table Origin" ------------------------------------------------------------------------ primop WhereFromOp "whereFrom#" GenPrimOp a -> State# s -> (# State# s, Addr# #) - { TODO } + { Returns the {\tt InfoProvEnt } for the info table of the given object + (value is {\tt NULL} if the table does not exist or there is no information + about the closure).} with out_of_line = True ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -80,16 +80,10 @@ module GHC.Cmm.CLabel ( mkRtsApFastLabel, mkPrimCallLabel, mkForeignLabel, - addLabelSize, - - foreignLabelStdcallInfo, - isBytesLabel, - isForeignLabel, - isSomeRODataLabel, - isStaticClosureLabel, - mkCCLabel, mkCCSLabel, - - mkIPELabel, InfoTableEnt(..), + mkCCLabel, + mkCCSLabel, + mkIPELabel, + InfoProvEnt(..), mkDynamicLinkerLabel, mkPicBaseLabel, @@ -112,6 +106,10 @@ module GHC.Cmm.CLabel ( isIdLabel, isTickyLabel, hasHaskellName, + isBytesLabel, + isForeignLabel, + isSomeRODataLabel, + isStaticClosureLabel, -- * Conversions toClosureLbl, @@ -125,7 +123,9 @@ module GHC.Cmm.CLabel ( pprCLabel, -- * Others - dynamicLinkerLabelInfo + dynamicLinkerLabelInfo, + addLabelSize, + foreignLabelStdcallInfo ) where #include "HsVersions.h" @@ -253,7 +253,7 @@ data CLabel | CC_Label CostCentre | CCS_Label CostCentreStack - | IPE_Label InfoTableEnt + | IPE_Label InfoProvEnt -- | These labels are generated and used inside the NCG only. @@ -735,19 +735,16 @@ mkBitmapLabel :: Unique -> CLabel mkBitmapLabel uniq = LargeBitmapLabel uniq -data InfoTableEnt = InfoTableEnt { infoTablePtr :: !CLabel - , infoTableEntClosureType :: !Int - , infoTableType :: !String - , infoTableProv :: !(Module, RealSrcSpan, String) } - deriving (Eq, Ord) - ---instance Outputable InfoTableEnt where --- ppr (InfoTableEnt l ct p) = pdoc (undefined :: Platform) l <> colon <> ppr ct <> colon <> ppr p +data InfoProvEnt = InfoProvEnt { infoTablePtr :: !CLabel + , infoProvEntClosureType :: !Int + , infoTableType :: !String + , infoTableProv :: !(Module, RealSrcSpan, String) } + deriving (Eq, Ord) -- Constructing Cost Center Labels mkCCLabel :: CostCentre -> CLabel mkCCSLabel :: CostCentreStack -> CLabel -mkIPELabel :: InfoTableEnt -> CLabel +mkIPELabel :: InfoProvEnt -> CLabel mkCCLabel cc = CC_Label cc mkCCSLabel ccs = CCS_Label ccs mkIPELabel ipe = IPE_Label ipe @@ -1393,7 +1390,7 @@ pprCLabel platform sty lbl = CC_Label cc -> maybe_underscore $ ppr cc CCS_Label ccs -> maybe_underscore $ ppr ccs - (IPE_Label (InfoTableEnt l _ _ (m, _, _))) -> pprCode CStyle (pdoc platform l) <> text "_" <> ppr m <> text "_ipe" + (IPE_Label (InfoProvEnt l _ _ (m, _, _))) -> pprCode CStyle (pdoc platform l) <> text "_" <> ppr m <> text "_ipe" CmmLabel _ _ fs CmmCode -> maybe_underscore $ ftext fs ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -1,4 +1,3 @@ -{-# LANGUAGE TypeApplications #-} {- (c) The GRASP/AQUA Project, Glasgow University, 1993-1998 ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -163,6 +163,19 @@ import GHC.Cmm.Info.Build import GHC.Cmm.Pipeline import GHC.Cmm.Info +import GHC.Unit +import GHC.Unit.External +import GHC.Unit.State +import GHC.Unit.Module.ModDetails +import GHC.Unit.Module.ModGuts +import GHC.Unit.Module.ModIface +import GHC.Unit.Module.ModSummary +import GHC.Unit.Module.Graph +import GHC.Unit.Module.Imported +import GHC.Unit.Module.Deps +import GHC.Unit.Module.Status +import GHC.Unit.Home.ModInfo + import GHC.Utils.Error import Data.IORef @@ -210,19 +223,6 @@ import Data.Set (Set) import Data.Functor import Control.DeepSeq (force) import Data.Bifunctor (first, bimap) -import GHC.Unit.Module.ModGuts -import GHC.Unit.Module.ModSummary -import GHC.Unit.Module -import GHC.Unit.Module.ModIface -import GHC.Unit.Module.ModDetails -import GHC.Unit.Module.Status -import GHC.Unit.Module.Imported -import GHC.Unit.Module.Graph -import GHC.Unit.Home.ModInfo -import GHC.Unit.Home -import GHC.Unit.State -import GHC.Unit.Module.Deps -import GHC.Unit.External #include "HsVersions.h" ===================================== compiler/GHC/StgToCmm/Prof.hs ===================================== @@ -286,7 +286,7 @@ initInfoTableProv (InfoTableProvMap dcmap clmap) this_mod mapM_ emitInfoTableProv ents --- Info Table Prov stuff -emitInfoTableProv :: InfoTableEnt -> FCode () +emitInfoTableProv :: InfoProvEnt -> FCode () emitInfoTableProv ip = do { dflags <- getDynFlags ; let (mod, src, label) = infoTableProv ip @@ -305,7 +305,7 @@ emitInfoTableProv ip = do showPpr dflags (pprCLabel platform CStyle (infoTablePtr ip)) ; closure_type <- newByteStringCLit $ bytesFS $ mkFastString $ - showPpr dflags (text $ show $ infoTableEntClosureType ip) + showPpr dflags (text $ show $ infoProvEntClosureType ip) ; let lits = [ CmmLabel (infoTablePtr ip), -- Info table pointer table_name, -- char *table_name ===================================== compiler/GHC/StgToCmm/Utils.hs ===================================== @@ -633,20 +633,20 @@ emitUpdRemSetPushThunk ptr = False -convertClosureMap :: [CmmInfoTable] -> Module -> ClosureMap -> [InfoTableEnt] +convertClosureMap :: [CmmInfoTable] -> Module -> ClosureMap -> [InfoProvEnt] convertClosureMap defns this_mod denv = mapMaybe (\cmit -> do let cl = cit_lbl cmit cn = rtsClosureType (cit_rep cmit) n <- hasHaskellName cl (ty, ss, l) <- lookupUniqMap denv n - return (InfoTableEnt cl cn ty (this_mod, ss, l))) defns + return (InfoProvEnt cl cn ty (this_mod, ss, l))) defns -convertDCMap :: Module -> DCMap -> [InfoTableEnt] +convertDCMap :: Module -> DCMap -> [InfoProvEnt] convertDCMap this_mod (UniqMap denv) = concatMap (\(dc, ns) -> mapMaybe (\(k, mss) -> case mss of Nothing -> Nothing Just (ss, l) -> Just $ - InfoTableEnt (mkConInfoTableLabel (dataConName dc) (Just (this_mod, k))) + InfoProvEnt (mkConInfoTableLabel (dataConName dc) (Just (this_mod, k))) 0 "" (this_mod, ss, l)) ns) (nonDetEltsUFM denv) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/129de9a0aa783114fbeabf557d3591d75f0aec0c...d9332454f4c3a7615c6a94f70bcf67f05fd9d7b6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/129de9a0aa783114fbeabf557d3591d75f0aec0c...d9332454f4c3a7615c6a94f70bcf67f05fd9d7b6 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 Wed Nov 18 11:08:58 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 06:08:58 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 33 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fb500ca6530d_8313fd6c367a17c13919a@gitlab.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 29e792c0 by Sebastian Graf at 2020-11-18T10:27:47+01:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - b19f9da6 by Sebastian Graf at 2020-11-18T11:14:33+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands ============ Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1((1(U),S(U)))`. This would allow Nested CPR to unbox the division, for example. Nested strict product demands ============================= Fixing #18903 gives us enough expressiveness to tackle #18885, where we have ```hs f :: Int -> Int f y = let x | expensive y == 1 = (expensive (y+1), expensive (y+2)) | otherwise = (expensive (y+3), expensive (y+4)) in case () of _ | expensive (y+5) == 42 -> fst x _ | expensive (y+6) == 41 -> fst x + snd x _ | otherwise -> 0 ``` Here, we used to give `x` demand `1P(1P(U),1P(U))`. The outer `1` is because `x` is used lazily and the inner `1`s are redundant with that fact. That leaves some expressiveness on the table. After this change, we infer `1P(SP(U),1P(U))`, meaning that *whenever we evaluate `x`*, we evaluate its first component strictly, effectively making strictness product demands apply *relatively*. Usage product demands still apply absolutely, though. More details on how we could exploit the new language in `Note [Absent sub-demands]`. Fixes #18903 and fixes #18885. - - - - - 921b1e5f by Sebastian Graf at 2020-11-18T11:14:35+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 8249c98d by Sebastian Graf at 2020-11-18T11:14:35+01:00 fix regression - - - - - fa70a702 by Sebastian Graf at 2020-11-18T11:14:35+01:00 fix - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aabd8a4cb01328e8b885c9a3608a229a69c295ff...fa70a702d12f3833c5600fd00c34b67e2e2b3fba -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aabd8a4cb01328e8b885c9a3608a229a69c295ff...fa70a702d12f3833c5600fd00c34b67e2e2b3fba 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 Wed Nov 18 12:10:03 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 07:10:03 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 4 commits: Demand: Interleave usage and strictness demands (#18903) Message-ID: <5fb50f1ba9837_8313fd6c07f5270147247@gitlab.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 9ba7385c by Sebastian Graf at 2020-11-18T13:09:52+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands ============ Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1((1(U),S(U)))`. This would allow Nested CPR to unbox the division, for example. Nested strict product demands ============================= Fixing #18903 gives us enough expressiveness to tackle #18885, where we have ```hs f :: Int -> Int f y = let x | expensive y == 1 = (expensive (y+1), expensive (y+2)) | otherwise = (expensive (y+3), expensive (y+4)) in case () of _ | expensive (y+5) == 42 -> fst x _ | expensive (y+6) == 41 -> fst x + snd x _ | otherwise -> 0 ``` Here, we used to give `x` demand `1P(1P(U),1P(U))`. The outer `1` is because `x` is used lazily and the inner `1`s are redundant with that fact. That leaves some expressiveness on the table. After this change, we infer `1P(SP(U),1P(U))`, meaning that *whenever we evaluate `x`*, we evaluate its first component strictly, effectively making strictness product demands apply *relatively*. Usage product demands still apply absolutely, though. More details on how we could exploit the new language in `Note [Absent sub-demands]`. Fixes #18903 and fixes #18885. - - - - - ba6aac47 by Sebastian Graf at 2020-11-18T13:09:52+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 12a5fd8c by Sebastian Graf at 2020-11-18T13:09:52+01:00 fix regression - - - - - a08a715e by Sebastian Graf at 2020-11-18T13:09:52+01:00 fix - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa70a702d12f3833c5600fd00c34b67e2e2b3fba...a08a715e80c691c09bf2ab86de8d07cb86bbbe5a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa70a702d12f3833c5600fd00c34b67e2e2b3fba...a08a715e80c691c09bf2ab86de8d07cb86bbbe5a 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 Wed Nov 18 12:38:52 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 07:38:52 -0500 Subject: [Git][ghc/ghc][wip/T18932] PmCheck: Print types of uncovered patterns (#18932) Message-ID: <5fb515dcea578_8313fd6ee63b12c150116@gitlab.mail> Sebastian Graf pushed to branch wip/T18932 at Glasgow Haskell Compiler / GHC Commits: e18ed3cf by Sebastian Graf at 2020-11-18T13:38:46+01:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 30 changed files: - compiler/GHC/HsToCore/Pmc.hs - testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr - testsuite/tests/deSugar/should_compile/GadtOverlap.stderr - testsuite/tests/deSugar/should_compile/T14135.stderr - testsuite/tests/deSugar/should_compile/T14546a.stderr - testsuite/tests/deSugar/should_compile/T14546d.stderr - testsuite/tests/deSugar/should_compile/T5455.stderr - testsuite/tests/dependent/should_compile/KindEqualities.stderr - testsuite/tests/driver/T8101.stderr - testsuite/tests/driver/T8101b.stderr - testsuite/tests/driver/werror.stderr - testsuite/tests/ghci/prog018/prog018.stdout - testsuite/tests/parser/should_compile/T15139.stderr - testsuite/tests/pmcheck/complete_sigs/T13964.stderr - testsuite/tests/pmcheck/complete_sigs/T14059a.stderr - testsuite/tests/pmcheck/complete_sigs/T17386.stderr - testsuite/tests/pmcheck/complete_sigs/completesig02.stderr - testsuite/tests/pmcheck/complete_sigs/completesig04.stderr - testsuite/tests/pmcheck/complete_sigs/completesig06.stderr - testsuite/tests/pmcheck/complete_sigs/completesig07.stderr - testsuite/tests/pmcheck/complete_sigs/completesig10.stderr - testsuite/tests/pmcheck/complete_sigs/completesig11.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase008.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e18ed3cf184add91b1f12b43d25bc22b9dd043b5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e18ed3cf184add91b1f12b43d25bc22b9dd043b5 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 Wed Nov 18 12:53:52 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 07:53:52 -0500 Subject: [Git][ghc/ghc][wip/T18932] PmCheck: Print types of uncovered patterns (#18932) Message-ID: <5fb5196098390_8313fd6cb9e5e6c154749@gitlab.mail> Sebastian Graf pushed to branch wip/T18932 at Glasgow Haskell Compiler / GHC Commits: 9667ab7d by Sebastian Graf at 2020-11-18T13:53:43+01:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 30 changed files: - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr - testsuite/tests/deSugar/should_compile/GadtOverlap.stderr - testsuite/tests/deSugar/should_compile/T14135.stderr - testsuite/tests/deSugar/should_compile/T14546a.stderr - testsuite/tests/deSugar/should_compile/T14546d.stderr - testsuite/tests/deSugar/should_compile/T5455.stderr - testsuite/tests/dependent/should_compile/KindEqualities.stderr - testsuite/tests/driver/T8101.stderr - testsuite/tests/driver/T8101b.stderr - testsuite/tests/driver/werror.stderr - testsuite/tests/ghci/prog018/prog018.stdout - testsuite/tests/parser/should_compile/T15139.stderr - testsuite/tests/pmcheck/complete_sigs/T13964.stderr - testsuite/tests/pmcheck/complete_sigs/T14059a.stderr - testsuite/tests/pmcheck/complete_sigs/T17386.stderr - testsuite/tests/pmcheck/complete_sigs/completesig02.stderr - testsuite/tests/pmcheck/complete_sigs/completesig04.stderr - testsuite/tests/pmcheck/complete_sigs/completesig06.stderr - testsuite/tests/pmcheck/complete_sigs/completesig07.stderr - testsuite/tests/pmcheck/complete_sigs/completesig10.stderr - testsuite/tests/pmcheck/complete_sigs/completesig11.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9667ab7d2fe7f115902003638a2a9e9a61576fb8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9667ab7d2fe7f115902003638a2a9e9a61576fb8 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 Wed Nov 18 14:29:08 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Wed, 18 Nov 2020 09:29:08 -0500 Subject: [Git][ghc/ghc][wip/amg/renamer-refactor] More plausible substNameAvailInfo Message-ID: <5fb52fb4c3e1e_83115d0dda0164687@gitlab.mail> Adam Gundry pushed to branch wip/amg/renamer-refactor at Glasgow Haskell Compiler / GHC Commits: 4b16fb18 by Adam Gundry at 2020-11-18T14:20:41+00:00 More plausible substNameAvailInfo - - - - - 1 changed file: - compiler/GHC/Types/Name/Shape.hs Changes: ===================================== compiler/GHC/Types/Name/Shape.hs ===================================== @@ -184,10 +184,8 @@ substName env n | Just n' <- lookupNameEnv env n = n' -- to induce a substitution on 'availNames'. substNameAvailInfo :: HscEnv -> ShNameSubst -> AvailInfo -> IO AvailInfo substNameAvailInfo _ env (Avail n) = return (Avail (substName env n)) -substNameAvailInfo hsc_env env (AvailFL fl) = - AvailFL <$> setNameFieldSelector hsc_env mb_mod fl -- AMG TODO mb_mod? - where - mb_mod = Nothing +substNameAvailInfo _ env (AvailFL fl) = + return (AvailFL fl { flSelector = substName env (flSelector fl) }) substNameAvailInfo hsc_env env (AvailTC n ns fs) = let mb_mod = fmap nameModule (lookupNameEnv env n) in AvailTC (substName env n) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4b16fb18146454c280dc8319c34aedca91aae2e0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4b16fb18146454c280dc8319c34aedca91aae2e0 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 Wed Nov 18 14:46:42 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 09:46:42 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] Testsuite updates Message-ID: <5fb533d2c0a29_83157faa3016537c@gitlab.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: ff04b6e3 by Sebastian Graf at 2020-11-18T15:46:37+01:00 Testsuite updates - - - - - 3 changed files: - testsuite/tests/simplCore/should_compile/T7360.stderr - testsuite/tests/stranal/sigs/UnsatFun.hs - testsuite/tests/stranal/sigs/UnsatFun.stderr Changes: ===================================== testsuite/tests/simplCore/should_compile/T7360.stderr ===================================== @@ -21,7 +21,7 @@ T7360.$WFoo3 -- RHS size: {terms: 5, types: 2, coercions: 0, joins: 0/0} fun1 [InlPrag=NOINLINE] :: Foo -> () -[GblId, Arity=1, Str=, Unf=OtherCon []] +[GblId, Arity=1, Str=, Unf=OtherCon []] fun1 = \ (x :: Foo) -> case x of { __DEFAULT -> GHC.Tuple.() } -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} ===================================== testsuite/tests/stranal/sigs/UnsatFun.hs ===================================== @@ -35,6 +35,7 @@ h3 f = f 2 `seq` 3 -- And here we check that the depth of the strictness --- of h is applied correctly. +-- of h is applied correctly. The lambda is unsaturated +-- and thus x is absent. g3 :: Int -> Int g3 x = h3 (\_ _ -> error (show x)) ===================================== testsuite/tests/stranal/sigs/UnsatFun.stderr ===================================== @@ -4,10 +4,10 @@ UnsatFun.$trModule: UnsatFun.f: b UnsatFun.g: b UnsatFun.g': <1P(U)> -UnsatFun.g3: +UnsatFun.g3: UnsatFun.h: UnsatFun.h2: <1CS(U)> -UnsatFun.h3: +UnsatFun.h3: @@ -28,9 +28,9 @@ UnsatFun.$trModule: UnsatFun.f: b UnsatFun.g: b UnsatFun.g': <1P(U)> -UnsatFun.g3: +UnsatFun.g3: UnsatFun.h: UnsatFun.h2: <1CS(U)> -UnsatFun.h3: +UnsatFun.h3: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ff04b6e387cde4f6f6bfc2959443d4e9f3f96990 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ff04b6e387cde4f6f6bfc2959443d4e9f3f96990 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 Wed Nov 18 15:39:52 2020 From: gitlab at gitlab.haskell.org (David Eichmann) Date: Wed, 18 Nov 2020 10:39:52 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_partial_tso_stack_decode] ghc-heap: partial TSO/STACK decoding Message-ID: <5fb5404881c84_83189f68681746d4@gitlab.mail> David Eichmann pushed to branch wip/ghc-debug_partial_tso_stack_decode at Glasgow Haskell Compiler / GHC Commits: 328f27d8 by David Eichmann at 2020-11-18T15:39:38+00:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22 changed files: - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Runtime/Interpreter.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Heap.c - rts/PrimOps.cmm Changes: ===================================== compiler/GHC/ByteCode/Types.hs ===================================== @@ -37,7 +37,7 @@ import Data.ByteString (ByteString) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.Maybe (catMaybes) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS -- ----------------------------------------------------------------------------- @@ -72,7 +72,7 @@ type ItblEnv = NameEnv (Name, ItblPtr) -- We need the Name in the range so we know which -- elements to filter out when unloading a module -newtype ItblPtr = ItblPtr (RemotePtr StgInfoTable) +newtype ItblPtr = ItblPtr (RemotePtr Heap.StgInfoTable) deriving (Show, NFData) data UnlinkedBCO ===================================== compiler/GHC/Runtime/Interpreter.hs ===================================== @@ -103,7 +103,7 @@ import qualified Data.ByteString.Lazy as LB import Data.Array ((!)) import Data.IORef import Foreign hiding (void) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS (CostCentre,CostCentreStack) import System.Exit import GHC.IO.Handle.Types (Handle) @@ -395,7 +395,7 @@ getBreakpointVar hsc_env ref ix = mb <- iservCmd hsc_env (GetBreakpointVar apStack ix) mapM (mkFinalizedHValue hsc_env) mb -getClosure :: HscEnv -> ForeignHValue -> IO (GenClosure ForeignHValue) +getClosure :: HscEnv -> ForeignHValue -> IO (Heap.GenClosure ForeignHValue) getClosure hsc_env ref = withForeignRef ref $ \hval -> do mb <- iservCmd hsc_env (GetClosure hval) ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -27,6 +27,9 @@ module GHC.Exts.Heap ( , GenClosure(..) , ClosureType(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , HasHeapRep(getClosureData) , getClosureDataFromHeapRep @@ -39,6 +42,12 @@ module GHC.Exts.Heap ( , peekItbl , pokeItbl + -- * Cost Centre (profiling) types + , StgTSOProfInfo(..) + , IndexTable(..) + , CostCentre(..) + , CostCentreStack(..) + -- * Closure inspection , getBoxedClosureData , allClosures @@ -53,12 +62,14 @@ import Prelude import GHC.Exts.Heap.Closures import GHC.Exts.Heap.ClosureTypes import GHC.Exts.Heap.Constants +import GHC.Exts.Heap.ProfInfo.Types #if defined(PROFILING) import GHC.Exts.Heap.InfoTableProf #else import GHC.Exts.Heap.InfoTable #endif import GHC.Exts.Heap.Utils +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures import Control.Monad import Data.Bits @@ -323,6 +334,45 @@ getClosureDataFromHeapRep heapRep infoTablePtr pts = do , finalizer = pts !! 3 , link = pts !! 4 } + TSO | [ u_lnk, u_gbl_lnk, tso_stack, u_trec, u_blk_ex, u_bq] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekTSOFields ptr + pure $ TSOClosure + { info = itbl + , link = u_lnk + , global_link = u_gbl_lnk + , tsoStack = tso_stack + , trec = u_trec + , blocked_exceptions = u_blk_ex + , bq = u_bq + , what_next = FFIClosures.tso_what_next fields + , why_blocked = FFIClosures.tso_why_blocked fields + , flags = FFIClosures.tso_flags fields + , threadId = FFIClosures.tso_threadId fields + , saved_errno = FFIClosures.tso_saved_errno fields + , tso_dirty = FFIClosures.tso_dirty fields + , alloc_limit = FFIClosures.tso_alloc_limit fields + , tot_stack_size = FFIClosures.tso_tot_stack_size fields + , prof = FFIClosures.tso_prof fields + }) + | otherwise + -> fail $ "Expected 6 ptr arguments to TSO, found " + ++ show (length pts) + STACK + | [] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekStackFields ptr + pure $ StackClosure + { info = itbl + , stack_size = FFIClosures.stack_size fields + , stack_dirty = FFIClosures.stack_dirty fields +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking = FFIClosures.stack_marking fields +#endif + }) + | otherwise + -> fail $ "Expected 0 ptr argument to STACK, found " + ++ show (length pts) _ -> pure $ UnsupportedClosure itbl ===================================== libraries/ghc-heap/GHC/Exts/Heap/Closures.hs ===================================== @@ -12,6 +12,9 @@ module GHC.Exts.Heap.Closures ( Closure , GenClosure(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , allClosures #if __GLASGOW_HASKELL__ >= 809 -- The closureSize# primop is unsupported on earlier GHC releases but we @@ -40,6 +43,8 @@ import GHC.Exts.Heap.InfoTable import GHC.Exts.Heap.InfoTableProf () #endif +import GHC.Exts.Heap.ProfInfo.Types + import Data.Bits import Data.Int import Data.Word @@ -100,11 +105,11 @@ type Closure = GenClosure Box -- | This is the representation of a Haskell value on the heap. It reflects -- -- --- The data type is parametrized by the type to store references in. Usually --- this is a 'Box' with the type synonym 'Closure'. +-- The data type is parametrized by `b`: the type to store references in. +-- Usually this is a 'Box' with the type synonym 'Closure'. -- --- All Heap objects have the same basic layout. A header containing a pointer --- to the info table and a payload with various fields. The @info@ field below +-- All Heap objects have the same basic layout. A header containing a pointer to +-- the info table and a payload with various fields. The @info@ field below -- always refers to the info table pointed to by the header. The remaining -- fields are the payload. -- @@ -268,6 +273,39 @@ data GenClosure b , link :: !b -- ^ next weak pointer for the capability, can be NULL. } + -- | Representation of StgTSO: A Thread State Object. The values for + -- 'what_next', 'why_blocked' and 'flags' are defined in @Constants.h at . + | TSOClosure + { info :: !StgInfoTable + -- pointers + , link :: !b + , global_link :: !b + , tsoStack :: !b -- ^ stackobj from StgTSO + , trec :: !b + , blocked_exceptions :: !b + , bq :: !b + -- values + , what_next :: !WhatNext + , why_blocked :: !WhyBlocked + , flags :: ![TsoFlags] + , threadId :: !Word64 + , saved_errno :: !Word32 + , tso_dirty :: !Word32 -- ^ non-zero => dirty + , alloc_limit :: !Int64 + , tot_stack_size :: !Word32 + , prof :: !(Maybe StgTSOProfInfo) + } + + -- | Representation of StgStack: The 'tsoStack ' of a 'TSOClosure'. + | StackClosure + { info :: !StgInfoTable + , stack_size :: !Word32 -- ^ stack size in *words* + , stack_dirty :: !Word8 -- ^ non-zero => dirty +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking :: !Word8 +#endif + } + ------------------------------------------------------------ -- Unboxed unlifted closures @@ -332,6 +370,43 @@ data PrimType | PDouble deriving (Eq, Show, Generic) +data WhatNext + = ThreadRunGHC + | ThreadInterpret + | ThreadKilled + | ThreadComplete + | WhatNextUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data WhyBlocked + = NotBlocked + | BlockedOnMVar + | BlockedOnMVarRead + | BlockedOnBlackHole + | BlockedOnRead + | BlockedOnWrite + | BlockedOnDelay + | BlockedOnSTM + | BlockedOnDoProc + | BlockedOnCCall + | BlockedOnCCall_Interruptible + | BlockedOnMsgThrowTo + | ThreadMigrating + | BlockedOnIOCompletion + | WhyBlockedUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data TsoFlags + = TsoLocked + | TsoBlockx + | TsoInterruptible + | TsoStoppedOnBreakpoint + | TsoMarked + | TsoSqueezed + | TsoAllocLimit + | TsoFlagsUnknownValue Word32 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + -- | For generic code, this function returns all referenced closures. allClosures :: GenClosure b -> [b] allClosures (ConstrClosure {..}) = ptrArgs ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs ===================================== @@ -0,0 +1,47 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.FFIClosures (module Reexport) where + +-- NOTE [hsc and CPP workaround] +-- +-- # Problem +-- +-- Often, .hsc files are used to get the correct offsets of C struct fields. +-- Those structs may be affected by CPP directives e.g. profiled vs not profiled +-- closure headers is affected by the PROFILED cpp define. Since we are building +-- multiple variants of the RTS, we must support all possible offsets e.g. by +-- running hsc2hs with cpp defines corresponding to each RTS flavour. The +-- problem is that GHC's build system runs hsc2hs *only once* per .hsc file +-- without properly setting cpp defines. This results in the same (probably +-- incorrect) offsets into our C structs. +-- +-- +-- # Workaround +-- +-- To work around this issue, we create multiple .hsc files each manually +-- defining thir cpp defines (see e.g. FFIClosures_ProfilingDisabled.hsc and +-- FFIClosures_ProfilingEnabled.hsc). Then we rely on cpp defines working +-- correctly in .hs files and use CPP to switch on which .hsc module to +-- re-export (see below). In each case we import the desired .hsc module as +-- `Reexport` and we import `()` (i.e. nothing) from all other .hsc variants +-- just so that the build system sees all .hsc file as dependencies. +-- +-- +-- # Future Work +-- +-- * Duplication of the code in the .hsc files could be reduced simply by +-- placing the code in a single .hsc.in file and `#include`ing it from each +-- .hsc file. The .hsc files would only be responsible for setting the correct +-- cpp defines. This currently doesn't work as hadrian doesn't know to copy +-- the .hsc.in file to the build directory. +-- * The correct solution would be for the build system to run `hsc2hs` with the +-- correct cpp defines once per RTS flavour. +-- + +#if defined(PROFILING) +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled () +#else +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,131 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingDisabled where + +-- See [hsc and CPP workaround] + +#undef PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } + ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,130 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingEnabled where + +-- See [hsc and CPP workaround] + +#define PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo (module Reexport) where + +-- See [hsc and CPP workaround] + +#if defined(PROFILING) +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled () +#else +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,12 @@ +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled( + peekStgTSOProfInfo +) where + +import Prelude +import Foreign +import GHC.Exts.Heap.ProfInfo.Types + +-- | This implementation is used when PROFILING is undefined. +-- It always returns 'Nothing', because there is no profiling info available. +peekStgTSOProfInfo :: Ptr tsoPtr -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,165 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled( + peekStgTSOProfInfo +) where + +#if __GLASGOW_HASKELL__ >= 811 + +-- See [hsc and CPP workaround] + +#define PROFILING + +#include "Rts.h" +#undef BLOCK_SIZE +#undef MBLOCK_SIZE +#undef BLOCKS_PER_MBLOCK +#include "DerivedConstants.h" + +import Data.IntSet (IntSet) +import qualified Data.IntSet as IntSet +import Data.IntMap.Strict (IntMap) +import qualified Data.IntMap.Strict as IntMap +import Data.IORef (IORef, newIORef, readIORef, writeIORef) +import Foreign +import Foreign.C.String +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.Types +import Prelude + +-- Use Int based containers for pointers (addresses) for better performance. +-- These will be queried a lot! +type AddressSet = IntSet +type AddressMap = IntMap + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo tsoPtr = do + cccs_ptr <- peekByteOff tsoPtr cccsOffset + costCenterCacheRef <- newIORef IntMap.empty + cccs' <- peekCostCentreStack IntSet.empty costCenterCacheRef cccs_ptr + + return $ Just StgTSOProfInfo { + cccs = cccs' + } + +cccsOffset :: Int +cccsOffset = (#const OFFSET_StgTSO_cccs) + (#size StgHeader) + +peekCostCentreStack + :: AddressSet + -> IORef (AddressMap CostCentre) + -> Ptr costCentreStack + -> IO (Maybe CostCentreStack) +peekCostCentreStack _ _ ptr | ptr == nullPtr = return Nothing +peekCostCentreStack loopBreakers _ ptr | IntSet.member (ptrToInt ptr) loopBreakers = return Nothing +peekCostCentreStack loopBreakers costCenterCacheRef ptr = do + ccs_ccsID' <- (#peek struct CostCentreStack_, ccsID) ptr + ccs_cc_ptr <- (#peek struct CostCentreStack_, cc) ptr + ccs_cc' <- peekCostCentre costCenterCacheRef ccs_cc_ptr + ccs_prevStack_ptr <- (#peek struct CostCentreStack_, prevStack) ptr + let loopBreakers' = (IntSet.insert ptrAsInt loopBreakers) + ccs_prevStack' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_prevStack_ptr + ccs_indexTable_ptr <- (#peek struct CostCentreStack_, indexTable) ptr + ccs_indexTable' <- peekIndexTable loopBreakers' costCenterCacheRef ccs_indexTable_ptr + ccs_root_ptr <- (#peek struct CostCentreStack_, root) ptr + ccs_root' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_root_ptr + ccs_depth' <- (#peek struct CostCentreStack_, depth) ptr + ccs_scc_count' <- (#peek struct CostCentreStack_, scc_count) ptr + ccs_selected' <- (#peek struct CostCentreStack_, selected) ptr + ccs_time_ticks' <- (#peek struct CostCentreStack_, time_ticks) ptr + ccs_mem_alloc' <- (#peek struct CostCentreStack_, mem_alloc) ptr + ccs_inherited_alloc' <- (#peek struct CostCentreStack_, inherited_alloc) ptr + ccs_inherited_ticks' <- (#peek struct CostCentreStack_, inherited_ticks) ptr + + return $ Just CostCentreStack { + ccs_ccsID = ccs_ccsID', + ccs_cc = ccs_cc', + ccs_prevStack = ccs_prevStack', + ccs_indexTable = ccs_indexTable', + ccs_root = ccs_root', + ccs_depth = ccs_depth', + ccs_scc_count = ccs_scc_count', + ccs_selected = ccs_selected', + ccs_time_ticks = ccs_time_ticks', + ccs_mem_alloc = ccs_mem_alloc', + ccs_inherited_alloc = ccs_inherited_alloc', + ccs_inherited_ticks = ccs_inherited_ticks' + } + where + ptrAsInt = ptrToInt ptr + +peekCostCentre :: IORef (AddressMap CostCentre) -> Ptr costCentre -> IO CostCentre +peekCostCentre costCenterCacheRef ptr = do + costCenterCache <- readIORef costCenterCacheRef + case IntMap.lookup ptrAsInt costCenterCache of + (Just a) -> return a + Nothing -> do + cc_ccID' <- (#peek struct CostCentre_, ccID) ptr + cc_label_ptr <- (#peek struct CostCentre_, label) ptr + cc_label' <- peekCString cc_label_ptr + cc_module_ptr <- (#peek struct CostCentre_, module) ptr + cc_module' <- peekCString cc_module_ptr + cc_srcloc_ptr <- (#peek struct CostCentre_, srcloc) ptr + cc_srcloc' <- do + if cc_srcloc_ptr == nullPtr then + return Nothing + else + fmap Just (peekCString cc_srcloc_ptr) + cc_mem_alloc' <- (#peek struct CostCentre_, mem_alloc) ptr + cc_time_ticks' <- (#peek struct CostCentre_, time_ticks) ptr + cc_is_caf' <- (#peek struct CostCentre_, is_caf) ptr + cc_link_ptr <- (#peek struct CostCentre_, link) ptr + cc_link' <- if cc_link_ptr == nullPtr then + return Nothing + else + fmap Just (peekCostCentre costCenterCacheRef cc_link_ptr) + + let result = CostCentre { + cc_ccID = cc_ccID', + cc_label = cc_label', + cc_module = cc_module', + cc_srcloc = cc_srcloc', + cc_mem_alloc = cc_mem_alloc', + cc_time_ticks = cc_time_ticks', + cc_is_caf = cc_is_caf', + cc_link = cc_link' + } + + writeIORef costCenterCacheRef (IntMap.insert ptrAsInt result costCenterCache) + + return result + where + ptrAsInt = ptrToInt ptr + +peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable) +peekIndexTable _ _ ptr | ptr == nullPtr = return Nothing +peekIndexTable loopBreakers costCenterCacheRef ptr = do + it_cc_ptr <- (#peek struct IndexTable_, cc) ptr + it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr + it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr + it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr + it_next_ptr <- (#peek struct IndexTable_, next) ptr + it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr + it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr + + return $ Just IndexTable { + it_cc = it_cc', + it_ccs = it_ccs', + it_next = it_next', + it_back_edge = it_back_edge' + } + +-- | casts a @Ptr@ to an @Int@ +ptrToInt :: Ptr a -> Int +ptrToInt (Ptr a##) = I## (addr2Int## a##) + +#else +import Prelude +import Foreign + +import GHC.Exts.Heap.ProfInfo.Types + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs ===================================== @@ -0,0 +1,56 @@ +{-# LANGUAGE DeriveGeneric #-} + +module GHC.Exts.Heap.ProfInfo.Types where + +import Prelude +import Data.Word +import GHC.Generics + +-- | This is a somewhat faithful representation of StgTSOProfInfo. See +-- +-- for more details on this data structure. +data StgTSOProfInfo = StgTSOProfInfo { + cccs :: Maybe CostCentreStack +} deriving (Show, Generic) + +-- | This is a somewhat faithful representation of CostCentreStack. See +-- +-- for more details on this data structure. +data CostCentreStack = CostCentreStack { + ccs_ccsID :: Int, + ccs_cc :: CostCentre, + ccs_prevStack :: Maybe CostCentreStack, + ccs_indexTable :: Maybe IndexTable, + ccs_root :: Maybe CostCentreStack, + ccs_depth :: Word, + ccs_scc_count :: Word64, + ccs_selected :: Word, + ccs_time_ticks :: Word, + ccs_mem_alloc :: Word64, + ccs_inherited_alloc :: Word64, + ccs_inherited_ticks :: Word +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of CostCentre. See +-- +-- for more details on this data structure. +data CostCentre = CostCentre { + cc_ccID :: Int, + cc_label :: String, + cc_module :: String, + cc_srcloc :: Maybe String, + cc_mem_alloc :: Word64, + cc_time_ticks :: Word, + cc_is_caf :: Bool, + cc_link :: Maybe CostCentre +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of IndexTable. See +-- +-- for more details on this data structure. +data IndexTable = IndexTable { + it_cc :: CostCentre, + it_ccs :: Maybe CostCentreStack, + it_next :: Maybe IndexTable, + it_back_edge :: Bool +} deriving (Show, Generic, Eq) ===================================== libraries/ghc-heap/ghc-heap.cabal.in ===================================== @@ -25,6 +25,7 @@ library build-depends: base >= 4.9.0 && < 5.0 , ghc-prim > 0.2 && < 0.8 , rts == 1.0.* + , containers >= 0.6.2.1 && < 0.7 ghc-options: -Wall cmm-sources: cbits/HeapPrim.cmm @@ -39,3 +40,10 @@ library GHC.Exts.Heap.InfoTable.Types GHC.Exts.Heap.InfoTableProf GHC.Exts.Heap.Utils + GHC.Exts.Heap.FFIClosures + GHC.Exts.Heap.FFIClosures_ProfilingDisabled + GHC.Exts.Heap.FFIClosures_ProfilingEnabled + GHC.Exts.Heap.ProfInfo.Types + GHC.Exts.Heap.ProfInfo.PeekProfInfo + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled ===================================== libraries/ghc-heap/tests/TestUtils.hs ===================================== @@ -0,0 +1,7 @@ +{-# LANGUAGE MagicHash #-} +module TestUtils where + +assertEqual :: (Show a, Eq a) => a -> a -> IO () +assertEqual a b + | a /= b = error (show a ++ " /= " ++ show b) + | otherwise = return () ===================================== libraries/ghc-heap/tests/all.T ===================================== @@ -36,3 +36,18 @@ test('closure_size_noopt', ], compile_and_run, ['']) +test('tso_and_stack_closures', + [extra_files(['create_tso.c','create_tso.h','TestUtils.hs']), + only_ways(['profthreaded']), + ignore_stdout, + ignore_stderr + ], + multi_compile_and_run, ['tso_and_stack_closures', [('create_tso.c','')], '']) + +test('parse_tso_flags', + [extra_files(['TestUtils.hs']), + only_ways(['normal']), + ignore_stdout, + ignore_stderr + ], + compile_and_run, ['']) ===================================== libraries/ghc-heap/tests/create_tso.c ===================================== @@ -0,0 +1,82 @@ +#include "Rts.h" +#include "RtsAPI.h" + +// Assumes the rts is paused +void unpack_closure + ( StgClosure * inClosure + , const StgInfoTable ** outInfoTablePtr + , int * outHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outHeapRep // Array of words + , int * outPointersSize // Size of outPointers (in words) + , StgClosure *** outPointers // Array of all pointers of the TSO + ) +{ + *outInfoTablePtr = get_itbl(inClosure); + + // Copy TSO pointers. + StgWord closureSizeW = heap_view_closureSize(inClosure); + int closureSizeB = sizeof(StgWord) * closureSizeW; + StgClosure ** pointers = malloc(closureSizeB); + *outPointersSize = collect_pointers(inClosure, closureSizeW, pointers); + *outPointers = pointers; + + // Copy the heap rep. + StgWord * heapRep = malloc(closureSizeB); + for (int i = 0; i < closureSizeW; i++) + { + heapRep[i] = ((StgWord*)inClosure)[i]; + } + + *outHeapRepSize = closureSizeB; + *outHeapRep = heapRep; +} + +// Must be called from a safe FFI call. +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ) +{ + // Pause RTS + PauseToken * token = rts_pause(); + Capability * cap = pauseTokenCapability(token); + + // Create TSO/Stack + HaskellObj trueClosure = rts_mkBool(cap, 1); + *outTso = createGenThread(cap, 500U, trueClosure); + + // Unpack TSO + unpack_closure( + (StgClosure*)(*outTso), + outTsoInfoTablePtr, + outTsoHeapRepSize, + outTsoHeapRep, + outTsoPointersSize, + outTsoPointers); + + // Unpack STACK + StgClosure * outStackAsClosure = (*outTsoPointers)[2]; + *outStack = (StgTSO *)outStackAsClosure; + unpack_closure( + outStackAsClosure, + outStackInfoTablePtr, + outStackHeapRepSize, + outStackHeapRep, + outStackPointersSize, + outStackPointers); + + // Resume RTS + rts_resume(token); +} ===================================== libraries/ghc-heap/tests/create_tso.h ===================================== @@ -0,0 +1,19 @@ +#include "Rts.h" +#include "RtsAPI.h" + +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ); ===================================== libraries/ghc-heap/tests/parse_tso_flags.hs ===================================== @@ -0,0 +1,17 @@ +import GHC.Exts.Heap.Closures +import GHC.Exts.Heap.FFIClosures +import TestUtils + +main :: IO() +main = do + assertEqual (parseTsoFlags 0) [] + assertEqual (parseTsoFlags 1) [TsoFlagsUnknownValue 1] + assertEqual (parseTsoFlags 2) [TsoLocked] + assertEqual (parseTsoFlags 4) [TsoBlockx] + assertEqual (parseTsoFlags 8) [TsoInterruptible] + assertEqual (parseTsoFlags 16) [TsoStoppedOnBreakpoint] + assertEqual (parseTsoFlags 64) [TsoMarked] + assertEqual (parseTsoFlags 128) [TsoSqueezed] + assertEqual (parseTsoFlags 256) [TsoAllocLimit] + + assertEqual (parseTsoFlags 6) [TsoLocked, TsoBlockx] ===================================== libraries/ghc-heap/tests/tso_and_stack_closures.hs ===================================== @@ -0,0 +1,167 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} + +import Control.Monad (forM_, unless) +import Data.List (find) +import Data.Word +import Foreign +import Foreign.C.Types +import GHC.IO ( IO(..) ) +import GHC.Exts +import GHC.Exts.Heap +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures +import GHC.Word + +import TestUtils + +main :: IO () +main = do + (tso, stack) <- {-# SCC "MyCostCentre" #-} createAndUnpackTSOAndSTACKClosure + assertEqual (getClosureType tso) TSO + assertEqual (what_next tso) ThreadRunGHC + assertEqual (why_blocked tso) NotBlocked + assertEqual (saved_errno tso) 0 + forM_ (flags tso) $ \flag -> case flag of + TsoFlagsUnknownValue _ -> error $ "Unknown flag: " ++ show flag + _ | flag `elem` + [ TsoLocked + , TsoBlockx + , TsoStoppedOnBreakpoint + , TsoSqueezed + ] -> error $ "Unexpected flag: " ++ show flag + _ -> return () + + assertEqual (getClosureType stack) STACK + +#if defined(PROFILING) + let costCentre = ccs_cc <$> (cccs =<< prof tso) + case costCentre of + Nothing -> error $ "No CostCentre found in TSO: " ++ show tso + Just _ -> case findMyCostCentre (linkedCostCentres costCentre) of + Just myCostCentre -> do + assertEqual (cc_label myCostCentre) "MyCostCentre" + assertEqual (cc_module myCostCentre) "Main" + assertEqual (cc_srcloc myCostCentre) (Just "tso_and_stack_closures.hs:23:48-80") + assertEqual (cc_is_caf myCostCentre) False + Nothing -> error $ "MyCostCentre not found in:\n" ++ unlines (cc_label <$> linkedCostCentres costCentre) +#endif + +linkedCostCentres :: Maybe CostCentre -> [CostCentre] +linkedCostCentres Nothing = [] +linkedCostCentres (Just cc) = cc : linkedCostCentres (cc_link cc) + +findMyCostCentre:: [CostCentre] -> Maybe CostCentre +findMyCostCentre ccs = find (\cc -> cc_label cc == "MyCostCentre") ccs + +getClosureType :: GenClosure b -> ClosureType +getClosureType = tipe . info + +type StgTso = Any +type StgStack = Any +data MBA a = MBA (MutableByteArray# a) +data BA = BA ByteArray# + +foreign import ccall safe "create_tso.h create_and_unpack_tso_and_stack" + c_create_and_unpack_tso_and_stack + :: Ptr (Ptr StgTso) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> Ptr (Ptr StgStack) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> IO () + +createAndUnpackTSOAndSTACKClosure + :: IO ( GenClosure (Ptr Any) + , GenClosure (Ptr Any) + ) +createAndUnpackTSOAndSTACKClosure = do + + alloca $ \ptrPtrTso -> do + alloca $ \ptrPtrTsoInfoTable -> do + alloca $ \ptrTsoHeapRepSize -> do + alloca $ \ptrPtrTsoHeapRep -> do + alloca $ \ptrTsoPointersSize -> do + alloca $ \ptrPtrPtrTsoPointers -> do + + alloca $ \ptrPtrStack -> do + alloca $ \ptrPtrStackInfoTable -> do + alloca $ \ptrStackHeapRepSize -> do + alloca $ \ptrPtrStackHeapRep -> do + alloca $ \ptrStackPointersSize -> do + alloca $ \ptrPtrPtrStackPointers -> do + + c_create_and_unpack_tso_and_stack + + ptrPtrTso + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + ptrPtrStack + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + let fromHeapRep + ptrPtrClosureInfoTable + ptrClosureHeapRepSize + ptrPtrClosureHeapRep + ptrClosurePointersSize + ptrPtrPtrClosurePointers = do + ptrInfoTable :: Ptr StgInfoTable <- peek ptrPtrClosureInfoTable + + heapRepSize :: Int <- fromIntegral <$> peek ptrClosureHeapRepSize + let I# heapRepSize# = heapRepSize + ptrHeapRep :: Ptr Word8 <- peek ptrPtrClosureHeapRep + MBA mutHeapRepBA <- IO $ \s -> let + (# s', mba# #) = newByteArray# heapRepSize# s + in (# s', MBA mba# #) + forM_ [0..heapRepSize-1] $ \i@(I# i#) -> do + W8# w <- peekElemOff ptrHeapRep i + IO (\s -> (# writeWord8Array# mutHeapRepBA i# w s, () #)) + BA heapRep <- IO $ \s -> let + (# s', ba# #) = unsafeFreezeByteArray# mutHeapRepBA s + in (# s', BA ba# #) + + pointersSize :: Int <- fromIntegral <$> peek ptrClosurePointersSize + ptrPtrPointers :: Ptr (Ptr Any) <- peek ptrPtrPtrClosurePointers + ptrPtrPointers :: [Ptr Any] <- sequence + [ peekElemOff ptrPtrPointers i + | i <- [0..pointersSize-1] + ] + + getClosureDataFromHeapRep + heapRep + ptrInfoTable + ptrPtrPointers + + tso <- fromHeapRep + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + stack <- fromHeapRep + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + return (tso, stack) ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables, - GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards #-} + GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards, + CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-} -- | @@ -29,7 +30,7 @@ import GHCi.TH.Binary () -- For Binary instances import GHCi.BreakArray import GHC.LanguageExtensions -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.ForeignSrcLang import GHC.Fingerprint import Control.Concurrent @@ -110,7 +111,7 @@ data Message a where -> Int -- constr tag -> Int -- pointer tag -> ByteString -- constructor desccription - -> Message (RemotePtr StgInfoTable) + -> Message (RemotePtr Heap.StgInfoTable) -- | Evaluate a statement EvalStmt @@ -211,7 +212,7 @@ data Message a where -- type reconstruction. GetClosure :: HValueRef - -> Message (GenClosure HValueRef) + -> Message (Heap.GenClosure HValueRef) -- | Evaluate something. This is used to support :force in GHCi. Seq @@ -449,10 +450,20 @@ instance Binary (FunPtr a) where get = castPtrToFunPtr <$> get -- Binary instances to support the GetClosure message -instance Binary StgInfoTable -instance Binary ClosureType -instance Binary PrimType -instance Binary a => Binary (GenClosure a) +#if MIN_VERSION_ghc_heap(8,11,0) +instance Binary Heap.StgTSOProfInfo +instance Binary Heap.CostCentreStack +instance Binary Heap.CostCentre +instance Binary Heap.IndexTable +instance Binary Heap.WhatNext +instance Binary Heap.WhyBlocked +instance Binary Heap.TsoFlags +#endif + +instance Binary Heap.StgInfoTable +instance Binary Heap.ClosureType +instance Binary Heap.PrimType +instance Binary a => Binary (Heap.GenClosure a) data Msg = forall a . (Binary a, Show a) => Msg (Message a) ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -32,7 +32,7 @@ import Data.Binary.Get import Data.ByteString (ByteString) import qualified Data.ByteString.Unsafe as B import GHC.Exts -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack import Foreign hiding (void) import Foreign.C @@ -93,8 +93,8 @@ run m = case m of toRemotePtr <$> mkConInfoTable tc ptrs nptrs tag ptrtag desc StartTH -> startTH GetClosure ref -> do - clos <- getClosureData =<< localRef ref - mapM (\(Box x) -> mkRemoteRef (HValue x)) clos + clos <- Heap.getClosureData =<< localRef ref + mapM (\(Heap.Box x) -> mkRemoteRef (HValue x)) clos Seq ref -> doSeq ref ResumeSeq ref -> resumeSeq ref _other -> error "GHCi.Run.run" ===================================== rts/Heap.c ===================================== @@ -203,7 +203,26 @@ StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[siz ptrs[nptrs++] = (StgClosure *)((StgMVar *)closure)->tail; ptrs[nptrs++] = ((StgMVar *)closure)->value; break; + case TSO: + ASSERT((StgClosure *)((StgTSO *)closure)->_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->_link; + ASSERT((StgClosure *)((StgTSO *)closure)->global_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->global_link; + + ASSERT((StgClosure *)((StgTSO *)closure)->stackobj != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->stackobj; + + ASSERT((StgClosure *)((StgTSO *)closure)->trec != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->trec; + + ASSERT((StgClosure *)((StgTSO *)closure)->blocked_exceptions != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->blocked_exceptions; + + ASSERT((StgClosure *)((StgTSO *)closure)->bq != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->bq; + + break; case WEAK: ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->cfinalizers; ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->key; ===================================== rts/PrimOps.cmm ===================================== @@ -2371,11 +2371,11 @@ stg_unpackClosurezh ( P_ closure ) clos = UNTAG(closure); W_ len; - // The array returned is the raw data for the entire closure. + // The array returned, dat_arr, is the raw data for the entire closure. // The length is variable based upon the closure type, ptrs, and non-ptrs (len) = foreign "C" heap_view_closureSize(clos "ptr"); - W_ ptrs_arr_sz, ptrs_arr_cards, dat_arr_sz; + W_ dat_arr_sz; dat_arr_sz = SIZEOF_StgArrBytes + WDS(len); ("ptr" dat_arr) = ccall allocateMightFail(MyCapability() "ptr", BYTES_TO_WDS(dat_arr_sz)); @@ -2396,7 +2396,7 @@ for: W_ ptrArray; - // Follow the pointers + // Collect pointers. ("ptr" ptrArray) = foreign "C" heap_view_closurePtrs(MyCapability() "ptr", clos "ptr"); return (info, dat_arr, ptrArray); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/328f27d87e734a407d08b9b65a42e2b3bb4014f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/328f27d87e734a407d08b9b65a42e2b3bb4014f8 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 Wed Nov 18 16:06:49 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 11:06:49 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/con-info-new Message-ID: <5fb5469960a16_8313fd6928badc8178314@gitlab.mail> Matthew Pickering pushed new branch wip/con-info-new at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/con-info-new 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 Wed Nov 18 16:09:08 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 11:09:08 -0500 Subject: [Git][ghc/ghc][wip/con-info-new] 6 commits: Revert "Remove GHC.Types.Unique.Map module" Message-ID: <5fb547248ddda_83172204dc178533@gitlab.mail> Matthew Pickering pushed to branch wip/con-info-new at Glasgow Haskell Compiler / GHC Commits: 8cd6ef1a by Matthew Pickering at 2020-11-18T16:08:52+00:00 Revert "Remove GHC.Types.Unique.Map module" This reverts commit 1c7c6f1afc8e7f7ba5d256780bc9d5bb5f3e7601. - - - - - ec618c1b by Matthew Pickering at 2020-11-18T16:08:52+00:00 Profiling by info table mode (-hi) - - - - - 141cff71 by Matthew Pickering at 2020-11-18T16:08:52+00:00 IPE? - - - - - 28582546 by Matthew Pickering at 2020-11-18T16:08:52+00:00 Data Con info - - - - - 249abf30 by Matthew Pickering at 2020-11-18T16:08:52+00:00 Add whereFrom# primop - - - - - 902ed6a0 by Matthew Pickering at 2020-11-18T16:08:52+00:00 Add test for whereFrom# - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d0bfc9183078dcdb56081fd50cbb5493ccfb38a1...902ed6a00e715a11d61d5cc24e5c901f6e6ffa99 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d0bfc9183078dcdb56081fd50cbb5493ccfb38a1...902ed6a00e715a11d61d5cc24e5c901f6e6ffa99 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 Wed Nov 18 16:18:48 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 11:18:48 -0500 Subject: [Git][ghc/ghc][wip/con-info-new] 6 commits: Revert "Remove GHC.Types.Unique.Map module" Message-ID: <5fb5496860736_83115dbfc3017891d@gitlab.mail> Matthew Pickering pushed to branch wip/con-info-new at Glasgow Haskell Compiler / GHC Commits: 2b7f03bd by Matthew Pickering at 2020-11-18T16:17:44+00:00 Revert "Remove GHC.Types.Unique.Map module" This reverts commit 1c7c6f1afc8e7f7ba5d256780bc9d5bb5f3e7601. - - - - - c8cdf1d3 by Matthew Pickering at 2020-11-18T16:17:44+00:00 Profiling by info table mode (-hi) - - - - - ef6d046e by Matthew Pickering at 2020-11-18T16:18:33+00:00 IPE? - - - - - d8e27abe by Matthew Pickering at 2020-11-18T16:18:34+00:00 Data Con info - - - - - 6e759ddc by Matthew Pickering at 2020-11-18T16:18:34+00:00 Add whereFrom# primop - - - - - a657a8b3 by Matthew Pickering at 2020-11-18T16:18:34+00:00 Add test for whereFrom# - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/902ed6a00e715a11d61d5cc24e5c901f6e6ffa99...a657a8b3024554383b9a591d82ee5a43f36900e9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/902ed6a00e715a11d61d5cc24e5c901f6e6ffa99...a657a8b3024554383b9a591d82ee5a43f36900e9 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 Wed Nov 18 16:24:46 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 11:24:46 -0500 Subject: [Git][ghc/ghc][wip/con-info-new] 6 commits: Revert "Remove GHC.Types.Unique.Map module" Message-ID: <5fb54ace37379_8313fd6c4f9e6f81807a@gitlab.mail> Matthew Pickering pushed to branch wip/con-info-new at Glasgow Haskell Compiler / GHC Commits: 4addeede by Matthew Pickering at 2020-11-18T16:24:25+00:00 Revert "Remove GHC.Types.Unique.Map module" This reverts commit 1c7c6f1afc8e7f7ba5d256780bc9d5bb5f3e7601. - - - - - d5e70644 by Matthew Pickering at 2020-11-18T16:24:29+00:00 Profiling by info table mode (-hi) - - - - - 8bd1b823 by Matthew Pickering at 2020-11-18T16:24:29+00:00 IPE? - - - - - 5cfd5a1c by Matthew Pickering at 2020-11-18T16:24:29+00:00 Data Con info - - - - - 4cd24bae by Matthew Pickering at 2020-11-18T16:24:29+00:00 Add whereFrom# primop - - - - - 2a7b7100 by Matthew Pickering at 2020-11-18T16:24:29+00:00 Add test for whereFrom# - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a657a8b3024554383b9a591d82ee5a43f36900e9...2a7b71001e3baf98cba33e350fbf09254dbf35f9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a657a8b3024554383b9a591d82ee5a43f36900e9...2a7b71001e3baf98cba33e350fbf09254dbf35f9 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 Wed Nov 18 16:30:44 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 11:30:44 -0500 Subject: [Git][ghc/ghc][wip/con-info-new] 5 commits: Profiling by info table mode (-hi) Message-ID: <5fb54c34cc91f_831159da9581809c8@gitlab.mail> Matthew Pickering pushed to branch wip/con-info-new at Glasgow Haskell Compiler / GHC Commits: 34b03977 by Matthew Pickering at 2020-11-18T16:30:35+00:00 Profiling by info table mode (-hi) - - - - - e2436d98 by Matthew Pickering at 2020-11-18T16:30:35+00:00 IPE? - - - - - 66cc88c2 by Matthew Pickering at 2020-11-18T16:30:35+00:00 Data Con info - - - - - 1886fe3b by Matthew Pickering at 2020-11-18T16:30:35+00:00 Add whereFrom# primop - - - - - 02618707 by Matthew Pickering at 2020-11-18T16:30:35+00:00 Add test for whereFrom# - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a7b71001e3baf98cba33e350fbf09254dbf35f9...02618707cd39b74d109de9e1c45c495eb8d5f340 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a7b71001e3baf98cba33e350fbf09254dbf35f9...02618707cd39b74d109de9e1c45c495eb8d5f340 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 Wed Nov 18 16:42:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 11:42:30 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/bss-alignment Message-ID: <5fb54ef66dc76_8313fd6cb4a229818313c@gitlab.mail> Ben Gamari pushed new branch wip/bss-alignment at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/bss-alignment 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 Wed Nov 18 16:42:48 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 11:42:48 -0500 Subject: [Git][ghc/ghc][wip/bss-alignment] rts/linker: Align bssSize to page size when mapping symbol extras Message-ID: <5fb54f087826d_8313fd6cb5348a01833d2@gitlab.mail> Ben Gamari pushed to branch wip/bss-alignment at Glasgow Haskell Compiler / GHC Commits: 0ab1a308 by Ben Gamari at 2020-11-18T11:42:43-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - 1 changed file: - rts/linker/SymbolExtras.c Changes: ===================================== rts/linker/SymbolExtras.c ===================================== @@ -77,7 +77,9 @@ int ocAllocateExtras(ObjectCode* oc, int count, int first, int bssSize) /* N.B. We currently can't mark symbol extras as non-executable in this * case. */ size_t n = roundUpToPage(oc->fileSize); - bssSize = roundUpToAlign(bssSize, 8); + // round bssSize up to the nearest page size since we need to ensure that + // symbol_extras is aligned to a page boundary so it can be mprotect'd. + bssSize = roundUpToPage(bssSize); size_t allocated_size = n + bssSize + extras_size; void *new = mmapForLinker(allocated_size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); if (new) { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ab1a308139e73070b23b156a83eb094a97ba0ec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0ab1a308139e73070b23b156a83eb094a97ba0ec 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 Wed Nov 18 16:56:13 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 11:56:13 -0500 Subject: [Git][ghc/ghc][wip/con-info] 144 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fb5522d22307_8313fd68e7968d818695c@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - faa95a99 by Matthew Pickering at 2020-11-18T13:42:30+00:00 Fix haddock parse error - - - - - 4addeede by Matthew Pickering at 2020-11-18T16:24:25+00:00 Revert "Remove GHC.Types.Unique.Map module" This reverts commit 1c7c6f1afc8e7f7ba5d256780bc9d5bb5f3e7601. - - - - - 34b03977 by Matthew Pickering at 2020-11-18T16:30:35+00:00 Profiling by info table mode (-hi) - - - - - e2436d98 by Matthew Pickering at 2020-11-18T16:30:35+00:00 IPE? - - - - - 66cc88c2 by Matthew Pickering at 2020-11-18T16:30:35+00:00 Data Con info - - - - - 1886fe3b by Matthew Pickering at 2020-11-18T16:30:35+00:00 Add whereFrom# primop - - - - - 02618707 by Matthew Pickering at 2020-11-18T16:30:35+00:00 Add test for whereFrom# - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9332454f4c3a7615c6a94f70bcf67f05fd9d7b6...02618707cd39b74d109de9e1c45c495eb8d5f340 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d9332454f4c3a7615c6a94f70bcf67f05fd9d7b6...02618707cd39b74d109de9e1c45c495eb8d5f340 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 Wed Nov 18 17:13:46 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 12:13:46 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Data Con info Message-ID: <5fb5564ae51c2_8313fd69bebda7818951a@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: b0ed0e8a by Matthew Pickering at 2020-11-18T17:13:22+00:00 Data Con info - - - - - 001e786c by Matthew Pickering at 2020-11-18T17:13:22+00:00 Add whereFrom# primop - - - - - 03c4d3ec by Matthew Pickering at 2020-11-18T17:13:22+00:00 Add test for whereFrom# - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/IPE.hs - includes/stg/MiscClosures.h - libraries/base/GHC/Stack/CCS.hsc - rts/PrimOps.cmm - rts/RtsSymbols.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/02618707cd39b74d109de9e1c45c495eb8d5f340...03c4d3ecf69ab5681e86b9e6051892ef3e626b45 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/02618707cd39b74d109de9e1c45c495eb8d5f340...03c4d3ecf69ab5681e86b9e6051892ef3e626b45 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 Wed Nov 18 17:15:21 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Wed, 18 Nov 2020 12:15:21 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Data Con info Message-ID: <5fb556a92c51b_8313fd6c27b5ad8190251@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: a6054214 by Matthew Pickering at 2020-11-18T17:15:08+00:00 Data Con info - - - - - 82d11a29 by Matthew Pickering at 2020-11-18T17:15:08+00:00 Add whereFrom# primop - - - - - 2f1a52e7 by Matthew Pickering at 2020-11-18T17:15:09+00:00 Add test for whereFrom# - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/IPE.hs - includes/stg/MiscClosures.h - libraries/base/GHC/Stack/CCS.hsc - rts/PrimOps.cmm - rts/RtsSymbols.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/03c4d3ecf69ab5681e86b9e6051892ef3e626b45...2f1a52e7e2f04f224174791d80c84247ad79f38f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/03c4d3ecf69ab5681e86b9e6051892ef3e626b45...2f1a52e7e2f04f224174791d80c84247ad79f38f 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 Wed Nov 18 19:37:17 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 14:37:17 -0500 Subject: [Git][ghc/ghc][ghc-9.0] 2 commits: Export SPEC from GHC.Exts (#13681) Message-ID: <5fb577ed92321_36a7f2b0ae847273@gitlab.mail> Ben Gamari pushed to branch ghc-9.0 at Glasgow Haskell Compiler / GHC Commits: c94c56d5 by Sylvain Henry at 2020-11-10T11:04:03-05:00 Export SPEC from GHC.Exts (#13681) (cherry picked from commit 4c407f6e71f096835f8671e2d3ea6bda38074314) - - - - - d4483f7b by Ben Gamari at 2020-11-14T06:49:57-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. (cherry picked from commit 6d21ecee535782f01dba9947a49e282afee25724) - - - - - 2 changed files: - libraries/base/GHC/Exts.hs - rts/linker/PEi386.c Changes: ===================================== libraries/base/GHC/Exts.hs ===================================== @@ -67,7 +67,7 @@ module GHC.Exts breakpoint, breakpointCond, -- * Ids with special behaviour - inline, noinline, lazy, oneShot, + inline, noinline, lazy, oneShot, SPEC (..), -- * Running 'RealWorld' state thread runRW#, ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7fcca77f1b3d315b95de2acc76bdac3512a522ff...d4483f7b81dc7bd3d246fc22728a1ec86570e6e8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7fcca77f1b3d315b95de2acc76bdac3512a522ff...d4483f7b81dc7bd3d246fc22728a1ec86570e6e8 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 Wed Nov 18 19:37:45 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 14:37:45 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 2 commits: Demand: Interleave usage and strictness demands (#18903) Message-ID: <5fb57809262e0_36a7f2b0c6447458@gitlab.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: b8e7e479 by Sebastian Graf at 2020-11-18T20:28:24+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands ============ Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1((1(U),S(U)))`. This would allow Nested CPR to unbox the division, for example. Nested strict product demands ============================= Fixing #18903 gives us enough expressiveness to tackle #18885, where we have ```hs f :: Int -> Int f y = let x | expensive y == 1 = (expensive (y+1), expensive (y+2)) | otherwise = (expensive (y+3), expensive (y+4)) in case () of _ | expensive (y+5) == 42 -> fst x _ | expensive (y+6) == 41 -> fst x + snd x _ | otherwise -> 0 ``` Here, we used to give `x` demand `1P(1P(U),1P(U))`. The outer `1` is because `x` is used lazily and the inner `1`s are redundant with that fact. That leaves some expressiveness on the table. After this change, we infer `1P(SP(U),1P(U))`, meaning that *whenever we evaluate `x`*, we evaluate its first component strictly, effectively making strictness product demands apply *relatively*. Usage product demands still apply absolutely, though. More details on how we could exploit the new language in `Note [Absent sub-demands]`. Fixes #18903 and fixes #18885. While fixing regressions, I also discovered and fixed #18957. There's a single remaining regression in `T9630`, which increases +16% in residency but decreases slightly in total allocations. I checked the heap profile, which doesn't suggest any obvious regressions. Ticky doesn't point to the reason either, because total allocations actually improved. I think it's OK to just accept it. Metric Increase: T9630 Metric Decrease: T13253-spj - - - - - e506b8c3 by Sebastian Graf at 2020-11-18T20:28:43+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ff04b6e387cde4f6f6bfc2959443d4e9f3f96990...e506b8c37f0ebcabc2d6e30f2d073b15b37a65b1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ff04b6e387cde4f6f6bfc2959443d4e9f3f96990...e506b8c37f0ebcabc2d6e30f2d073b15b37a65b1 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 Wed Nov 18 19:42:41 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 18 Nov 2020 14:42:41 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 2 commits: Demand: Interleave usage and strictness demands (#18903) Message-ID: <5fb579317b6f1_36a7f2b0728480ae@gitlab.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 8896c6fc by Sebastian Graf at 2020-11-18T20:41:56+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands ============ Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1CS(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Nested strict product demands ============================= Fixing #18903 gives us enough expressiveness to tackle #18885, where we have ```hs f :: Int -> Int f y = let x | expensive y == 1 = (expensive (y+1), expensive (y+2)) | otherwise = (expensive (y+3), expensive (y+4)) in case () of _ | expensive (y+5) == 42 -> fst x _ | expensive (y+6) == 41 -> fst x + snd x _ | otherwise -> 0 ``` Here, we used to give `x` demand `1P(1P(U),1P(U))`. The outer `1` is because `x` is used lazily and the inner `1`s are redundant with that fact. That leaves some expressiveness on the table. After this change, we infer `1P(SP(U),1P(U))`, meaning that *whenever we evaluate `x`*, we evaluate its first component strictly, effectively making strictness product demands apply *relatively*. Usage product demands still apply absolutely, though. More details on how we could exploit the new language in `Note [Absent sub-demands]`. Fixes #18903 and fixes #18885. While fixing regressions, I also discovered and fixed #18957. There's a single remaining regression in `T9630`, which increases +16% in residency but decreases slightly in total allocations. I checked the heap profile, which doesn't suggest any obvious regressions. Ticky doesn't point to the reason either, because total allocations actually improved. I think it's OK to just accept it. Metric Increase: T9630 Metric Decrease: T13253-spj - - - - - 0195df96 by Sebastian Graf at 2020-11-18T20:42:33+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e506b8c37f0ebcabc2d6e30f2d073b15b37a65b1...0195df964354808e4c8574d518f21f35fef0033e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e506b8c37f0ebcabc2d6e30f2d073b15b37a65b1...0195df964354808e4c8574d518f21f35fef0033e 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 Wed Nov 18 19:42:43 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 14:42:43 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/make-verbosity Message-ID: <5fb57933c0e8_36a7f2b113c48274@gitlab.mail> Ben Gamari pushed new branch wip/make-verbosity at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/make-verbosity 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 Wed Nov 18 19:45:33 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Wed, 18 Nov 2020 14:45:33 -0500 Subject: [Git][ghc/ghc][wip/amg/renamer-refactor] Minor fixups Message-ID: <5fb579dde9a2f_36a7f2b0ee451026@gitlab.mail> Adam Gundry pushed to branch wip/amg/renamer-refactor at Glasgow Haskell Compiler / GHC Commits: 5ceb206d by Adam Gundry at 2020-11-18T19:14:44+00:00 Minor fixups - - - - - 6 changed files: - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Types/Name/Reader.hs Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -765,8 +765,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name = do lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name case res of NameNotFound -> return (Left (unknownSubordinateErr doc rdr_name)) - FoundChild _p (ChildName n) -> return (Right n) - FoundChild _p (ChildField fl) -> return (Right (flSelector fl)) -- AMG TODO: really? + FoundChild _p child -> return (Right (childName child)) IncorrectParent {} -- See [Mismatched class methods and associated type families] -- in TcInstDecls. ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -960,8 +960,9 @@ filterImports iface decl_spec (Just (want_hiding, L l import_items)) -- See Note [Dealing with imports] imp_occ_env :: OccEnv (NameEnv (Child, -- the name or field AvailInfo, -- the export item providing it - Maybe Name)) -- TODO comment - imp_occ_env = mkOccEnv_C (plusNameEnv_C combine) [ (occName c, mkNameEnv [(childName c, (c, a, Nothing))]) + Maybe Name)) -- the parent of associated types + imp_occ_env = mkOccEnv_C (plusNameEnv_C combine) + [ (occName c, mkNameEnv [(childName c, (c, a, Nothing))]) | a <- all_avails , c <- availChildren a] -- See Note [Dealing with imports] @@ -983,7 +984,8 @@ filterImports iface decl_spec (Just (want_hiding, L l import_items)) (c2, a2, mb2) = ASSERT2( c1 == c2 && isNothing mb1 && isNothing mb2 && (isAvailTC a1 || isAvailTC a2) , ppr c1 <+> ppr c2 <+> ppr a1 <+> ppr a2 <+> ppr mb1 <+> ppr mb2 ) - if isAvailTC a1 then (c1, a1, Nothing) else (c2, a2, Nothing) -- AMG TODO: is Nothing right? + if isAvailTC a1 then (c1, a1, Nothing) + else (c1, a2, Nothing) isAvailTC AvailTC{} = True isAvailTC _ = False ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -22,7 +22,9 @@ import GHC.Tc.Utils.TcType import GHC.Core.Type import GHC.Core.DataCon import GHC.Types.Name -import GHC.Types.Name.Reader ( pprNameProvenance , GlobalRdrElt (..), globalRdrEnvElts, gre_name ) +import GHC.Types.Name.Reader ( pprNameProvenance , GlobalRdrElt (..) + , globalRdrEnvElts, gre_name + , isOverloadedRecFldGRE ) import GHC.Builtin.Names ( gHC_ERR ) import GHC.Types.Id import GHC.Types.Var.Set @@ -470,10 +472,12 @@ pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (HoleFit {..}) = holeVs = sep $ map (parens . (text "_" <+> dcolon <+>) . ppr) hfMatches holeDisp = if sMs then holeVs else sep $ replicate (length hfMatches) $ text "_" - occDisp = pprPrefixOcc $ case hfCand of - GreHFCand gre -> occName gre - NameHFCand name -> occName name - IdHFCand id_ -> occName id_ + occDisp = case hfCand of + -- AMG TODO: make OutputableBndr GlobalRdrElt instance that does the right thing? + GreHFCand gre | isOverloadedRecFldGRE gre -> pprPrefixOcc (occName gre) + | otherwise -> pprPrefixOcc (gre_name gre) + NameHFCand name -> pprPrefixOcc name + IdHFCand id_ -> pprPrefixOcc id_ tyDisp = ppWhen sTy $ dcolon <+> ppr hfType has = not . null wrapDisp = ppWhen (has hfWrap && (sWrp || sWrpVars)) @@ -787,7 +791,7 @@ tcFilterHoleFits limit typed_hole ht@(hole_ty, _) candidates = #if __GLASGOW_HASKELL__ <= 810 IdHFCand id -> idName id #endif - GreHFCand gre -> gre_name gre -- AMG TODO dubious + GreHFCand gre -> gre_name gre NameHFCand name -> name discard_it = go subs seen maxleft ty elts keep_it eid eid_ty wrp ms = go (fit:subs) (extendVarSet seen eid) ===================================== compiler/GHC/Tc/Gen/Export.hs ===================================== @@ -526,8 +526,8 @@ lookupChildrenExport spec_parent rdr_items = ; return (Left (L l (IEName (L l ub))))} FoundChild par child -> do { checkPatSynParent spec_parent par child ; return $ case child of - ChildField fl -> Right (L (getLoc n) fl) - ChildName name -> Left (replaceLWrappedName n name) -- AMG TODO + ChildField fl -> Right (L (getLoc n) fl) + ChildName name -> Left (replaceLWrappedName n name) } IncorrectParent p g td gs -> failWithDcErr p g td gs ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -176,7 +176,7 @@ checkHsigIface tcg_env gr sig_iface -- be a reexport. In this case, make sure the 'Name' of the -- reexport matches the 'Name exported here. | [gre] <- lookupGlobalRdrEnv gr (nameOccName name) = do - let name' = gre_name gre -- AMG TODO this looks fishy + let name' = gre_name gre when (name /= name') $ do -- See Note [Error reporting bad reexport] -- TODO: Actually this error swizzle doesn't work ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -57,7 +57,7 @@ module GHC.Types.Name.Reader ( greRdrNames, greSrcSpan, greQualModName, gresToAvailInfo, greDefinitionModule, greDefinitionSrcSpan, - gre_name, -- AMG TODO: can we get rid of export? + gre_name, -- ** Global 'RdrName' mapping elements: 'GlobalRdrElt', 'Provenance', 'ImportSpec' GlobalRdrElt(..), isLocalGRE, isRecFldGRE, isOverloadedRecFldGRE, greLabel, @@ -750,10 +750,10 @@ gresToAvailInfo gres comb :: GlobalRdrElt -> AvailInfo -> AvailInfo comb _ (Avail n) = Avail n -- Duplicated name, should not happen - comb _ (AvailFL fl) = AvailFL fl -- TODO: shouldn't happen either? + comb _ (AvailFL fl) = AvailFL fl -- AMG TODO: shouldn't happen either? comb gre (AvailTC m ns fls) = case (gre_par gre, gre_child gre) of - (NoParent, ChildName me) -> AvailTC m (me:ns) fls -- Not sure this ever happens -- TODO: AvailTC invariant? + (NoParent, ChildName me) -> AvailTC m (me:ns) fls -- Not sure this ever happens -- AMG TODO: AvailTC invariant? (NoParent, ChildField fl) -> AvailTC m ns (fl:fls) (ParentIs {}, ChildName me) -> AvailTC m (insertChildIntoChildren m ns me) fls (ParentIs {}, ChildField fl) -> AvailTC m ns (fl:fls) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ceb206d45d7754acedc917af07e7a0646c0ef41 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5ceb206d45d7754acedc917af07e7a0646c0ef41 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 Wed Nov 18 20:08:01 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 18 Nov 2020 15:08:01 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: nativeGen/dwarf: Fix procedure end addresses Message-ID: <5fb57f217db9a_36a7f2b09586105@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - e4a82ad1 by Sebastian Graf at 2020-11-18T15:07:53-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Session.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cd78879414e78d0462b762ad10b62d90ca826a98...e4a82ad18c8b00d7f49660246ea8f69339a9db94 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cd78879414e78d0462b762ad10b62d90ca826a98...e4a82ad18c8b00d7f49660246ea8f69339a9db94 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 Wed Nov 18 21:22:50 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 16:22:50 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] NCG: Fix 64bit int comparisons on 32bit x86 Message-ID: <5fb590aa3a546_36a7f2b032c86686@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 410b43a2 by Andreas Klebinger at 2020-11-18T16:22:35-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) (cherry picked from commit fda3e50b559f6f25347f9ad7239e5003e27937b0) - - - - - 6 changed files: - compiler/nativeGen/X86/CodeGen.hs - compiler/nativeGen/X86/Cond.hs - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm Changes: ===================================== compiler/nativeGen/X86/CodeGen.hs ===================================== @@ -1804,6 +1804,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1821,22 +1850,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/nativeGen/X86/Cond.hs ===================================== @@ -13,22 +13,22 @@ import GhcPrelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condUnsigned :: Cond -> Bool ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/410b43a29576c40f4a65c9558f080a97c194636c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/410b43a29576c40f4a65c9558f080a97c194636c 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 Wed Nov 18 21:49:05 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 16:49:05 -0500 Subject: [Git][ghc/ghc][wip/bump-time] Bump time submodule to 1.11.1 Message-ID: <5fb596d19a7a8_36a7f2b01b088883@gitlab.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: 237d7268 by Ben Gamari at 2020-11-18T16:48:54-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 9 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/Main.hs - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 0633b48b010093f64f98ee494265436e96456aed ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 544046ba30a1bfe3e691ae1ae2e7db87fb34a858 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit c25d6a76702b454426e149fb590da5cb69f3bd0a ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit e079823775066bcab56b22842be6cce6e060fb9f ===================================== utils/ghc-cabal/Main.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -28,6 +29,7 @@ import Distribution.Verbosity import qualified Distribution.InstalledPackageInfo as Installed import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Utils.ShortText (fromShortText) +import Distribution.Utils.Path (getSymbolicPath) import Control.Exception (bracket) import Control.Monad @@ -433,7 +435,7 @@ generate directory distdir config_args variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd), - variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), + variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/237d72684b8b9bbd772942d113804e04c0784a97 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/237d72684b8b9bbd772942d113804e04c0784a97 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 Nov 19 02:26:00 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Wed, 18 Nov 2020 21:26:00 -0500 Subject: [Git][ghc/ghc] Pushed new branch gitlab/wip/T18857 Message-ID: <5fb5d7b8c7a25_36a7f2b032c1055d9@gitlab.mail> Moritz Angermann pushed new branch gitlab/wip/T18857 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/gitlab/wip/T18857 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 Nov 19 02:26:44 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Wed, 18 Nov 2020 21:26:44 -0500 Subject: [Git][ghc/ghc][wip/T18857] 4 commits: gitlab-ci: Run LLVM job on appropriately-labelled MRs Message-ID: <5fb5d7e4e90ca_36a7f2b113c1057f9@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 0c4c0082 by Ben Gamari at 2020-11-19T10:25:11+08:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 03b9d65f by Ben Gamari at 2020-11-19T10:25:11+08:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 09ce35c7 by Ben Gamari at 2020-11-19T10:25:11+08:00 hadrian: Don't use -fllvm to bootstrap under LLVM flavour Previously Hadrian's LLVM build flavours would use `-fllvm` for all invocations, even those to stage0 GHC. This meant that we needed to keep two LLVM versions around in all of the CI images. Moreover, it differed from the behavior of the old make build system's llvm flavours. Change this to reflect the behavior of the `make` build system, using `-fllvm` only with the stage1 and stage2 compilers. - - - - - 5807df4f by Ben Gamari at 2020-11-19T10:25:12+08:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' fixup ShortText & SymbolExtras - - - - - 9 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToLlvm/Base.hs - hadrian/src/Settings/Flavours/Llvm.hs - libraries/ghc-boot/GHC/Data/ShortText.hs - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/SymbolExtras.c - rts/linker/elf_reloc_aarch64.c - testsuite/driver/testlib.py Changes: ===================================== .gitlab-ci.yml ===================================== @@ -659,22 +659,6 @@ validate-x86_64-linux-deb9-debug: when: always expire_in: 2 week -# Disabled to alleviate CI load -.validate-x86_64-linux-deb9-llvm: - extends: .build-x86_64-linux-deb9 - stage: full-build - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - -nightly-x86_64-linux-deb9-llvm: - <<: *nightly - extends: .build-x86_64-linux-deb9 - stage: full-build - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - validate-x86_64-linux-deb9-integer-simple: extends: .build-x86_64-linux-deb9 stage: full-build @@ -759,6 +743,23 @@ release-x86_64-linux-deb10-dwarf: TEST_ENV: "x86_64-linux-deb10-dwarf" BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz" +validate-x86_64-linux-deb10-llvm: + extends: .build-x86_64-linux-deb10 + stage: full-build + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/' + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + +nightly-x86_64-linux-deb10-llvm: + <<: *nightly + extends: .build-x86_64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + ################################# # x86_64-linux-ubuntu 20.04 ################################# ===================================== compiler/GHC/CmmToLlvm/Base.hs ===================================== @@ -476,6 +476,8 @@ ghcInternalFunctions :: LlvmM () ghcInternalFunctions = do platform <- getPlatform let w = llvmWord platform + cint = LMInt $ widthInBits $ cIntWidth platform + mk "memcmp" cint [i8Ptr, i8Ptr, w] mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w] mk "memmove" i8Ptr [i8Ptr, i8Ptr, w] mk "memset" i8Ptr [i8Ptr, w, w] ===================================== hadrian/src/Settings/Flavours/Llvm.hs ===================================== @@ -25,5 +25,5 @@ mkLlvmFlavour :: Flavour -> Flavour mkLlvmFlavour flav = flav { name = name flav ++ "-llvm" , args = mconcat [ args flav - , builder Ghc ? arg "-fllvm" ] + , notStage0 ? builder Ghc ? arg "-fllvm" ] } ===================================== libraries/ghc-boot/GHC/Data/ShortText.hs ===================================== @@ -1,6 +1,22 @@ -{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-} +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} - +-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore. +-- LLVM based GHC's fail to compile memcmp ffi calls. These end up as memcmp$def in the llvm ir, however we +-- don't have any prototypes and subsequently the llvm toolchain chokes on them. Since 7fdcce6d, we use +-- ShortText for the package database. This however introduces this very module; which through inlining ends +-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in +-- the memcmp call we choke on. +-- +-- The solution thusly is to force late binding via the linker instead of inlining when comping with the +-- bootstrap compiler. This will produce a slower (slightly less optimised) stage1 compiler only. +-- +-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion. +-- +-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler, +-- we can drop this code as well. +#if GHC_STAGE < 1 +{-# OPTIONS_GHC -fignore-interface-pragmas #-} +#endif -- | -- An Unicode string for internal GHC use. Meant to replace String -- in places where being a lazy linked is not very useful and a more ===================================== rts/LinkerInternals.h ===================================== @@ -141,7 +141,7 @@ typedef struct _Segment { int n_sections; } Segment; -#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif ===================================== rts/linker/Elf.c ===================================== @@ -940,7 +940,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1867,6 +1867,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1940,6 +1941,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/SymbolExtras.c ===================================== @@ -77,7 +77,9 @@ int ocAllocateExtras(ObjectCode* oc, int count, int first, int bssSize) /* N.B. We currently can't mark symbol extras as non-executable in this * case. */ size_t n = roundUpToPage(oc->fileSize); - bssSize = roundUpToAlign(bssSize, 8); + // round bssSize up to the nearest page size since we need to ensure that + // symbol_extras is aligned to a page boundary so it can be mprotect'd. + bssSize = roundUpToPage(bssSize); size_t allocated_size = n + bssSize + extras_size; void *new = mmapForLinker(allocated_size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); if (new) { ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== testsuite/driver/testlib.py ===================================== @@ -2216,6 +2216,13 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + + # filter out nix garbage, that just keeps on showing up as errors on darwin + s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2286,6 +2293,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/866234216353eb87ba5fa5e9fccaf747c88bcab3...5807df4f99a6d109070b591331ed9f1f90cbd4f7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/866234216353eb87ba5fa5e9fccaf747c88bcab3...5807df4f99a6d109070b591331ed9f1f90cbd4f7 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 Nov 19 02:48:02 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 18 Nov 2020 21:48:02 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] 2 commits: rts: Refactor foreign export tracking Message-ID: <5fb5dce2931ff_36a7f2b113c1102a5@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: ed57c3a9 by Ben Gamari at 2020-11-18T21:39:41-05:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. (cherry picked from commit c492134912e5270180881b7345ee86dc32756bdd) - - - - - 65be3832 by Ben Gamari at 2020-11-18T21:39:53-05:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. (cherry picked from commit 40dc91069d15bfc1d81f1722b39e06cac8fdddd1) - - - - - 10 changed files: - compiler/deSugar/DsForeign.hs - includes/Rts.h - + includes/rts/ForeignExports.h - + rts/ForeignExports.c - + rts/ForeignExports.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/RtsSymbols.c - rts/rts.cabal.in Changes: ===================================== compiler/deSugar/DsForeign.hs ===================================== @@ -86,15 +86,16 @@ dsForeigns' :: [LForeignDecl GhcTc] dsForeigns' [] = return (NoStubs, nilOL) dsForeigns' fos = do + mod <- getModule fives <- mapM do_ldecl fos let (hs, cs, idss, bindss) = unzip4 fives fe_ids = concat idss - fe_init_code = map foreignExportInitialiser fe_ids + fe_init_code = foreignExportsInitialiser mod fe_ids -- return (ForeignStubs (vcat hs) - (vcat cs $$ vcat fe_init_code), + (vcat cs $$ fe_init_code), foldr (appOL . toOL) nilOL bindss) where do_ldecl (dL->L loc decl) = putSrcSpanDs loc (do_decl decl) @@ -667,8 +668,8 @@ mkFExportCBits dflags c_nm maybe_target arg_htys res_hty is_IO_res_ty cc ] -foreignExportInitialiser :: Id -> SDoc -foreignExportInitialiser hs_fn = +foreignExportsInitialiser :: Module -> [Id] -> SDoc +foreignExportsInitialiser mod hs_fns = -- Initialise foreign exports by registering a stable pointer from an -- __attribute__((constructor)) function. -- The alternative is to do this from stginit functions generated in @@ -677,14 +678,24 @@ foreignExportInitialiser hs_fn = -- all modules that are imported directly or indirectly are actually used by -- the program. -- (this is bad for big umbrella modules like Graphics.Rendering.OpenGL) + -- + -- See Note [Tracking foreign exports] in rts/ForeignExports.c vcat - [ text "static void stginit_export_" <> ppr hs_fn - <> text "() __attribute__((constructor));" - , text "static void stginit_export_" <> ppr hs_fn <> text "()" - , braces (text "foreignExportStablePtr" - <> parens (text "(StgPtr) &" <> ppr hs_fn <> text "_closure") - <> semi) + [ text "static struct ForeignExportsList" <+> list_symbol <+> equals + <+> braces (text ".exports = " <+> export_list) <> semi + , text "static void " <> ctor_symbol <> text "(void)" + <+> text " __attribute__((constructor));" + , text "static void " <> ctor_symbol <> text "()" + , braces (text "registerForeignExports" <> parens (char '&' <> list_symbol) <> semi) ] + where + mod_str = pprModuleName (moduleName mod) + ctor_symbol = text "stginit_export_" <> mod_str + list_symbol = text "stg_exports_" <> mod_str + export_list = braces $ pprWithCommas closure_ptr hs_fns + + closure_ptr :: Id -> SDoc + closure_ptr fn = text "(StgPtr) &" <> ppr fn <> text "_closure" mkHObj :: Type -> SDoc ===================================== includes/Rts.h ===================================== @@ -209,6 +209,9 @@ void _assertFail(const char *filename, unsigned int linenum) #include "rts/storage/GC.h" #include "rts/NonMoving.h" +/* Foreign exports */ +#include "rts/ForeignExports.h" + /* Other RTS external APIs */ #include "rts/Parallel.h" #include "rts/Signals.h" ===================================== includes/rts/ForeignExports.h ===================================== @@ -0,0 +1,38 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team, 1995-2009 + * + * Interface to the RTS's foreign export tracking code. + * + * Do not #include this file directly: #include "Rts.h" instead. + * + * To understand the structure of the RTS headers, see the wiki: + * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/source-tree/includes + * + * ---------------------------------------------------------------------------*/ + +#pragma once + +struct _ObjectCode; + +/* N.B. See Note [Tracking foreign exports] in + * rts/ForeignExports.c. */ +struct ForeignExportsList { + /* a link field for linking these together into lists. + */ + struct ForeignExportsList *next; + /* the length of ->exports */ + int n_entries; + /* if the RTS linker loaded the module, + * to which ObjectCode these exports belong. */ + struct _ObjectCode *oc; + /* if the RTS linker loaded the module, + * this points to an array of length ->n_entries + * recording the StablePtr for each export. */ + StgStablePtr **stable_ptrs; + /* the exported closures. of length ->exports. */ + StgPtr exports[]; +}; + +void registerForeignExports(struct ForeignExportsList *exports); + ===================================== rts/ForeignExports.c ===================================== @@ -0,0 +1,130 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team 2020 + * + * Management of foreign exports. + * + * ---------------------------------------------------------------------------*/ + +#include "Rts.h" +#include "RtsUtils.h" +#include "ForeignExports.h" + +/* protected by linker_mutex after start-up */ +static struct ForeignExportsList *pending = NULL; +static ObjectCode *loading_obj = NULL; + +/* + * Note [Tracking foreign exports] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * Foreign exports are garbage collection roots. That is, things (e.g. CAFs) + * depended upon by a module's `foreign export`s need to be kept alive for as + * long an module is loaded. To ensure this we create a stable pointer to each + * `foreign export`'d closure. This works as follows: + * + * 1. The compiler (namely GHC.HsToCore.Foreign.Decl.foreignExports) + * inserts a C-stub into each module containing a `foreign export`. This + * stub contains two things: + * + * - A `ForeignExportsList` listing all of the exported closures, and + * + * - An initializer which calls `registerForeignExports` with a reference to + * the `ForeignExportsList`. + * + * 2. When the module's object code is loaded, its initializer is called by the + * linker (this might be the system's dynamic linker or GHC's own static + * linker). `registerForeignExports` then places the module's + * `ForeignExportsList` on `pending` list. + * + * 3. When loading has finished (e.g. during RTS initialization or at the end + * of `Linker.c:ocTryLoad`) `processForeignExports` is called. Here we + * traverse the `pending` list and create a `StablePtr` for each export + * therein. + * + * The reason for this two-step process is that we are very restricted in what + * we can do in an initializer function. For instance, we cannot necessarily + * call `malloc` since the `libc`'s own initializer may not have run yet. + * For instance, doing exactly this resulted in #18548. + * + * Another consideration here is that the linker needs to know which + * `StablePtr`s belong to each `ObjectCode` so it can free them when the module is + * unloaded. For this reason, the linker informs us when it is loading an + * object by calling `foreignExportsLoadingObject` and + * `foreignExportsFinishedLoadingObject`. We take note of the `ObjectCode*` we + * are loading in `loading_obj` such that we can associate the `ForeignExportsList` with + * the `ObjectCode` in `processForeignExports`. We then record each of the + * StablePtrs we create in the ->stable_ptrs array of ForeignExportsList so + * they can be enumerated during unloading. + * + */ + +void registerForeignExports(struct ForeignExportsList *exports) +{ + ASSERT(exports->next == NULL); + ASSERT(exports->oc == NULL); + exports->next = pending; + exports->oc = loading_obj; + pending = exports; +} + +/* ----------------------------------------------------------------------------- + Create a StablePtr for a foreign export. This is normally called by + a C function with __attribute__((constructor)), which is generated + by GHC and linked into the module. + + If the object code is being loaded dynamically, then we remember + which StablePtrs were allocated by the constructors and free them + again in unloadObj(). + -------------------------------------------------------------------------- */ + +void foreignExportsLoadingObject(ObjectCode *oc) +{ + ASSERT(loading_obj == NULL); + loading_obj = oc; +} + +void foreignExportsFinishedLoadingObject() +{ + ASSERT(loading_obj != NULL); + loading_obj = NULL; + processForeignExports(); +} + +/* Caller must own linker_mutex so that we can safely modify + * oc->stable_ptrs. */ +void processForeignExports() +{ + while (pending) { + struct ForeignExportsList *cur = pending; + pending = cur->next; + + /* sanity check */ + ASSERT(cur->stable_ptrs == NULL); + + /* N.B. We only need to populate the ->stable_ptrs + * array if the object might later be unloaded. + */ + if (cur->oc != NULL) { + cur->stable_ptrs = + stgMallocBytes(sizeof(StgStablePtr*) * cur->n_entries, + "foreignExportStablePtr"); + + for (int i=0; i < cur->n_entries; i++) { + StgStablePtr *sptr = getStablePtr(cur->exports[i]); + + if (cur->oc != NULL) { + cur->stable_ptrs[i] = sptr; + } + } + cur->next = cur->oc->foreign_exports; + cur->oc->foreign_exports = cur; + } else { + /* can't be unloaded, don't bother populating + * ->stable_ptrs array. */ + for (int i=0; i < cur->n_entries; i++) { + getStablePtr(cur->exports[i]); + } + } + } +} ===================================== rts/ForeignExports.h ===================================== @@ -0,0 +1,21 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team 2020 + * + * Management of foreign exports. + * + * ---------------------------------------------------------------------------*/ + +#pragma once + +#include "Rts.h" +#include "LinkerInternals.h" + +#include "BeginPrivate.h" + +void foreignExportsLoadingObject(ObjectCode *oc); +void foreignExportsFinishedLoadingObject(void); +void processForeignExports(void); + +#include "EndPrivate.h" + ===================================== rts/Linker.c ===================================== @@ -26,6 +26,7 @@ #include "RtsSymbols.h" #include "RtsSymbolInfo.h" #include "Profiling.h" +#include "ForeignExports.h" #include "sm/OSMem.h" #include "linker/M32Alloc.h" #include "linker/CacheFlush.h" @@ -951,37 +952,6 @@ SymbolAddr* lookupSymbol( SymbolName* lbl ) return r; } -/* ----------------------------------------------------------------------------- - Create a StablePtr for a foreign export. This is normally called by - a C function with __attribute__((constructor)), which is generated - by GHC and linked into the module. - - If the object code is being loaded dynamically, then we remember - which StablePtrs were allocated by the constructors and free them - again in unloadObj(). - -------------------------------------------------------------------------- */ - -static ObjectCode *loading_obj = NULL; - -StgStablePtr foreignExportStablePtr (StgPtr p) -{ - ForeignExportStablePtr *fe_sptr; - StgStablePtr *sptr; - - sptr = getStablePtr(p); - - if (loading_obj != NULL) { - fe_sptr = stgMallocBytes(sizeof(ForeignExportStablePtr), - "foreignExportStablePtr"); - fe_sptr->stable_ptr = sptr; - fe_sptr->next = loading_obj->stable_ptrs; - loading_obj->stable_ptrs = fe_sptr; - } - - return sptr; -} - - /* ----------------------------------------------------------------------------- * Debugging aid: look in GHCi's object symbol tables for symbols * within DELTA bytes of the specified address, and show their names. @@ -1252,14 +1222,18 @@ static void freeOcStablePtrs (ObjectCode *oc) { // Release any StablePtrs that were created when this // object module was initialized. - ForeignExportStablePtr *fe_ptr, *next; + struct ForeignExportsList *exports, *next; - for (fe_ptr = oc->stable_ptrs; fe_ptr != NULL; fe_ptr = next) { - next = fe_ptr->next; - freeStablePtr(fe_ptr->stable_ptr); - stgFree(fe_ptr); + for (exports = oc->foreign_exports; exports != NULL; exports = next) { + next = exports->next; + for (int i = 0; i < exports->n_entries; i++) { + freeStablePtr(exports->stable_ptrs[i]); + } + stgFree(exports->stable_ptrs); + exports->stable_ptrs = NULL; + exports->next = NULL; } - oc->stable_ptrs = NULL; + oc->foreign_exports = NULL; } static void @@ -1416,7 +1390,7 @@ mkOc( pathchar *path, char *image, int imageSize, oc->n_segments = 0; oc->segments = NULL; oc->proddables = NULL; - oc->stable_ptrs = NULL; + oc->foreign_exports = NULL; #if defined(NEED_SYMBOL_EXTRAS) oc->symbol_extras = NULL; #endif @@ -1777,7 +1751,8 @@ int ocTryLoad (ObjectCode* oc) { IF_DEBUG(linker, debugBelch("ocTryLoad: ocRunInit start\n")); - loading_obj = oc; // tells foreignExportStablePtr what to do + // See Note [Tracking foreign exports] in ForeignExports.c + foreignExportsLoadingObject(oc); #if defined(OBJFORMAT_ELF) r = ocRunInit_ELF ( oc ); #elif defined(OBJFORMAT_PEi386) @@ -1787,7 +1762,7 @@ int ocTryLoad (ObjectCode* oc) { #else barf("ocTryLoad: initializers not implemented on this platform"); #endif - loading_obj = NULL; + foreignExportsFinishedLoadingObject(); if (!r) { return r; } ===================================== rts/LinkerInternals.h ===================================== @@ -135,17 +135,6 @@ typedef struct _Segment { int n_sections; } Segment; -/* - * We must keep track of the StablePtrs that are created for foreign - * exports by constructor functions when the module is loaded, so that - * we can free them again when the module is unloaded. If we don't do - * this, then the StablePtr will keep the module alive indefinitely. - */ -typedef struct ForeignExportStablePtr_ { - StgStablePtr stable_ptr; - struct ForeignExportStablePtr_ *next; -} ForeignExportStablePtr; - #if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif @@ -240,7 +229,8 @@ typedef struct _ObjectCode { char* bssBegin; char* bssEnd; - ForeignExportStablePtr *stable_ptrs; + /* a list of all ForeignExportsLists owned by this object */ + struct ForeignExportsList *foreign_exports; /* Holds the list of symbols in the .o file which require extra information.*/ ===================================== rts/RtsStartup.c ===================================== @@ -20,6 +20,7 @@ #include "STM.h" /* initSTM */ #include "RtsSignals.h" #include "Weak.h" +#include "ForeignExports.h" /* processForeignExports */ #include "Ticky.h" #include "StgRun.h" #include "Prelude.h" /* fixupRTStoPreludeRefs */ @@ -287,7 +288,13 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) getStablePtr((StgPtr)runHandlersPtr_closure); #endif - // Initialize the top-level handler system + /* + * process any foreign exports which were registered while loading the + * image + * */ + processForeignExports(); + + /* initialize the top-level handler system */ initTopHandler(); /* initialise the shared Typeable store */ ===================================== rts/RtsSymbols.c ===================================== @@ -643,7 +643,7 @@ SymI_HasProto(freeFullProgArgv) \ SymI_HasProto(getProcessElapsedTime) \ SymI_HasProto(getStablePtr) \ - SymI_HasProto(foreignExportStablePtr) \ + SymI_HasProto(registerForeignExports) \ SymI_HasProto(hs_init) \ SymI_HasProto(hs_init_with_rtsopts) \ SymI_HasProto(hs_init_ghc) \ ===================================== rts/rts.cabal.in ===================================== @@ -131,6 +131,7 @@ library rts/EventLogWriter.h rts/FileLock.h rts/Flags.h + rts/ForeignExports.h rts/GetTime.h rts/Globals.h rts/Hpc.h @@ -382,6 +383,7 @@ library ClosureFlags.c Disassembler.c FileLock.c + ForeignExports.c Globals.c Hash.c Heap.c View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/410b43a29576c40f4a65c9558f080a97c194636c...65be3832f3aa48bbde896ee846c18fcba1f16b42 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/410b43a29576c40f4a65c9558f080a97c194636c...65be3832f3aa48bbde896ee846c18fcba1f16b42 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 Nov 19 04:38:14 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 18 Nov 2020 23:38:14 -0500 Subject: [Git][ghc/ghc][master] Add Addr# atomic primops (#17751) Message-ID: <5fb5f6b656c9d_36a7f2b04941173eb@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 5 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/StgToCmm/Prim.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.stdout Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -1669,7 +1669,7 @@ primop FetchAddByteArrayOp_Int "fetchAddIntArray#" GenPrimOp primop FetchSubByteArrayOp_Int "fetchSubIntArray#" GenPrimOp MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) {Given an array, and offset in machine words, and a value to subtract, - atomically subtract the value to the element. Returns the value of + atomically subtract the value from the element. Returns the value of the element before the operation. Implies a full memory barrier.} with has_side_effects = True can_fail = True @@ -1677,7 +1677,7 @@ primop FetchSubByteArrayOp_Int "fetchSubIntArray#" GenPrimOp primop FetchAndByteArrayOp_Int "fetchAndIntArray#" GenPrimOp MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) {Given an array, and offset in machine words, and a value to AND, - atomically AND the value to the element. Returns the value of the + atomically AND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.} with has_side_effects = True can_fail = True @@ -1685,7 +1685,7 @@ primop FetchAndByteArrayOp_Int "fetchAndIntArray#" GenPrimOp primop FetchNandByteArrayOp_Int "fetchNandIntArray#" GenPrimOp MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) {Given an array, and offset in machine words, and a value to NAND, - atomically NAND the value to the element. Returns the value of the + atomically NAND the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.} with has_side_effects = True can_fail = True @@ -1693,7 +1693,7 @@ primop FetchNandByteArrayOp_Int "fetchNandIntArray#" GenPrimOp primop FetchOrByteArrayOp_Int "fetchOrIntArray#" GenPrimOp MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) {Given an array, and offset in machine words, and a value to OR, - atomically OR the value to the element. Returns the value of the + atomically OR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.} with has_side_effects = True can_fail = True @@ -1701,7 +1701,7 @@ primop FetchOrByteArrayOp_Int "fetchOrIntArray#" GenPrimOp primop FetchXorByteArrayOp_Int "fetchXorIntArray#" GenPrimOp MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, Int# #) {Given an array, and offset in machine words, and a value to XOR, - atomically XOR the value to the element. Returns the value of the + atomically XOR the value into the element. Returns the value of the element before the operation. Implies a full memory barrier.} with has_side_effects = True can_fail = True @@ -2121,6 +2121,67 @@ primop CasAddrOp_Word "atomicCasWordAddr#" GenPrimOp with has_side_effects = True can_fail = True +primop FetchAddAddrOp_Word "fetchAddWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) + {Given an address, and a value to add, + atomically add the value to the element. Returns the value of the + element before the operation. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop FetchSubAddrOp_Word "fetchSubWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) + {Given an address, and a value to subtract, + atomically subtract the value from the element. Returns the value of + the element before the operation. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop FetchAndAddrOp_Word "fetchAndWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) + {Given an address, and a value to AND, + atomically AND the value into the element. Returns the value of the + element before the operation. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop FetchNandAddrOp_Word "fetchNandWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) + {Given an address, and a value to NAND, + atomically NAND the value into the element. Returns the value of the + element before the operation. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop FetchOrAddrOp_Word "fetchOrWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) + {Given an address, and a value to OR, + atomically OR the value into the element. Returns the value of the + element before the operation. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop FetchXorAddrOp_Word "fetchXorWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> (# State# s, Word# #) + {Given an address, and a value to XOR, + atomically XOR the value into the element. Returns the value of the + element before the operation. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop AtomicReadAddrOp_Word "atomicReadWordAddr#" GenPrimOp + Addr# -> State# s -> (# State# s, Word# #) + {Given an address, read a machine word. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + +primop AtomicWriteAddrOp_Word "atomicWriteWordAddr#" GenPrimOp + Addr# -> Word# -> State# s -> State# s + {Given an address, write a machine word. Implies a full memory barrier.} + with has_side_effects = True + can_fail = True + + ------------------------------------------------------------------------ section "Mutable variables" {Operations on MutVar\#s.} ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -2121,12 +2121,12 @@ genCCall is32Bit (PrimTarget (MO_AtomicRMW width amop)) -- final move should go away, because it's the last use of arg -- and the first use of dst_r. AMO_Add -> return $ (toOL [ LOCK (XADD format (OpReg arg) (OpAddr amode)) - , MOV format (OpReg arg) (OpReg dst_r) - ], bid) + , MOV format (OpReg arg) (OpReg dst_r) + ], bid) AMO_Sub -> return $ (toOL [ NEGI format (OpReg arg) - , LOCK (XADD format (OpReg arg) (OpAddr amode)) - , MOV format (OpReg arg) (OpReg dst_r) - ], bid) + , LOCK (XADD format (OpReg arg) (OpAddr amode)) + , MOV format (OpReg arg) (OpReg dst_r) + ], bid) -- In these cases we need a new block id, and have to return it so -- that later instruction selection can reference it. AMO_And -> cmpxchg_code (\ src dst -> unitOL $ AND format src dst) ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -850,6 +850,25 @@ emitPrimOp dflags primop = case primop of emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] InterlockedExchange_Word -> \[src, value] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] + + FetchAddAddrOp_Word -> \[addr, n] -> opIntoRegs $ \[res] -> + doAtomicAddrRMW res AMO_Add addr (bWord platform) n + FetchSubAddrOp_Word -> \[addr, n] -> opIntoRegs $ \[res] -> + doAtomicAddrRMW res AMO_Sub addr (bWord platform) n + FetchAndAddrOp_Word -> \[addr, n] -> opIntoRegs $ \[res] -> + doAtomicAddrRMW res AMO_And addr (bWord platform) n + FetchNandAddrOp_Word -> \[addr, n] -> opIntoRegs $ \[res] -> + doAtomicAddrRMW res AMO_Nand addr (bWord platform) n + FetchOrAddrOp_Word -> \[addr, n] -> opIntoRegs $ \[res] -> + doAtomicAddrRMW res AMO_Or addr (bWord platform) n + FetchXorAddrOp_Word -> \[addr, n] -> opIntoRegs $ \[res] -> + doAtomicAddrRMW res AMO_Xor addr (bWord platform) n + + AtomicReadAddrOp_Word -> \[addr] -> opIntoRegs $ \[res] -> + doAtomicReadAddr res addr (bWord platform) + AtomicWriteAddrOp_Word -> \[addr, val] -> opIntoRegs $ \[] -> + doAtomicWriteAddr addr (bWord platform) val + CasAddrOp_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] CasAddrOp_Word -> \[dst, expected, new] -> opIntoRegs $ \[res] -> @@ -1040,17 +1059,17 @@ emitPrimOp dflags primop = case primop of -- Atomic read-modify-write FetchAddByteArrayOp_Int -> \[mba, ix, n] -> opIntoRegs $ \[res] -> - doAtomicRMW res AMO_Add mba ix (bWord platform) n + doAtomicByteArrayRMW res AMO_Add mba ix (bWord platform) n FetchSubByteArrayOp_Int -> \[mba, ix, n] -> opIntoRegs $ \[res] -> - doAtomicRMW res AMO_Sub mba ix (bWord platform) n + doAtomicByteArrayRMW res AMO_Sub mba ix (bWord platform) n FetchAndByteArrayOp_Int -> \[mba, ix, n] -> opIntoRegs $ \[res] -> - doAtomicRMW res AMO_And mba ix (bWord platform) n + doAtomicByteArrayRMW res AMO_And mba ix (bWord platform) n FetchNandByteArrayOp_Int -> \[mba, ix, n] -> opIntoRegs $ \[res] -> - doAtomicRMW res AMO_Nand mba ix (bWord platform) n + doAtomicByteArrayRMW res AMO_Nand mba ix (bWord platform) n FetchOrByteArrayOp_Int -> \[mba, ix, n] -> opIntoRegs $ \[res] -> - doAtomicRMW res AMO_Or mba ix (bWord platform) n + doAtomicByteArrayRMW res AMO_Or mba ix (bWord platform) n FetchXorByteArrayOp_Int -> \[mba, ix, n] -> opIntoRegs $ \[res] -> - doAtomicRMW res AMO_Xor mba ix (bWord platform) n + doAtomicByteArrayRMW res AMO_Xor mba ix (bWord platform) n AtomicReadByteArrayOp_Int -> \[mba, ix] -> opIntoRegs $ \[res] -> doAtomicReadByteArray res mba ix (bWord platform) AtomicWriteByteArrayOp_Int -> \[mba, ix, val] -> opIntoRegs $ \[] -> @@ -2855,22 +2874,33 @@ doWriteSmallPtrArrayOp addr idx val = do -- | Emit an atomic modification to a byte array element. The result -- reg contains that previous value of the element. Implies a full -- memory barrier. -doAtomicRMW :: LocalReg -- ^ Result reg +doAtomicByteArrayRMW + :: LocalReg -- ^ Result reg -> AtomicMachOp -- ^ Atomic op (e.g. add) -> CmmExpr -- ^ MutableByteArray# -> CmmExpr -- ^ Index -> CmmType -- ^ Type of element by which we are indexing -> CmmExpr -- ^ Op argument (e.g. amount to add) -> FCode () -doAtomicRMW res amop mba idx idx_ty n = do +doAtomicByteArrayRMW res amop mba idx idx_ty n = do profile <- getProfile platform <- getPlatform let width = typeWidth idx_ty addr = cmmIndexOffExpr platform (arrWordsHdrSize profile) width mba idx + doAtomicAddrRMW res amop addr idx_ty n + +doAtomicAddrRMW + :: LocalReg -- ^ Result reg + -> AtomicMachOp -- ^ Atomic op (e.g. add) + -> CmmExpr -- ^ Addr# + -> CmmType -- ^ Pointed value type + -> CmmExpr -- ^ Op argument (e.g. amount to add) + -> FCode () +doAtomicAddrRMW res amop addr ty n = do emitPrimCall [ res ] - (MO_AtomicRMW width amop) + (MO_AtomicRMW (typeWidth ty) amop) [ addr, n ] -- | Emit an atomic read to a byte array that acts as a memory barrier. @@ -2886,9 +2916,18 @@ doAtomicReadByteArray res mba idx idx_ty = do let width = typeWidth idx_ty addr = cmmIndexOffExpr platform (arrWordsHdrSize profile) width mba idx + doAtomicReadAddr res addr idx_ty + +-- | Emit an atomic read to an address that acts as a memory barrier. +doAtomicReadAddr + :: LocalReg -- ^ Result reg + -> CmmExpr -- ^ Addr# + -> CmmType -- ^ Type of element by which we are indexing + -> FCode () +doAtomicReadAddr res addr ty = do emitPrimCall [ res ] - (MO_AtomicRead width) + (MO_AtomicRead (typeWidth ty)) [ addr ] -- | Emit an atomic write to a byte array that acts as a memory barrier. @@ -2904,9 +2943,18 @@ doAtomicWriteByteArray mba idx idx_ty val = do let width = typeWidth idx_ty addr = cmmIndexOffExpr platform (arrWordsHdrSize profile) width mba idx + doAtomicWriteAddr addr idx_ty val + +-- | Emit an atomic write to an address that acts as a memory barrier. +doAtomicWriteAddr + :: CmmExpr -- ^ Addr# + -> CmmType -- ^ Type of element by which we are indexing + -> CmmExpr -- ^ Value to write + -> FCode () +doAtomicWriteAddr addr ty val = do emitPrimCall [ {- no results -} ] - (MO_AtomicWrite width) + (MO_AtomicWrite (typeWidth ty)) [ addr, val ] doCasByteArray ===================================== testsuite/tests/concurrent/should_run/AtomicPrimops.hs ===================================== @@ -13,61 +13,49 @@ import GHC.Exts import GHC.IO -- | Iterations per worker. -iters :: Int +iters :: Word iters = 1000000 main :: IO () main = do + -- ByteArray# fetchAddSubTest fetchAndTest fetchNandTest fetchOrTest fetchXorTest casTest - casTestAddr readWriteTest - --- | Test fetchAddIntArray# by having two threads concurrenctly + -- Addr# + fetchAddSubAddrTest + fetchAndAddrTest + fetchNandAddrTest + fetchOrAddrTest + fetchXorAddrTest + casAddrTest + readWriteAddrTest + +loop :: Word -> IO () -> IO () +loop 0 act = return () +loop n act = act >> loop (n-1) act + +-- | Test fetchAddIntArray# by having two threads concurrently -- increment a counter and then checking the sum at the end. fetchAddSubTest :: IO () fetchAddSubTest = do tot <- race 0 - (\ mba -> work fetchAddIntArray mba iters 2) - (\ mba -> work fetchSubIntArray mba iters 1) + (\ mba -> loop iters $ fetchAddIntArray mba 0 2) + (\ mba -> loop iters $ fetchSubIntArray mba 0 1) assertEq 1000000 tot "fetchAddSubTest" - where - work :: (MByteArray -> Int -> Int -> IO ()) -> MByteArray -> Int -> Int - -> IO () - work op mba 0 val = return () - work op mba n val = op mba 0 val >> work op mba (n-1) val --- | Test fetchXorIntArray# by having two threads concurrenctly XORing --- and then checking the result at the end. Works since XOR is --- commutative. --- --- Covers the code paths for AND, NAND, and OR as well. -fetchXorTest :: IO () -fetchXorTest = do - res <- race n0 - (\ mba -> work mba iters t1pat) - (\ mba -> work mba iters t2pat) - assertEq expected res "fetchXorTest" - where - work :: MByteArray -> Int -> Int -> IO () - work mba 0 val = return () - work mba n val = fetchXorIntArray mba 0 val >> work mba (n-1) val - - -- The two patterns are 1010... and 0101... The second pattern is larger - -- than maxBound, avoid warnings by initialising as a Word. - (n0, t1pat, t2pat) - | sizeOf (undefined :: Int) == 8 = - ( 0x00000000ffffffff, 0x5555555555555555 - , fromIntegral (0x9999999999999999 :: Word)) - | otherwise = ( 0x0000ffff, 0x55555555 - , fromIntegral (0x99999999 :: Word)) - expected - | sizeOf (undefined :: Int) == 8 = 4294967295 - | otherwise = 65535 +-- | Test fetchAddWordAddr# by having two threads concurrently +-- increment a counter and then checking the sum at the end. +fetchAddSubAddrTest :: IO () +fetchAddSubAddrTest = do + tot <- raceAddr 0 + (\ addr -> loop iters $ fetchAddWordPtr addr 2) + (\ addr -> loop iters $ fetchSubWordPtr addr 1) + assertEq 1000000 tot "fetchAddSubAddrTest" -- The tests for AND, NAND, and OR are trivial for two reasons: -- @@ -81,71 +69,132 @@ fetchXorTest = do -- Right now we only test that they return the correct value for a -- single op on each thread. --- | Test an associative operation. -fetchOpTest :: (MByteArray -> Int -> Int -> IO ()) - -> Int -> String -> IO () -fetchOpTest op expected name = do - res <- race n0 - (\ mba -> work mba t1pat) - (\ mba -> work mba t2pat) - assertEq expected res name - where - work :: MByteArray -> Int -> IO () - work mba val = op mba 0 val - -- | Initial value and operation arguments for race test. -- -- The two patterns are 1010... and 0101... The second pattern is larger than -- maxBound, avoid warnings by initialising as a Word. -n0, t1pat, t2pat :: Int +n0, t1pat, t2pat :: Word (n0, t1pat, t2pat) - | sizeOf (undefined :: Int) == 8 = - ( 0x00000000ffffffff, 0x5555555555555555 - , fromIntegral (0x9999999999999999 :: Word)) - | otherwise = ( 0x0000ffff, 0x55555555 - , fromIntegral (0x99999999 :: Word)) + | sizeOf (undefined :: Word) == 8 + = (0x00000000ffffffff, 0x5555555555555555, 0x9999999999999999) + | otherwise + = (0x0000ffff, 0x55555555, 0x99999999) + +-- | Test an associative operation. +fetchOpTest :: (MByteArray -> Int -> Int -> IO ()) + -> Int -> String -> IO () +fetchOpTest op expected name = do + res <- race (fromIntegral n0) + (\ mba -> op mba 0 (fromIntegral t1pat)) + (\ mba -> op mba 0 (fromIntegral t2pat)) + assertEq expected res name fetchAndTest :: IO () fetchAndTest = fetchOpTest fetchAndIntArray expected "fetchAndTest" where expected - | sizeOf (undefined :: Int) == 8 = 286331153 + | sizeOf (undefined :: Word) == 8 = 286331153 | otherwise = 4369 +fetchOrTest :: IO () +fetchOrTest = fetchOpTest fetchOrIntArray expected "fetchOrTest" + where expected + | sizeOf (undefined :: Word) == 8 + = fromIntegral (15987178197787607039 :: Word) + | otherwise + = fromIntegral (3722313727 :: Word) + -- | Test NAND without any race, as NAND isn't associative. fetchNandTest :: IO () fetchNandTest = do - mba <- newByteArray (sizeOf (undefined :: Int)) - writeIntArray mba 0 n0 - fetchNandIntArray mba 0 t1pat - fetchNandIntArray mba 0 t2pat + mba <- newByteArray (sizeOf (undefined :: Word)) + writeIntArray mba 0 (fromIntegral n0) + fetchNandIntArray mba 0 (fromIntegral t1pat) + fetchNandIntArray mba 0 (fromIntegral t2pat) res <- readIntArray mba 0 assertEq expected res "fetchNandTest" where expected - | sizeOf (undefined :: Int) == 8 = 7378697629770151799 + | sizeOf (undefined :: Word) == 8 = 7378697629770151799 | otherwise = -2576976009 -fetchOrTest :: IO () -fetchOrTest = fetchOpTest fetchOrIntArray expected "fetchOrTest" +-- | Test fetchXorIntArray# by having two threads concurrently XORing +-- and then checking the result at the end. Works since XOR is +-- commutative. +-- +-- Covers the code paths for AND, NAND, and OR as well. +fetchXorTest :: IO () +fetchXorTest = do + res <- race (fromIntegral n0) + (\mba -> loop iters $ fetchXorIntArray mba 0 (fromIntegral t1pat)) + (\mba -> loop iters $ fetchXorIntArray mba 0 (fromIntegral t2pat)) + assertEq expected res "fetchXorTest" + where + expected + | sizeOf (undefined :: Word) == 8 = 4294967295 + | otherwise = 65535 + + +-- | Test an associative operation. +fetchOpAddrTest :: (Ptr Word -> Word -> IO ()) -> Word -> String -> IO () +fetchOpAddrTest op expected name = do + res <- raceAddr n0 + (\ptr -> op ptr t1pat) + (\ptr -> op ptr t2pat) + assertEq expected res name + +fetchAndAddrTest :: IO () +fetchAndAddrTest = fetchOpAddrTest fetchAndWordPtr expected "fetchAndAddrTest" where expected - | sizeOf (undefined :: Int) == 8 - = fromIntegral (15987178197787607039 :: Word) + | sizeOf (undefined :: Word) == 8 = 286331153 + | otherwise = 4369 + +fetchOrAddrTest :: IO () +fetchOrAddrTest = fetchOpAddrTest fetchOrWordPtr expected "fetchOrAddrTest" + where expected + | sizeOf (undefined :: Word) == 8 + = 15987178197787607039 | otherwise - = fromIntegral (3722313727 :: Word) + = 3722313727 + + +-- | Test NAND without any race, as NAND isn't associative. +fetchNandAddrTest :: IO () +fetchNandAddrTest = do + ptr <- castPtr <$> callocBytes (sizeOf (undefined :: Word)) + poke ptr n0 + fetchNandWordPtr ptr t1pat + fetchNandWordPtr ptr t2pat + res <- peek ptr + assertEq expected res "fetchNandAddrTest" + where expected + | sizeOf (undefined :: Word) == 8 = 7378697629770151799 + | otherwise = -2576976009 + +-- | Test fetchXorIntArray# by having two threads concurrently XORing +-- and then checking the result at the end. Works since XOR is +-- commutative. +-- +-- Covers the code paths for AND, NAND, and OR as well. +fetchXorAddrTest :: IO () +fetchXorAddrTest = do + res <- raceAddr n0 + (\ptr -> loop iters $ fetchXorWordPtr ptr t1pat) + (\ptr -> loop iters $ fetchXorWordPtr ptr t2pat) + assertEq expected res "fetchXorAddrTest" + where + expected + | sizeOf (undefined :: Int) == 8 = 4294967295 + | otherwise = 65535 -- | Test casIntArray# by using it to emulate fetchAddIntArray# and --- then having two threads concurrenctly increment a counter, +-- then having two threads concurrently increment a counter, -- checking the sum at the end. casTest :: IO () casTest = do tot <- race 0 - (\ mba -> work mba iters 1) - (\ mba -> work mba iters 2) - assertEq (3 * iters) tot "casTest" + (\ mba -> loop iters $ add mba 0 1) + (\ mba -> loop iters $ add mba 0 2) + assertEq (3 * fromIntegral iters) tot "casTest" where - work :: MByteArray -> Int -> Int -> IO () - work mba 0 val = return () - work mba n val = add mba 0 val >> work mba (n-1) val - -- Fetch-and-add implemented using CAS. add :: MByteArray -> Int -> Int -> IO () add mba ix n = do @@ -153,6 +202,24 @@ casTest = do old' <- casIntArray mba ix old (old + n) when (old /= old') $ add mba ix n +-- | Test atomicCasWordAddr# by having two threads concurrently increment a +-- counter, checking the sum at the end. +casAddrTest :: IO () +casAddrTest = do + tot <- raceAddr 0 + (\ addr -> loop iters $ add addr 1) + (\ addr -> loop iters $ add addr 2) + assertEq (3 * iters) tot "casAddrTest" + where + -- Fetch-and-add implemented using CAS. + add :: Ptr Word -> Word -> IO () + add ptr n = peek ptr >>= go + where + go old = do + old' <- atomicCasWordPtr ptr old (old + n) + when (old /= old') $ go old' + + -- | Tests atomic reads and writes by making sure that one thread sees -- updates that are done on another. This test isn't very good at the -- moment, as this might work even without atomic ops, but at least it @@ -172,6 +239,21 @@ readWriteTest = do putMVar latch () takeMVar done +readWriteAddrTest :: IO () +readWriteAddrTest = do + ptr <- castPtr <$> callocBytes (sizeOf (undefined :: Word)) + poke ptr 0 + latch <- newEmptyMVar + done <- newEmptyMVar + forkIO $ do + takeMVar latch + n <- atomicReadWordPtr ptr + assertEq 1 n "readWriteAddrTest" + putMVar done () + atomicWriteWordPtr ptr 1 + putMVar latch () + takeMVar done + -- | Create two threads that mutate the byte array passed to them -- concurrently. The array is one word large. race :: Int -- ^ Initial value of array element @@ -188,44 +270,21 @@ race n0 thread1 thread2 = do mapM_ takeMVar [done1, done2] readIntArray mba 0 --- | Test atomicCasWordAddr# by having two threads concurrenctly increment a --- counter, checking the sum at the end. -casTestAddr :: IO () -casTestAddr = do - tot <- raceAddr 0 - (\ addr -> work addr (fromIntegral iters) 1) - (\ addr -> work addr (fromIntegral iters) 2) - assertEq (3 * fromIntegral iters) tot "casTestAddr" - where - work :: Ptr Word -> Word -> Word -> IO () - work ptr 0 val = return () - work ptr n val = add ptr val >> work ptr (n-1) val - - -- Fetch-and-add implemented using CAS. - add :: Ptr Word -> Word -> IO () - add ptr n = peek ptr >>= go - where - go old = do - old' <- atomicCasWordPtr ptr old (old + n) - when (old /= old') $ go old' - - -- | Create two threads that mutate the byte array passed to them - -- concurrently. The array is one word large. - raceAddr :: Word -- ^ Initial value of array element - -> (Ptr Word -> IO ()) -- ^ Thread 1 action - -> (Ptr Word -> IO ()) -- ^ Thread 2 action - -> IO Word -- ^ Final value of array element - raceAddr n0 thread1 thread2 = do - done1 <- newEmptyMVar - done2 <- newEmptyMVar - ptr <- asWordPtr <$> callocBytes (sizeOf (undefined :: Word)) - forkIO $ thread1 ptr >> putMVar done1 () - forkIO $ thread2 ptr >> putMVar done2 () - mapM_ takeMVar [done1, done2] - peek ptr - where - asWordPtr :: Ptr a -> Ptr Word - asWordPtr = castPtr +-- | Create two threads that mutate the byte array passed to them +-- concurrently. The array is one word large. +raceAddr :: Word -- ^ Initial value of array element + -> (Ptr Word -> IO ()) -- ^ Thread 1 action + -> (Ptr Word -> IO ()) -- ^ Thread 2 action + -> IO Word -- ^ Final value of array element +raceAddr n0 thread1 thread2 = do + done1 <- newEmptyMVar + done2 <- newEmptyMVar + ptr <- castPtr <$> callocBytes (sizeOf (undefined :: Word)) + poke ptr n0 + forkIO $ thread1 ptr >> putMVar done1 () + forkIO $ thread2 ptr >> putMVar done2 () + mapM_ takeMVar [done1, done2] + peek ptr ------------------------------------------------------------------------ -- Test helper @@ -306,6 +365,46 @@ casIntArray (MBA mba#) (I# ix#) (I# old#) (I# new#) = IO $ \ s# -> ------------------------------------------------------------------------ -- Wrappers around Addr# +fetchAddWordPtr :: Ptr Word -> Word -> IO () +fetchAddWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case fetchAddWordAddr# addr# n# s# of + (# s2#, _ #) -> (# s2#, () #) + +fetchSubWordPtr :: Ptr Word -> Word -> IO () +fetchSubWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case fetchSubWordAddr# addr# n# s# of + (# s2#, _ #) -> (# s2#, () #) + +fetchAndWordPtr :: Ptr Word -> Word -> IO () +fetchAndWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case fetchAndWordAddr# addr# n# s# of + (# s2#, _ #) -> (# s2#, () #) + +fetchOrWordPtr :: Ptr Word -> Word -> IO () +fetchOrWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case fetchOrWordAddr# addr# n# s# of + (# s2#, _ #) -> (# s2#, () #) + +fetchNandWordPtr :: Ptr Word -> Word -> IO () +fetchNandWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case fetchNandWordAddr# addr# n# s# of + (# s2#, _ #) -> (# s2#, () #) + +fetchXorWordPtr :: Ptr Word -> Word -> IO () +fetchXorWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case fetchXorWordAddr# addr# n# s# of + (# s2#, _ #) -> (# s2#, () #) + +atomicWriteWordPtr :: Ptr Word -> Word -> IO () +atomicWriteWordPtr (Ptr addr#) (W# n#) = IO $ \ s# -> + case atomicWriteWordAddr# addr# n# s# of + s2# -> (# s2#, () #) + +atomicReadWordPtr :: Ptr Word -> IO Word +atomicReadWordPtr (Ptr addr#) = IO $ \ s# -> + case atomicReadWordAddr# addr# s# of + (# s2#, n# #) -> (# s2#, W# n# #) + -- Should this be added to Foreign.Storable? Similar to poke, but does the -- update atomically. atomicCasWordPtr :: Ptr Word -> Word -> Word -> IO Word ===================================== testsuite/tests/concurrent/should_run/AtomicPrimops.stdout ===================================== @@ -4,5 +4,11 @@ fetchNandTest: OK fetchOrTest: OK fetchXorTest: OK casTest: OK -casTestAddr: OK readWriteTest: OK +fetchAddSubAddrTest: OK +fetchAndAddrTest: OK +fetchNandAddrTest: OK +fetchOrAddrTest: OK +fetchXorAddrTest: OK +casAddrTest: OK +readWriteAddrTest: OK View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/52114fa0f97805d4c4924bc3abce1a8b0fc7a5c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/52114fa0f97805d4c4924bc3abce1a8b0fc7a5c6 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 Nov 19 04:38:47 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 18 Nov 2020 23:38:47 -0500 Subject: [Git][ghc/ghc][master] PmCheck: Print types of uncovered patterns (#18932) Message-ID: <5fb5f6d777adc_36a7f2b09581212e3@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 30 changed files: - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr - testsuite/tests/deSugar/should_compile/GadtOverlap.stderr - testsuite/tests/deSugar/should_compile/T14135.stderr - testsuite/tests/deSugar/should_compile/T14546a.stderr - testsuite/tests/deSugar/should_compile/T14546d.stderr - testsuite/tests/deSugar/should_compile/T5455.stderr - testsuite/tests/dependent/should_compile/KindEqualities.stderr - testsuite/tests/driver/T8101.stderr - testsuite/tests/driver/T8101b.stderr - testsuite/tests/driver/werror.stderr - testsuite/tests/ghci/prog018/prog018.stdout - testsuite/tests/parser/should_compile/T15139.stderr - testsuite/tests/pmcheck/complete_sigs/T13964.stderr - testsuite/tests/pmcheck/complete_sigs/T14059a.stderr - testsuite/tests/pmcheck/complete_sigs/T17386.stderr - testsuite/tests/pmcheck/complete_sigs/completesig02.stderr - testsuite/tests/pmcheck/complete_sigs/completesig04.stderr - testsuite/tests/pmcheck/complete_sigs/completesig06.stderr - testsuite/tests/pmcheck/complete_sigs/completesig07.stderr - testsuite/tests/pmcheck/complete_sigs/completesig10.stderr - testsuite/tests/pmcheck/complete_sigs/completesig11.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase002.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase003.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase004.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase005.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase006.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase007.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8150f6546e6fd0006252e245d5697f13ffd8ce3e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8150f6546e6fd0006252e245d5697f13ffd8ce3e 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 Nov 19 05:10:00 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 19 Nov 2020 00:10:00 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: PmCheck: Print types of uncovered patterns (#18932) Message-ID: <5fb5fe285f6f_36a7f2b1358126987@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - b7983199 by Ben Gamari at 2020-11-19T00:09:33-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - df1333d7 by Ben Gamari at 2020-11-19T00:09:33-05:00 testsuite: Refactor CountParserDeps - - - - - b5da7539 by Ben Gamari at 2020-11-19T00:09:33-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - df139c62 by Krzysztof Gogolewski at 2020-11-19T00:09:40-05:00 Export indexError from GHC.Ix (#18579) - - - - - 07824cbe by Sylvain Henry at 2020-11-19T00:09:42-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 75f9f03a by Sylvain Henry at 2020-11-19T00:09:42-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - 03b4c107 by Greg Steuck at 2020-11-19T00:09:45-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 45244ac3 by Ben Gamari at 2020-11-19T00:09:46-05:00 gitlab-ci: Add usage message to ci.sh - - - - - ded01ab9 by Ben Gamari at 2020-11-19T00:09:46-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/extending_ghc.rst - docs/users_guide/profiling.rst The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e4a82ad18c8b00d7f49660246ea8f69339a9db94...ded01ab9bb90d712a8825ad0c25937963d475272 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e4a82ad18c8b00d7f49660246ea8f69339a9db94...ded01ab9bb90d712a8825ad0c25937963d475272 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 Nov 19 08:56:31 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Thu, 19 Nov 2020 03:56:31 -0500 Subject: [Git][ghc/ghc][wip/con-info] Make cgs_used_info strict Message-ID: <5fb6333f2306d_36a7f2b113c1355c0@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 54eb5bbe by Matthew Pickering at 2020-11-19T08:56:18+00:00 Make cgs_used_info strict - - - - - 1 changed file: - compiler/GHC/StgToCmm/Monad.hs Changes: ===================================== compiler/GHC/StgToCmm/Monad.hs ===================================== @@ -316,7 +316,7 @@ data CgState cgs_uniqs :: UniqSupply, -- | These are IDs which have an info table - cgs_used_info :: [CmmInfoTable] + cgs_used_info :: ![CmmInfoTable] } data HeapUsage -- See Note [Virtual and real heap pointers] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54eb5bbe383d3c4c22661fd789185441c9136d22 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/54eb5bbe383d3c4c22661fd789185441c9136d22 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 Nov 19 09:57:32 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Thu, 19 Nov 2020 04:57:32 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] 3 commits: Add Addr# atomic primops (#17751) Message-ID: <5fb6418cc32c8_36a7f2b0ee41414b1@gitlab.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 8a96ae3c by Daniel Rogozin at 2020-11-19T12:57:10+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Instance/Class.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Utils/Binary.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c675efff7e9ee02b4913b65adf8ab36145b4e8a1...8a96ae3c460fa4235b322f7715c93118f668e3db -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c675efff7e9ee02b4913b65adf8ab36145b4e8a1...8a96ae3c460fa4235b322f7715c93118f668e3db 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 Nov 19 11:12:05 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Thu, 19 Nov 2020 06:12:05 -0500 Subject: [Git][ghc/ghc][wip/T18914] 3 commits: Add Addr# atomic primops (#17751) Message-ID: <5fb6530584258_36a7f2b113c14879f@gitlab.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 6d08443b by Ryan Scott at 2020-11-19T06:12:01-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). I also made `HsCoreTy` a type synonym instead of a newtype, as making it a distinct data type wasn't buying us much. * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.stdout - testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr - testsuite/tests/deSugar/should_compile/GadtOverlap.stderr - testsuite/tests/deSugar/should_compile/T14135.stderr - testsuite/tests/deSugar/should_compile/T14546a.stderr - testsuite/tests/deSugar/should_compile/T14546d.stderr - testsuite/tests/deSugar/should_compile/T5455.stderr - testsuite/tests/dependent/should_compile/KindEqualities.stderr - testsuite/tests/deriving/should_compile/T14578.stderr - + testsuite/tests/deriving/should_compile/T18914.hs - testsuite/tests/deriving/should_compile/all.T - testsuite/tests/driver/T8101.stderr - testsuite/tests/driver/T8101b.stderr - testsuite/tests/driver/werror.stderr - testsuite/tests/ghci/prog018/prog018.stdout - testsuite/tests/parser/should_compile/T15139.stderr - testsuite/tests/pmcheck/complete_sigs/T13964.stderr - testsuite/tests/pmcheck/complete_sigs/T14059a.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3ad23abd9f554df383eef9cd293505911b58ac2...6d08443b3dd6a5343b6485f19a68eae158594446 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e3ad23abd9f554df383eef9cd293505911b58ac2...6d08443b3dd6a5343b6485f19a68eae158594446 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 Nov 19 12:55:07 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Thu, 19 Nov 2020 07:55:07 -0500 Subject: [Git][ghc/ghc][wip/refactor-demand] 2 commits: Demand: Interleave usage and strictness demands (#18903) Message-ID: <5fb66b2b5ff11_36a7f2b0c641521d9@gitlab.mail> Sebastian Graf pushed to branch wip/refactor-demand at Glasgow Haskell Compiler / GHC Commits: 07723a60 by Sebastian Graf at 2020-11-19T13:48:17+01:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - fd1fa0fa by Sebastian Graf at 2020-11-19T13:53:49+01:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0195df964354808e4c8574d518f21f35fef0033e...fd1fa0fa20f6b431ef1f0fd8d48313632385dcfb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0195df964354808e4c8574d518f21f35fef0033e...fd1fa0fa20f6b431ef1f0fd8d48313632385dcfb 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 Nov 19 15:07:11 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 10:07:11 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/ghc-8.10-backports Message-ID: <5fb68a1f489b2_36a7f2b032c176049@gitlab.mail> Ben Gamari deleted branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC -- 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 Nov 19 15:07:14 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 10:07:14 -0500 Subject: [Git][ghc/ghc][ghc-8.10] 5 commits: testsuite: Add test for #18346 Message-ID: <5fb68a22ee168_36a7f2b049417628c@gitlab.mail> Ben Gamari pushed to branch ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: f96d6cd7 by Ben Gamari at 2020-11-14T06:47:14-05:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. (cherry picked from commit ee5dcdf95a7c408e9c339aacebf89a007a735f8f) - - - - - 36c1027d by Ben Gamari at 2020-11-14T06:47:14-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. (cherry picked from commit 6d21ecee535782f01dba9947a49e282afee25724) - - - - - 410b43a2 by Andreas Klebinger at 2020-11-18T16:22:35-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) (cherry picked from commit fda3e50b559f6f25347f9ad7239e5003e27937b0) - - - - - ed57c3a9 by Ben Gamari at 2020-11-18T21:39:41-05:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. (cherry picked from commit c492134912e5270180881b7345ee86dc32756bdd) - - - - - 65be3832 by Ben Gamari at 2020-11-18T21:39:53-05:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. (cherry picked from commit 40dc91069d15bfc1d81f1722b39e06cac8fdddd1) - - - - - 20 changed files: - compiler/deSugar/DsForeign.hs - compiler/nativeGen/X86/CodeGen.hs - compiler/nativeGen/X86/Cond.hs - includes/Rts.h - + includes/rts/ForeignExports.h - + rts/ForeignExports.c - + rts/ForeignExports.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/RtsSymbols.c - rts/linker/PEi386.c - rts/rts.cabal.in - testsuite/tests/cmm/should_run/all.T - + testsuite/tests/cmm/should_run/cmp64.hs - + testsuite/tests/cmm/should_run/cmp64.stdout - + testsuite/tests/cmm/should_run/cmp64_cmm.cmm - + testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs - + testsuite/tests/simplCore/should_compile/T18346/T18346.hs - + testsuite/tests/simplCore/should_compile/T18346/all.T Changes: ===================================== compiler/deSugar/DsForeign.hs ===================================== @@ -86,15 +86,16 @@ dsForeigns' :: [LForeignDecl GhcTc] dsForeigns' [] = return (NoStubs, nilOL) dsForeigns' fos = do + mod <- getModule fives <- mapM do_ldecl fos let (hs, cs, idss, bindss) = unzip4 fives fe_ids = concat idss - fe_init_code = map foreignExportInitialiser fe_ids + fe_init_code = foreignExportsInitialiser mod fe_ids -- return (ForeignStubs (vcat hs) - (vcat cs $$ vcat fe_init_code), + (vcat cs $$ fe_init_code), foldr (appOL . toOL) nilOL bindss) where do_ldecl (dL->L loc decl) = putSrcSpanDs loc (do_decl decl) @@ -667,8 +668,8 @@ mkFExportCBits dflags c_nm maybe_target arg_htys res_hty is_IO_res_ty cc ] -foreignExportInitialiser :: Id -> SDoc -foreignExportInitialiser hs_fn = +foreignExportsInitialiser :: Module -> [Id] -> SDoc +foreignExportsInitialiser mod hs_fns = -- Initialise foreign exports by registering a stable pointer from an -- __attribute__((constructor)) function. -- The alternative is to do this from stginit functions generated in @@ -677,14 +678,24 @@ foreignExportInitialiser hs_fn = -- all modules that are imported directly or indirectly are actually used by -- the program. -- (this is bad for big umbrella modules like Graphics.Rendering.OpenGL) + -- + -- See Note [Tracking foreign exports] in rts/ForeignExports.c vcat - [ text "static void stginit_export_" <> ppr hs_fn - <> text "() __attribute__((constructor));" - , text "static void stginit_export_" <> ppr hs_fn <> text "()" - , braces (text "foreignExportStablePtr" - <> parens (text "(StgPtr) &" <> ppr hs_fn <> text "_closure") - <> semi) + [ text "static struct ForeignExportsList" <+> list_symbol <+> equals + <+> braces (text ".exports = " <+> export_list) <> semi + , text "static void " <> ctor_symbol <> text "(void)" + <+> text " __attribute__((constructor));" + , text "static void " <> ctor_symbol <> text "()" + , braces (text "registerForeignExports" <> parens (char '&' <> list_symbol) <> semi) ] + where + mod_str = pprModuleName (moduleName mod) + ctor_symbol = text "stginit_export_" <> mod_str + list_symbol = text "stg_exports_" <> mod_str + export_list = braces $ pprWithCommas closure_ptr hs_fns + + closure_ptr :: Id -> SDoc + closure_ptr fn = text "(StgPtr) &" <> ppr fn <> text "_closure" mkHObj :: Type -> SDoc ===================================== compiler/nativeGen/X86/CodeGen.hs ===================================== @@ -1804,6 +1804,35 @@ I386: First, we have to ensure that the condition codes are set according to the supplied comparison operation. -} +{- Note [64-bit integer comparisons on 32-bit] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + + When doing these comparisons there are 2 kinds of + comparisons. + + * Comparison for equality (or lack thereof) + + We use xor to check if high/low bits are + equal. Then combine the results using or and + perform a single conditional jump based on the + result. + + * Other comparisons: + + We map all other comparisons to the >= operation. + Why? Because it's easy to encode it with a single + conditional jump. + + We do this by first computing [r1_lo - r2_lo] + and use the carry flag to compute + [r1_high - r2_high - CF]. + + At which point if r1 >= r2 then the result will be + positive. Otherwise negative so we can branch on this + condition. + +-} + genCondBranch :: BlockId -- the source of the jump @@ -1821,22 +1850,63 @@ genCondBranch' :: Bool -> BlockId -> BlockId -> BlockId -> CmmExpr -> NatM InstrBlock -- 64-bit integer comparisons on 32-bit +-- See Note [64-bit integer comparisons on 32-bit] genCondBranch' is32Bit _bid true false (CmmMachOp mop [e1,e2]) | is32Bit, Just W64 <- maybeIntComparison mop = do - ChildCode64 code1 r1_lo <- iselExpr64 e1 - ChildCode64 code2 r2_lo <- iselExpr64 e2 - let r1_hi = getHiVRegFromLo r1_lo - r2_hi = getHiVRegFromLo r2_lo - cond = machOpToCond mop - Just cond' = maybeFlipCond cond - --TODO: Update CFG for x86 - let code = code1 `appOL` code2 `appOL` toOL [ - CMP II32 (OpReg r2_hi) (OpReg r1_hi), - JXX cond true, - JXX cond' false, - CMP II32 (OpReg r2_lo) (OpReg r1_lo), - JXX cond true] `appOL` genBranch false - return code + + -- The resulting registers here are both the lower part of + -- the register as well as a way to get at the higher part. + ChildCode64 code1 r1 <- iselExpr64 e1 + ChildCode64 code2 r2 <- iselExpr64 e2 + let cond = machOpToCond mop :: Cond + + let cmpCode = intComparison cond true false r1 r2 + return $ code1 `appOL` code2 `appOL` cmpCode + + where + intComparison :: Cond -> BlockId -> BlockId -> Reg -> Reg -> InstrBlock + intComparison cond true false r1_lo r2_lo = + case cond of + -- Impossible results of machOpToCond + ALWAYS -> panic "impossible" + NEG -> panic "impossible" + POS -> panic "impossible" + CARRY -> panic "impossible" + OFLO -> panic "impossible" + PARITY -> panic "impossible" + NOTPARITY -> panic "impossible" + -- Special case #1 x == y and x != y + EQQ -> cmpExact + NE -> cmpExact + -- [x >= y] + GE -> cmpGE + GEU -> cmpGE + -- [x > y] <==> ![y >= x] + GTT -> intComparison GE false true r2_lo r1_lo + GU -> intComparison GEU false true r2_lo r1_lo + -- [x <= y] <==> [y >= x] + LE -> intComparison GE true false r2_lo r1_lo + LEU -> intComparison GEU true false r2_lo r1_lo + -- [x < y] <==> ![x >= x] + LTT -> intComparison GE false true r1_lo r2_lo + LU -> intComparison GEU false true r1_lo r2_lo + where + r1_hi = getHiVRegFromLo r1_lo + r2_hi = getHiVRegFromLo r2_lo + cmpExact :: OrdList Instr + cmpExact = + toOL + [ XOR II32 (OpReg r2_hi) (OpReg r1_hi) + , XOR II32 (OpReg r2_lo) (OpReg r1_lo) + , OR II32 (OpReg r1_hi) (OpReg r1_lo) + , JXX cond true + , JXX ALWAYS false + ] + cmpGE = toOL + [ CMP II32 (OpReg r2_lo) (OpReg r1_lo) + , SBB II32 (OpReg r2_hi) (OpReg r1_hi) + , JXX cond true + , JXX ALWAYS false ] genCondBranch' _ bid id false bool = do CondCode is_float cond cond_code <- getCondCode bool ===================================== compiler/nativeGen/X86/Cond.hs ===================================== @@ -13,22 +13,22 @@ import GhcPrelude data Cond = ALWAYS -- What's really used? ToDo - | EQQ - | GE - | GEU - | GTT - | GU - | LE - | LEU - | LTT - | LU - | NE - | NEG - | POS - | CARRY - | OFLO - | PARITY - | NOTPARITY + | EQQ -- je/jz -> zf = 1 + | GE -- jge + | GEU -- ae + | GTT -- jg + | GU -- ja + | LE -- jle + | LEU -- jbe + | LTT -- jl + | LU -- jb + | NE -- jne + | NEG -- js + | POS -- jns + | CARRY -- jc + | OFLO -- jo + | PARITY -- jp + | NOTPARITY -- jnp deriving Eq condUnsigned :: Cond -> Bool ===================================== includes/Rts.h ===================================== @@ -209,6 +209,9 @@ void _assertFail(const char *filename, unsigned int linenum) #include "rts/storage/GC.h" #include "rts/NonMoving.h" +/* Foreign exports */ +#include "rts/ForeignExports.h" + /* Other RTS external APIs */ #include "rts/Parallel.h" #include "rts/Signals.h" ===================================== includes/rts/ForeignExports.h ===================================== @@ -0,0 +1,38 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team, 1995-2009 + * + * Interface to the RTS's foreign export tracking code. + * + * Do not #include this file directly: #include "Rts.h" instead. + * + * To understand the structure of the RTS headers, see the wiki: + * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/source-tree/includes + * + * ---------------------------------------------------------------------------*/ + +#pragma once + +struct _ObjectCode; + +/* N.B. See Note [Tracking foreign exports] in + * rts/ForeignExports.c. */ +struct ForeignExportsList { + /* a link field for linking these together into lists. + */ + struct ForeignExportsList *next; + /* the length of ->exports */ + int n_entries; + /* if the RTS linker loaded the module, + * to which ObjectCode these exports belong. */ + struct _ObjectCode *oc; + /* if the RTS linker loaded the module, + * this points to an array of length ->n_entries + * recording the StablePtr for each export. */ + StgStablePtr **stable_ptrs; + /* the exported closures. of length ->exports. */ + StgPtr exports[]; +}; + +void registerForeignExports(struct ForeignExportsList *exports); + ===================================== rts/ForeignExports.c ===================================== @@ -0,0 +1,130 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team 2020 + * + * Management of foreign exports. + * + * ---------------------------------------------------------------------------*/ + +#include "Rts.h" +#include "RtsUtils.h" +#include "ForeignExports.h" + +/* protected by linker_mutex after start-up */ +static struct ForeignExportsList *pending = NULL; +static ObjectCode *loading_obj = NULL; + +/* + * Note [Tracking foreign exports] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * Foreign exports are garbage collection roots. That is, things (e.g. CAFs) + * depended upon by a module's `foreign export`s need to be kept alive for as + * long an module is loaded. To ensure this we create a stable pointer to each + * `foreign export`'d closure. This works as follows: + * + * 1. The compiler (namely GHC.HsToCore.Foreign.Decl.foreignExports) + * inserts a C-stub into each module containing a `foreign export`. This + * stub contains two things: + * + * - A `ForeignExportsList` listing all of the exported closures, and + * + * - An initializer which calls `registerForeignExports` with a reference to + * the `ForeignExportsList`. + * + * 2. When the module's object code is loaded, its initializer is called by the + * linker (this might be the system's dynamic linker or GHC's own static + * linker). `registerForeignExports` then places the module's + * `ForeignExportsList` on `pending` list. + * + * 3. When loading has finished (e.g. during RTS initialization or at the end + * of `Linker.c:ocTryLoad`) `processForeignExports` is called. Here we + * traverse the `pending` list and create a `StablePtr` for each export + * therein. + * + * The reason for this two-step process is that we are very restricted in what + * we can do in an initializer function. For instance, we cannot necessarily + * call `malloc` since the `libc`'s own initializer may not have run yet. + * For instance, doing exactly this resulted in #18548. + * + * Another consideration here is that the linker needs to know which + * `StablePtr`s belong to each `ObjectCode` so it can free them when the module is + * unloaded. For this reason, the linker informs us when it is loading an + * object by calling `foreignExportsLoadingObject` and + * `foreignExportsFinishedLoadingObject`. We take note of the `ObjectCode*` we + * are loading in `loading_obj` such that we can associate the `ForeignExportsList` with + * the `ObjectCode` in `processForeignExports`. We then record each of the + * StablePtrs we create in the ->stable_ptrs array of ForeignExportsList so + * they can be enumerated during unloading. + * + */ + +void registerForeignExports(struct ForeignExportsList *exports) +{ + ASSERT(exports->next == NULL); + ASSERT(exports->oc == NULL); + exports->next = pending; + exports->oc = loading_obj; + pending = exports; +} + +/* ----------------------------------------------------------------------------- + Create a StablePtr for a foreign export. This is normally called by + a C function with __attribute__((constructor)), which is generated + by GHC and linked into the module. + + If the object code is being loaded dynamically, then we remember + which StablePtrs were allocated by the constructors and free them + again in unloadObj(). + -------------------------------------------------------------------------- */ + +void foreignExportsLoadingObject(ObjectCode *oc) +{ + ASSERT(loading_obj == NULL); + loading_obj = oc; +} + +void foreignExportsFinishedLoadingObject() +{ + ASSERT(loading_obj != NULL); + loading_obj = NULL; + processForeignExports(); +} + +/* Caller must own linker_mutex so that we can safely modify + * oc->stable_ptrs. */ +void processForeignExports() +{ + while (pending) { + struct ForeignExportsList *cur = pending; + pending = cur->next; + + /* sanity check */ + ASSERT(cur->stable_ptrs == NULL); + + /* N.B. We only need to populate the ->stable_ptrs + * array if the object might later be unloaded. + */ + if (cur->oc != NULL) { + cur->stable_ptrs = + stgMallocBytes(sizeof(StgStablePtr*) * cur->n_entries, + "foreignExportStablePtr"); + + for (int i=0; i < cur->n_entries; i++) { + StgStablePtr *sptr = getStablePtr(cur->exports[i]); + + if (cur->oc != NULL) { + cur->stable_ptrs[i] = sptr; + } + } + cur->next = cur->oc->foreign_exports; + cur->oc->foreign_exports = cur; + } else { + /* can't be unloaded, don't bother populating + * ->stable_ptrs array. */ + for (int i=0; i < cur->n_entries; i++) { + getStablePtr(cur->exports[i]); + } + } + } +} ===================================== rts/ForeignExports.h ===================================== @@ -0,0 +1,21 @@ +/* ----------------------------------------------------------------------------- + * + * (c) The GHC Team 2020 + * + * Management of foreign exports. + * + * ---------------------------------------------------------------------------*/ + +#pragma once + +#include "Rts.h" +#include "LinkerInternals.h" + +#include "BeginPrivate.h" + +void foreignExportsLoadingObject(ObjectCode *oc); +void foreignExportsFinishedLoadingObject(void); +void processForeignExports(void); + +#include "EndPrivate.h" + ===================================== rts/Linker.c ===================================== @@ -26,6 +26,7 @@ #include "RtsSymbols.h" #include "RtsSymbolInfo.h" #include "Profiling.h" +#include "ForeignExports.h" #include "sm/OSMem.h" #include "linker/M32Alloc.h" #include "linker/CacheFlush.h" @@ -951,37 +952,6 @@ SymbolAddr* lookupSymbol( SymbolName* lbl ) return r; } -/* ----------------------------------------------------------------------------- - Create a StablePtr for a foreign export. This is normally called by - a C function with __attribute__((constructor)), which is generated - by GHC and linked into the module. - - If the object code is being loaded dynamically, then we remember - which StablePtrs were allocated by the constructors and free them - again in unloadObj(). - -------------------------------------------------------------------------- */ - -static ObjectCode *loading_obj = NULL; - -StgStablePtr foreignExportStablePtr (StgPtr p) -{ - ForeignExportStablePtr *fe_sptr; - StgStablePtr *sptr; - - sptr = getStablePtr(p); - - if (loading_obj != NULL) { - fe_sptr = stgMallocBytes(sizeof(ForeignExportStablePtr), - "foreignExportStablePtr"); - fe_sptr->stable_ptr = sptr; - fe_sptr->next = loading_obj->stable_ptrs; - loading_obj->stable_ptrs = fe_sptr; - } - - return sptr; -} - - /* ----------------------------------------------------------------------------- * Debugging aid: look in GHCi's object symbol tables for symbols * within DELTA bytes of the specified address, and show their names. @@ -1252,14 +1222,18 @@ static void freeOcStablePtrs (ObjectCode *oc) { // Release any StablePtrs that were created when this // object module was initialized. - ForeignExportStablePtr *fe_ptr, *next; + struct ForeignExportsList *exports, *next; - for (fe_ptr = oc->stable_ptrs; fe_ptr != NULL; fe_ptr = next) { - next = fe_ptr->next; - freeStablePtr(fe_ptr->stable_ptr); - stgFree(fe_ptr); + for (exports = oc->foreign_exports; exports != NULL; exports = next) { + next = exports->next; + for (int i = 0; i < exports->n_entries; i++) { + freeStablePtr(exports->stable_ptrs[i]); + } + stgFree(exports->stable_ptrs); + exports->stable_ptrs = NULL; + exports->next = NULL; } - oc->stable_ptrs = NULL; + oc->foreign_exports = NULL; } static void @@ -1416,7 +1390,7 @@ mkOc( pathchar *path, char *image, int imageSize, oc->n_segments = 0; oc->segments = NULL; oc->proddables = NULL; - oc->stable_ptrs = NULL; + oc->foreign_exports = NULL; #if defined(NEED_SYMBOL_EXTRAS) oc->symbol_extras = NULL; #endif @@ -1777,7 +1751,8 @@ int ocTryLoad (ObjectCode* oc) { IF_DEBUG(linker, debugBelch("ocTryLoad: ocRunInit start\n")); - loading_obj = oc; // tells foreignExportStablePtr what to do + // See Note [Tracking foreign exports] in ForeignExports.c + foreignExportsLoadingObject(oc); #if defined(OBJFORMAT_ELF) r = ocRunInit_ELF ( oc ); #elif defined(OBJFORMAT_PEi386) @@ -1787,7 +1762,7 @@ int ocTryLoad (ObjectCode* oc) { #else barf("ocTryLoad: initializers not implemented on this platform"); #endif - loading_obj = NULL; + foreignExportsFinishedLoadingObject(); if (!r) { return r; } ===================================== rts/LinkerInternals.h ===================================== @@ -135,17 +135,6 @@ typedef struct _Segment { int n_sections; } Segment; -/* - * We must keep track of the StablePtrs that are created for foreign - * exports by constructor functions when the module is loaded, so that - * we can free them again when the module is unloaded. If we don't do - * this, then the StablePtr will keep the module alive indefinitely. - */ -typedef struct ForeignExportStablePtr_ { - StgStablePtr stable_ptr; - struct ForeignExportStablePtr_ *next; -} ForeignExportStablePtr; - #if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif @@ -240,7 +229,8 @@ typedef struct _ObjectCode { char* bssBegin; char* bssEnd; - ForeignExportStablePtr *stable_ptrs; + /* a list of all ForeignExportsLists owned by this object */ + struct ForeignExportsList *foreign_exports; /* Holds the list of symbols in the .o file which require extra information.*/ ===================================== rts/RtsStartup.c ===================================== @@ -20,6 +20,7 @@ #include "STM.h" /* initSTM */ #include "RtsSignals.h" #include "Weak.h" +#include "ForeignExports.h" /* processForeignExports */ #include "Ticky.h" #include "StgRun.h" #include "Prelude.h" /* fixupRTStoPreludeRefs */ @@ -287,7 +288,13 @@ hs_init_ghc(int *argc, char **argv[], RtsConfig rts_config) getStablePtr((StgPtr)runHandlersPtr_closure); #endif - // Initialize the top-level handler system + /* + * process any foreign exports which were registered while loading the + * image + * */ + processForeignExports(); + + /* initialize the top-level handler system */ initTopHandler(); /* initialise the shared Typeable store */ ===================================== rts/RtsSymbols.c ===================================== @@ -643,7 +643,7 @@ SymI_HasProto(freeFullProgArgv) \ SymI_HasProto(getProcessElapsedTime) \ SymI_HasProto(getStablePtr) \ - SymI_HasProto(foreignExportStablePtr) \ + SymI_HasProto(registerForeignExports) \ SymI_HasProto(hs_init) \ SymI_HasProto(hs_init_with_rtsopts) \ SymI_HasProto(hs_init_ghc) \ ===================================== rts/linker/PEi386.c ===================================== @@ -1952,13 +1952,15 @@ ocResolve_PEi386 ( ObjectCode* oc ) { uint64_t v; v = S + A; - if (v >> 32) { + // N.B. in the case of the sign-extended relocations we must ensure that v + // fits in a signed 32-bit value. See #15808. + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + A; - if (v >> 32) { + if (((int64_t) v > (int64_t) INT32_MAX) || ((int64_t) v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_ADDR32[NB]: High bits are set in %zx for %s", v, (char *)symbol); } @@ -1970,14 +1972,14 @@ ocResolve_PEi386 ( ObjectCode* oc ) { intptr_t v; v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { /* Make the trampoline then */ copyName (getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1); S = makeSymbolExtra_PEi386(oc, symIndex, S, (char *)symbol); /* And retry */ v = S + (int32_t)A - ((intptr_t)pP) - 4; - if ((v > (intptr_t) INT32_MAX) || (v < (intptr_t) INT32_MIN)) { + if ((v > (int64_t) INT32_MAX) || (v < (int64_t) INT32_MIN)) { barf("IMAGE_REL_AMD64_REL32: High bits are set in %zx for %s", v, (char *)symbol); } ===================================== rts/rts.cabal.in ===================================== @@ -131,6 +131,7 @@ library rts/EventLogWriter.h rts/FileLock.h rts/Flags.h + rts/ForeignExports.h rts/GetTime.h rts/Globals.h rts/Hpc.h @@ -382,6 +383,7 @@ library ClosureFlags.c Disassembler.c FileLock.c + ForeignExports.c Globals.c Hash.c Heap.c ===================================== testsuite/tests/cmm/should_run/all.T ===================================== @@ -2,3 +2,19 @@ test('HooplPostorder', extra_run_opts('"' + config.libdir + '"'), compile_and_run, ['-package ghc']) + +test('cmp64', + [ extra_run_opts('"' + config.libdir + '"') + , omit_ways(['ghci']) + , extra_clean('cmp64_cmm.o') + ], + multi_compile_and_run, + ['cmp64', [('cmp64_cmm.cmm', '')], '-O']) + + +# test('T17516', +# [ collect_compiler_stats('bytes allocated', 5), +# extra_clean(['T17516A.hi', 'T17516A.o']) +# ], +# multimod_compile, +# ['T17516', '-O -v0']) \ No newline at end of file ===================================== testsuite/tests/cmm/should_run/cmp64.hs ===================================== @@ -0,0 +1,156 @@ +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnliftedFFITypes #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE GHCForeignImportPrim #-} +{-# LANGUAGE CPP #-} + +{- Test 64bit comparisons. + We simply compare a number of values in different ways + and print the results. 32bit and 64bit platforms use + different code paths so if either one breaks this test + should catch it. + +-} + +module Main where + +#if defined(__GLASGOW_HASKELL__) +#include "MachDeps.h" +#endif + +import GHC.Types +import GHC.Exts +import GHC.Word +import GHC.Int +import Data.Bits +import Control.Monad +import Unsafe.Coerce + +#if WORD_SIZE_IN_BITS < 64 +#define INT64 Int64# +#define WORD64 Word64# +#define I64CON I64# +#else +#define INT64 Int# +#define WORD64 Word# +#define I64CON I# +#endif + + +data I64 = I64 INT64 +data W64 = W64 WORD64 + +foreign import prim "test_lt" lt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_gt" gt_s :: INT64 -> INT64 -> Int# +foreign import prim "test_le" le_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ge" ge_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_eq" eq_s :: INT64 -> INT64 -> Int# +foreign import prim "test_ne" ne_s :: INT64 -> INT64 -> Int# + +foreign import prim "test_ltu" lt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_gtu" gt_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_leu" le_u :: WORD64 -> WORD64 -> Int# +foreign import prim "test_geu" ge_u :: WORD64 -> WORD64 -> Int# + +wordValues :: [Word64] +wordValues = do + lowerBits <- interestingValues + higherBits <- interestingValues + return $ (fromIntegral higherBits `shiftL` 32) .|. fromIntegral lowerBits + +interestingValues :: [Word32] +interestingValues = + [ 0x00000000 + , 0x00000001 + , 0x00000002 + + , 0x7FFFFFFD + , 0x7FFFFFFE + , 0x7FFFFFFF + + , 0xFFFFFFFE + , 0xFFFFFFFD + , 0xFFFFFFFF + + , 0x80000000 + , 0x80000001 + , 0x80000002 + ] + +intValues :: [Int64] +intValues = map fromIntegral wordValues + +intOps :: [(INT64 -> INT64 -> Int#, String)] +intOps = [(lt_s, "lt_s") + ,(gt_s, "gt_s") + ,(le_s, "le_s") + ,(ge_s, "ge_s") + + ,(eq_s, "eq_s") + ,(ne_s, "ne_s")] + +testInt :: Int64 -> Int64 -> (INT64 -> INT64 -> Int#) -> String -> IO () +testInt x y op op_name = do + (I64 w1,I64 w2) <- getInts x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + return () + +testInts = do + let tests = do + (op,op_desc) <- intOps + x <- intValues + y <- intValues + return $ testInt x y op op_desc + sequence tests + +wordOps :: [(WORD64 -> WORD64 -> Int#, String)] +wordOps = [(lt_u, "lt_u") + ,(gt_u, "gt_u") + ,(le_u, "le_u") + ,(ge_u, "ge_u")] + +testWord x y op op_name = do + (W64 w1,W64 w2) <- getWords x y + let !res = I# (op w1 w2) + putStrLn $ "(" ++ (show x) ++ " `" ++ op_name ++ "` " ++ show y ++ ") = " ++ show res + +testWords = do + let tests = do + (op,op_desc) <- wordOps + x <- wordValues + y <- wordValues + return $ testWord x y op op_desc + sequence tests + +main = do + testInts + testWords + + print "done" + print wordValues + print intValues + return () + + +-- We want to get a I64#/W64# both and 64 and 32bit platforms. +-- We unsafeCoerce on 64bit, on 32bit the unboxed argument already +-- has the right type. + +getInts :: Int64 -> Int64 -> IO ( I64, I64 ) +#if WORD_SIZE_IN_BITS < 64 +getInts (I64# a1) (I64# a2) = return (I64 a1, I64 a2) +#else +getInts (I64# a1) (I64# a2) = return $ unsafeCoerce# (I64 a1, I64 a2) +#endif + + +getWords :: Word64 -> Word64 -> IO ( W64, W64 ) +#if WORD_SIZE_IN_BITS < 64 +getWords (W64# a1) (W64# a2) = return (W64 a1, W64 a2) +#else +getWords (W64# a1) (W64# a2) = return $ unsafeCoerce# (W64 a1, W64 a2) +#endif ===================================== testsuite/tests/cmm/should_run/cmp64.stdout ===================================== The diff for this file was not included because it is too large. ===================================== testsuite/tests/cmm/should_run/cmp64_cmm.cmm ===================================== @@ -0,0 +1,31 @@ +#include "Cmm.h" + +#define TEST(name, op) \ + name (bits64 x, bits64 y) { \ + if(x `op` y) { \ + return (1); \ + } else { \ + return (0); \ + } \ + } + +cmm_func_test(bits64 foo, bits64 bar) { + return (1); +} + +TEST(test_lt, lt) +TEST(test_gt, gt) + +TEST(test_ne, ne) +TEST(test_eq, eq) + +TEST(test_ge, ge) +TEST(test_le, le) + +TEST(test_geu, geu) +TEST(test_leu, leu) + +TEST(test_ltu, ltu) +TEST(test_gtu, gtu) + + ===================================== testsuite/tests/simplCore/should_compile/T18346/MiniLens.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE RankNTypes #-} + +module MiniLens ((^.), Getting, Lens', lens, view) where + +import Data.Functor.Const (Const(..)) + +type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t + +type Lens' s a = Lens s s a a + +lens :: (s -> a) -> (s -> b -> t) -> Lens s t a b +lens sa sbt afb s = sbt s <$> afb (sa s) +{-# INLINE lens #-} + +type Getting r s a = (a -> Const r a) -> s -> Const r s + +view :: Getting a s a -> s -> a +view l = getConst . l Const +{-# INLINE view #-} + +(^.) :: s -> Getting a s a -> a +s ^. l = getConst (l Const s) +{-# INLINE (^.) #-} ===================================== testsuite/tests/simplCore/should_compile/T18346/T18346.hs ===================================== @@ -0,0 +1,18 @@ +{-# LANGUAGE RankNTypes #-} + +module GHCBug (field) where + +import MiniLens ((^.), Getting, Lens', lens, view) + +t' :: Getting () () () +t' = lens id const +{-# NOINLINE t' #-} + +mlift :: Functor f => Getting b a b -> Lens' (f a) (f b) +mlift l = lens (fmap (^. l)) const +{-# INLINE mlift #-} + +newtype Field = F (Maybe () -> Maybe ()) + +field :: Field +field = F (view (mlift t')) ===================================== testsuite/tests/simplCore/should_compile/T18346/all.T ===================================== @@ -0,0 +1,2 @@ +test('T18346', [extra_files(['MiniLens.hs'])], multimod_compile, ['T18346.hs', '-v0']) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cc085aefd9d72da6aff5c5305a6b864398f95ec3...65be3832f3aa48bbde896ee846c18fcba1f16b42 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cc085aefd9d72da6aff5c5305a6b864398f95ec3...65be3832f3aa48bbde896ee846c18fcba1f16b42 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 Nov 19 15:10:35 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 19 Nov 2020 10:10:35 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: users-guide: A bit of clean-up in profiling flag documentation Message-ID: <5fb68aeb8e06_36a7f2b113c1832ae@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 3e5329b9 by Ben Gamari at 2020-11-19T10:10:16-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 8470c8ab by Ben Gamari at 2020-11-19T10:10:16-05:00 testsuite: Refactor CountParserDeps - - - - - 42151151 by Ben Gamari at 2020-11-19T10:10:16-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - b15fb06a by Krzysztof Gogolewski at 2020-11-19T10:10:19-05:00 Export indexError from GHC.Ix (#18579) - - - - - d4c0cadc by Sylvain Henry at 2020-11-19T10:10:24-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 68aa3d6e by Sylvain Henry at 2020-11-19T10:10:24-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - a91c5996 by Greg Steuck at 2020-11-19T10:10:26-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 31c96b6a by Ben Gamari at 2020-11-19T10:10:26-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 3147e41d by Ben Gamari at 2020-11-19T10:10:26-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/extending_ghc.rst - docs/users_guide/profiling.rst - ghc/GHCi/UI.hs - ghc/Main.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ded01ab9bb90d712a8825ad0c25937963d475272...3147e41da9355f04da3b438d342ce259c8183a38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ded01ab9bb90d712a8825ad0c25937963d475272...3147e41da9355f04da3b438d342ce259c8183a38 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 Nov 19 16:41:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 11:41:56 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/hadrian-no-strip Message-ID: <5fb6a054279d2_36a7f2b032c1933c1@gitlab.mail> Ben Gamari pushed new branch wip/hadrian-no-strip at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/hadrian-no-strip 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 Nov 19 16:42:20 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 11:42:20 -0500 Subject: [Git][ghc/ghc][wip/hadrian-no-strip] 3 commits: Add Addr# atomic primops (#17751) Message-ID: <5fb6a06cd4446_36a7f2b13581935ed@gitlab.mail> Ben Gamari pushed to branch wip/hadrian-no-strip at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 21d74e82 by Ben Gamari at 2020-11-19T11:42:09-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs - compiler/GHC/StgToCmm/Prim.hs - hadrian/src/Flavour.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.hs - testsuite/tests/concurrent/should_run/AtomicPrimops.stdout - testsuite/tests/deSugar/should_compile/DsStrictWarn.stderr - testsuite/tests/deSugar/should_compile/GadtOverlap.stderr - testsuite/tests/deSugar/should_compile/T14135.stderr - testsuite/tests/deSugar/should_compile/T14546a.stderr - testsuite/tests/deSugar/should_compile/T14546d.stderr - testsuite/tests/deSugar/should_compile/T5455.stderr - testsuite/tests/dependent/should_compile/KindEqualities.stderr - testsuite/tests/driver/T8101.stderr - testsuite/tests/driver/T8101b.stderr - testsuite/tests/driver/werror.stderr - testsuite/tests/ghci/prog018/prog018.stdout - testsuite/tests/parser/should_compile/T15139.stderr - testsuite/tests/pmcheck/complete_sigs/T13964.stderr - testsuite/tests/pmcheck/complete_sigs/T14059a.stderr - testsuite/tests/pmcheck/complete_sigs/T17386.stderr - testsuite/tests/pmcheck/complete_sigs/completesig02.stderr - testsuite/tests/pmcheck/complete_sigs/completesig04.stderr - testsuite/tests/pmcheck/complete_sigs/completesig06.stderr - testsuite/tests/pmcheck/complete_sigs/completesig07.stderr - testsuite/tests/pmcheck/complete_sigs/completesig10.stderr - testsuite/tests/pmcheck/complete_sigs/completesig11.stderr - testsuite/tests/pmcheck/should_compile/EmptyCase001.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/609275722b520c3f49f755fdc3c6a55ee09b9c80...21d74e8253d3046f187028528f2bfcc8050d0a70 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/609275722b520c3f49f755fdc3c6a55ee09b9c80...21d74e8253d3046f187028528f2bfcc8050d0a70 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 Nov 19 16:43:31 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 11:43:31 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/eventlog-opt Message-ID: <5fb6a0b3b76d6_36a7f2b07281987a6@gitlab.mail> Ben Gamari pushed new branch wip/eventlog-opt at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/eventlog-opt 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 Nov 19 17:36:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 12:36:40 -0500 Subject: [Git][ghc/ghc][wip/dwarf-info-offset] 17 commits: testsuite: Add testcase for #18733 Message-ID: <5fb6ad286d70b_36a7f2b032c209830@gitlab.mail> Ben Gamari pushed to branch wip/dwarf-info-offset at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 76d483ae by Ben Gamari at 2020-11-19T12:00:57-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bd3d97ca81081a8a76e0f101e477a4175978b20f...76d483aeb0d807f083327f1d5e6444e5a62530d8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bd3d97ca81081a8a76e0f101e477a4175978b20f...76d483aeb0d807f083327f1d5e6444e5a62530d8 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 Nov 19 17:48:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 12:48:26 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ghc-8.10-backports Message-ID: <5fb6afeae6840_36a7f2b0c6421331a@gitlab.mail> Ben Gamari pushed new branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghc-8.10-backports 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 Nov 19 20:30:57 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Thu, 19 Nov 2020 15:30:57 -0500 Subject: [Git][ghc/ghc][wip/T18566] 19 commits: testsuite: Add testcase for #18733 Message-ID: <5fb6d601cff65_36a7b6bfe6c25321a@gitlab.mail> Sebastian Graf pushed to branch wip/T18566 at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - b112b042 by Ben Gamari at 2020-11-19T21:29:32+01:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 160d80c6 by Ben Gamari at 2020-11-19T21:29:32+01:00 testsuite: Refactor CountParserDeps - - - - - 2e36cda1 by Ben Gamari at 2020-11-19T21:30:45+01:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bb6eacc77324238401ed96bc47f273f1b61750f...2e36cda155d19228967572dfde036785bc80ef1b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8bb6eacc77324238401ed96bc47f273f1b61750f...2e36cda155d19228967572dfde036785bc80ef1b 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 Nov 19 20:34:14 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 15:34:14 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fb6d6c6e69e8_36a7be9284c257442@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: c4f9fdc9 by Moritz Angermann at 2020-11-19T20:32:44+00:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Metric Increase: T13701 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal - libraries/binary - libraries/bytestring - libraries/ghc-bignum/ghc-bignum.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c4f9fdc97e4cc9c5e7b91820ead844344fce9354 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c4f9fdc97e4cc9c5e7b91820ead844344fce9354 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 Nov 19 20:38:13 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 15:38:13 -0500 Subject: [Git][ghc/ghc][ghc-8.8] 4 commits: macOS: Load frameworks without stating them first. Message-ID: <5fb6d7b54bf3a_36a73fd2fda4e560266559@gitlab.mail> Ben Gamari pushed to branch ghc-8.8 at Glasgow Haskell Compiler / GHC Commits: f0a38f69 by Matthias Andreas Benkard at 2020-11-14T16:32:37-08:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - 70ccc8fd by Matthias Andreas Benkard at 2020-11-14T16:33:06-08:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - e156ae01 by Matthias Andreas Benkard at 2020-11-14T16:33:13-08:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - a3b2eef8 by Liam Damewood at 2020-11-16T08:24:42-08:00 Update reference to macOS Big Sur release notes. - - - - - 1 changed file: - compiler/ghci/Linker.hs Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1676,6 +1676,38 @@ addEnvPaths name list -- ---------------------------------------------------------------------------- -- Loading a dynamic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32) +{- +Note [macOS Big Sur dynamic libraries] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +macOS Big Sur makes the following change to how frameworks are shipped +with the OS: + +> New in macOS Big Sur 11 beta, the system ships with a built-in +> dynamic linker cache of all system-provided libraries. As part of +> this change, copies of dynamic libraries are no longer present on +> the filesystem. Code that attempts to check for dynamic library +> presence by looking for a file at a path or enumerating a directory +> will fail. Instead, check for library presence by attempting to +> dlopen() the path, which will correctly check for the library in the +> cache. (62986286) + +(https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11_0_1-release-notes/) + +Therefore, the previous method of checking whether a library exists +before attempting to load it makes GHC.Runtime.Linker.loadFramework +fail to find frameworks installed at /System/Library/Frameworks. +Instead, any attempt to load a framework at runtime, such as by +passing -framework OpenGL to runghc or running code loading such a +framework with GHCi, fails with a 'not found' message. + +GHC.Runtime.Linker.loadFramework now opportunistically loads the +framework libraries without checking for their existence first, +failing only if all attempts to load a given framework from any of the +various possible locations fail. See also #18446, which this change +addresses. +-} + -- Darwin / MacOS X only: load a framework -- a framework is a dynamic library packaged inside a directory of the same -- name. They are searched for in different paths than normal libraries. @@ -1686,17 +1718,29 @@ loadFramework hsc_env extraPaths rootname Left _ -> [] Right dir -> [dir "Library/Frameworks"] ps = extraPaths ++ homeFrameworkPath ++ defaultFrameworkPaths - ; mb_fwk <- findFile ps fwk_file - ; case mb_fwk of - Just fwk_path -> loadDLL hsc_env fwk_path - Nothing -> return (Just "not found") } - -- Tried all our known library paths, but dlopen() - -- has no built-in paths for frameworks: give up + ; errs <- findLoadDLL ps [] + ; return $ fmap (intercalate ", ") errs + } where fwk_file = rootname <.> "framework" rootname - -- sorry for the hardcoded paths, I hope they won't change anytime soon: + + -- sorry for the hardcoded paths, I hope they won't change anytime soon: defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"] + -- Try to call loadDLL for each candidate path. + -- + -- See Note [macOS Big Sur dynamic libraries] + findLoadDLL [] errs = + -- Tried all our known library paths, but dlopen() + -- has no built-in paths for frameworks: give up + return $ Just errs + findLoadDLL (p:ps) errs = + do { dll <- loadDLL hsc_env (p fwk_file) + ; case dll of + Nothing -> return Nothing + Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs) + } + {- ********************************************************************** Helper functions View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c58498b2dd95bac99cb3fa9014fa64cf12dd2f18...a3b2eef8a784b3484caae96e5c69289aafd444d6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c58498b2dd95bac99cb3fa9014fa64cf12dd2f18...a3b2eef8a784b3484caae96e5c69289aafd444d6 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 Nov 19 20:45:39 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 15:45:39 -0500 Subject: [Git][ghc/ghc][wip/T18234] 13 commits: nativeGen/dwarf: Fix procedure end addresses Message-ID: <5fb6d97327bdf_36a73fd2f1d8640026960@gitlab.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 1af80c13 by Ben Gamari at 2020-11-19T15:45:25-05:00 gitlab-ci: Add usage message to ci.sh - - - - - e6ca5c86 by Ben Gamari at 2020-11-19T15:45:25-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - d3121895 by Ben Gamari at 2020-11-19T15:45:25-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/95d2b07d218a5ba8865a887f0c19866d90f19c9a...d31218958264e4e20dbab7f0745d9590963cd7e7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/95d2b07d218a5ba8865a887f0c19866d90f19c9a...d31218958264e4e20dbab7f0745d9590963cd7e7 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 Nov 19 20:48:29 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 19 Nov 2020 15:48:29 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: Export indexError from GHC.Ix (#18579) Message-ID: <5fb6da1ddc44c_36a73fd2fda4e560277910@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: a44710b3 by Krzysztof Gogolewski at 2020-11-19T15:48:14-05:00 Export indexError from GHC.Ix (#18579) - - - - - 79de421d by Kamil Dworakowski at 2020-11-19T15:48:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 0d59d487 by Sebastian Graf at 2020-11-19T15:48:17-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 4f25115a by Sebastian Graf at 2020-11-19T15:48:17-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 50ef31e8 by Sebastian Graf at 2020-11-19T15:48:17-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - c231694d by Greg Steuck at 2020-11-19T15:48:19-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 8d15de18 by Ben Gamari at 2020-11-19T15:48:19-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - bfcb5cf7 by Ben Gamari at 2020-11-19T15:48:20-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 841b0fdf by Ben Gamari at 2020-11-19T15:48:20-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/ffi.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - libraries/base/GHC/Ix.hs - rts/linker/SymbolExtras.c - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3147e41da9355f04da3b438d342ce259c8183a38...841b0fdfaeab70319926ee743969d8a1e4d40d1e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3147e41da9355f04da3b438d342ce259c8183a38...841b0fdfaeab70319926ee743969d8a1e4d40d1e 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 Nov 19 20:49:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 15:49:25 -0500 Subject: [Git][ghc/ghc][wip/T18234] gitlab-ci: Introduce a nightly cross-compilation job Message-ID: <5fb6da554f045_36a77e854342845cb@gitlab.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: b2b1ccad by Ben Gamari at 2020-11-19T15:49:16-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 2 changed files: - .gitlab-ci.yml - .gitlab/ci.sh Changes: ===================================== .gitlab-ci.yml ===================================== @@ -257,6 +257,33 @@ validate-x86_64-linux-deb9-unreg-hadrian: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +validate-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV" + variables: + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*cross-compilation.*/' + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build needs: [lint-linters, lint-submods] ===================================== .gitlab/ci.sh ===================================== @@ -40,9 +40,9 @@ Hadrian build system build_hadrian Build GHC via the Hadrian build system test_hadrian Test GHC via the Hadrian build system - Environment variables affecting both build systems: + CROSS_TARGET Triple of cross-compilation target. VERBOSE Set to non-empty for verbose build output MSYSTEM (Windows-only) Which platform to build form (MINGW64 or MINGW32). @@ -111,11 +111,11 @@ function setup_locale() { function mingw_init() { case "$MSYSTEM" in MINGW32) - triple="i386-unknown-mingw32" + target_triple="i386-unknown-mingw32" boot_triple="i386-unknown-mingw32" # triple of bootstrap GHC ;; MINGW64) - triple="x86_64-unknown-mingw32" + target_triple="x86_64-unknown-mingw32" boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC ;; *) @@ -378,8 +378,8 @@ function configure() { end_section "booting" local target_args="" - if [[ -n "$triple" ]]; then - target_args="--target=$triple" + if [[ -n "$target_triple" ]]; then + target_args="--target=$target_triple" fi start_section "configuring" @@ -430,6 +430,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -450,6 +455,11 @@ function build_hadrian() { } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -537,6 +547,11 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2b1ccad1c479557895a978e4e6b01edcafa0dd1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2b1ccad1c479557895a978e4e6b01edcafa0dd1 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 Nov 19 20:54:49 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Thu, 19 Nov 2020 15:54:49 -0500 Subject: [Git][ghc/ghc][wip/T18914] 2 commits: Use HsOuterExplicit in instance sigs in deriving-generated code Message-ID: <5fb6db99223f5_36a73fd2f1d86400286622@gitlab.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: 6abe3b2d by Ryan Scott at 2020-11-19T15:53:09-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). I also made `HsCoreTy` a type synonym instead of a newtype, as making it a distinct data type wasn't buying us much. * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - b826244a by Ryan Scott at 2020-11-19T15:53:09-05:00 testsuite: Mark T14702 as fragile on Windows See #18953. - - - - - 11 changed files: - compiler/GHC/Hs/Type.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/deriving/should_compile/T14578.stderr - + testsuite/tests/deriving/should_compile/T18914.hs - testsuite/tests/deriving/should_compile/all.T - testsuite/tests/rts/all.T - utils/haddock Changes: ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -24,7 +24,7 @@ module GHC.Hs.Type ( HsArrow(..), arrowToHsType, hsLinear, hsUnrestricted, isUnrestricted, - HsType(..), NewHsTypeX(..), LHsType, HsKind, LHsKind, + HsType(..), HsCoreTy, LHsType, HsKind, LHsKind, HsForAllTelescope(..), HsTyVarBndr(..), LHsTyVarBndr, LHsQTyVars(..), HsOuterTyVarBndrs(..), HsOuterFamEqnTyVarBndrs, HsOuterSigTyVarBndrs, @@ -1039,12 +1039,6 @@ data HsType pass -- For details on above see note [Api annotations] in GHC.Parser.Annotation - -- | HsCoreTy (XCoreTy pass) Type -- An escape hatch for tunnelling a *closed* - -- -- Core Type through HsSyn. - -- -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - - -- For details on above see note [Api annotations] in GHC.Parser.Annotation - | HsExplicitListTy -- A promoted explicit list (XExplicitListTy pass) PromotionFlag -- whether explicitly promoted, for pretty printer @@ -1077,16 +1071,13 @@ data HsType pass | XHsType (XXType pass) -data NewHsTypeX - = NHsCoreTy Type -- An escape hatch for tunnelling a *closed* - -- Core Type through HsSyn. - -- See also Note [Typechecking NHsCoreTys] in - -- GHC.Tc.Gen.HsType. - deriving Data - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None - -instance Outputable NewHsTypeX where - ppr (NHsCoreTy ty) = ppr ty +-- An escape hatch for tunnelling a Core 'Type' through 'HsType'. +-- For more details on how this works, see: +-- +-- * @Note [Renaming HsCoreTys]@ in "GHC.Rename.HsType" +-- +-- * @Note [Typechecking HsCoreTys]@ in "GHC.Tc.Gen.HsType" +type HsCoreTy = Type type instance XForAllTy (GhcPass _) = NoExtField type instance XQualTy (GhcPass _) = NoExtField @@ -1124,7 +1115,7 @@ type instance XTyLit (GhcPass _) = NoExtField type instance XWildCardTy (GhcPass _) = NoExtField -type instance XXType (GhcPass _) = NewHsTypeX +type instance XXType (GhcPass _) = HsCoreTy -- Note [Literal source text] in GHC.Types.Basic for SourceText fields in @@ -2250,7 +2241,7 @@ hsTypeNeedsParens p = go_hs_ty go_hs_ty (HsOpTy{}) = p >= opPrec go_hs_ty (HsParTy{}) = False go_hs_ty (HsDocTy _ (L _ t) _) = go_hs_ty t - go_hs_ty (XHsType (NHsCoreTy ty)) = go_core_ty ty + go_hs_ty (XHsType ty) = go_core_ty ty go_core_ty (TyVarTy{}) = False go_core_ty (AppTy{}) = p >= appPrec ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -39,6 +39,7 @@ import GHC.Prelude import {-# SOURCE #-} GHC.Rename.Splice( rnSpliceType ) +import GHC.Core.TyCo.FVs ( tyCoVarsOfTypeList ) import GHC.Driver.Session import GHC.Hs import GHC.Rename.Env @@ -48,6 +49,7 @@ import GHC.Rename.Utils ( HsDocContext(..), inHsDocContext, withHsDocContext , checkShadowedRdrNames ) import GHC.Rename.Fixity ( lookupFieldFixityRn, lookupFixityRn , lookupTyFixityRn ) +import GHC.Rename.Unbound ( notInScopeErr ) import GHC.Tc.Utils.Monad import GHC.Types.Name.Reader import GHC.Builtin.Names @@ -634,10 +636,20 @@ rnHsTyKi env (HsDocTy _ ty haddock_doc) = do { (ty', fvs) <- rnLHsTyKi env ty ; return (HsDocTy noExtField ty' haddock_doc, fvs) } -rnHsTyKi _ (XHsType (NHsCoreTy ty)) - = return (XHsType (NHsCoreTy ty), emptyFVs) - -- The emptyFVs probably isn't quite right - -- but I don't think it matters +-- See Note [Renaming HsCoreTys] +rnHsTyKi env (XHsType ty) + = do mapM_ (check_in_scope . nameRdrName) fvs_list + return (XHsType ty, fvs) + where + fvs_list = map getName $ tyCoVarsOfTypeList ty + fvs = mkFVs fvs_list + + check_in_scope :: RdrName -> RnM () + check_in_scope rdr_name = do + mb_name <- lookupLocalOccRn_maybe rdr_name + when (isNothing mb_name) $ + addErr $ withHsDocContext (rtke_ctxt env) $ + notInScopeErr rdr_name rnHsTyKi env ty@(HsExplicitListTy _ ip tys) = do { data_kinds <- xoptM LangExt.DataKinds @@ -661,6 +673,39 @@ rnHsArrow _env (HsLinearArrow u) = return (HsLinearArrow u, emptyFVs) rnHsArrow env (HsExplicitMult u p) = (\(mult, fvs) -> (HsExplicitMult u mult, fvs)) <$> rnLHsTyKi env p +{- +Note [Renaming HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to rename an HsCoreTy, +since it's already been renamed to some extent. However, in an attempt to +detect ill-formed HsCoreTys, the renamer checks to see if all free type +variables in an HsCoreTy are in scope. To see why this can matter, consider +this example from #18914: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +Because of #18914, a previous GHC would generate the following code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) -- The type within @(...) is an HsCoreTy + @(N f a) -- So is this + (m @f) + +There are two HsCoreTys in play—(f a) and (N f a)—both of which have +`f` and `a` as free type variables. The `f` is in scope from the instance head, +but `a` is completely unbound, which is what led to #18914. To avoid this sort +of mistake going forward, the renamer will now detect that `a` is unbound and +throw an error accordingly. +-} + -------------- rnTyVar :: RnTyKiEnv -> RdrName -> RnM Name rnTyVar env rdr_name ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1819,6 +1819,94 @@ a truly higher-rank type like so: Then the same situation will arise again. But at least it won't arise for the common case of methods with ordinary, prenex-quantified types. +----- +-- Wrinkle: Use HsOuterExplicit +----- + +One minor complication with the plan above is that we need to ensure that the +type variables from a method's instance signature properly scope over the body +of the method. For example, recall: + + instance (C m, forall p q. Coercible p q => Coercible (m p) (m q)) => + C (T m) where + join :: forall a. T m (T m a) -> T m a + join = coerce @( m (m a) -> m a) + @(T m (T m a) -> T m a) + join + +In the example above, it is imperative that the `a` in the instance signature +for `join` scope over the body of `join` by way of ScopedTypeVariables. +This might sound obvious, but note that in gen_Newtype_binds, which is +responsible for generating the code above, the type in `join`'s instance +signature is given as a Core type, whereas gen_Newtype_binds will eventually +produce HsBinds (i.e., source Haskell) that is renamed and typechecked. We +must ensure that `a` is in scope over the body of `join` during renaming +or else the generated code will be rejected. + +In short, we need to convert the instance signature from a Core type to an +HsType (i.e., a source Haskell type). Two possible options are: + +1. Convert the Core type entirely to an HsType (i.e., a source Haskell type). +2. Embed the entire Core type using HsCoreTy. + +Neither option is quite satisfactory: + +1. Converting a Core type to an HsType in full generality is surprisingly + complicated. Previous versions of GHCs did this, but it was the source of + numerous bugs (see #14579 and #16518, for instance). +2. While HsCoreTy is much less complicated that option (1), it's not quite + what we want. In order for `a` to be in scope over the body of `join` during + renaming, the `forall` must be contained in an HsOuterExplicit. + (See Note [Lexically scoped type variables] in GHC.Hs.Type.) HsCoreTy + bypasses HsOuterExplicit, so this won't work either. + +As a compromise, we adopt a combination of the two options above: + +* Split apart the top-level ForAllTys in the instance signature's Core type, +* Convert the top-level ForAllTys to an HsOuterExplicit, and +* Embed the remainder of the Core type in an HsCoreTy. + +This retains most of the simplicity of option (2) while still ensuring that +the type variables are correctly scoped. + +Note that splitting apart top-level ForAllTys will expand any type synonyms +in the Core type itself. This ends up being important to fix a corner case +observed in #18914. Consider this example: + + type T f = forall a. f a + + class C f where + m :: T f + + newtype N f a = MkN (f a) + deriving C + +What code should `deriving C` generate? It will have roughly the following +shape: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(...) (...) (m @f) + +At a minimum, we must instantiate `coerce` with `@(T f)` and `@(T (N f))`, but +with the `forall`s removed in order to make them monotypes. However, the +`forall` is hidden underneath the `T` type synonym, so we must first expand `T` +before we can strip of the `forall`. Expanding `T`, we get +`coerce @(forall a. f a) @(forall a. N f a)`, and after omitting the `forall`s, +we get `coerce @(f a) @(N f a)`. + +We can't stop there, however, or else we would end up with this code: + + instance C f => C (N f) where + m :: T (N f) + m = coerce @(f a) @(N f a) (m @f) + +Notice that the type variable `a` is completely unbound. In order to make sure +that `a` is in scope, we must /also/ expand the `T` in `m :: T (N f)` to get +`m :: forall a. N f a`. Fortunately, we will do just that in the plan outlined +above, since when we split off the top-level ForAllTys in the instance +signature, we must first expand the T type synonym. + Note [GND and ambiguity] ~~~~~~~~~~~~~~~~~~~~~~~~ We make an effort to make the code generated through GND be robust w.r.t. @@ -1891,13 +1979,30 @@ gen_Newtype_binds loc cls inst_tvs inst_tys rhs_ty , -- The derived instance signature, e.g., -- -- op :: forall c. a -> [T x] -> c -> Int + -- + -- Make sure that `forall c` is in an HsOuterExplicit so that it + -- scopes over the body of `op`. See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. L loc $ ClassOpSig noExtField False [loc_meth_RDR] - $ L loc $ mkHsImplicitSigType $ nlHsCoreTy to_ty + $ L loc $ mkHsExplicitSigType + (map mk_hs_tvb to_tvbs) + (nlHsCoreTy to_rho) ) where Pair from_ty to_ty = mkCoerceClassMethEqn cls inst_tvs inst_tys rhs_ty meth_id - (_, _, from_tau) = tcSplitSigmaTy from_ty - (_, _, to_tau) = tcSplitSigmaTy to_ty + (_, _, from_tau) = tcSplitSigmaTy from_ty + (to_tvbs, to_rho) = tcSplitForAllInvisTVBinders to_ty + (_, to_tau) = tcSplitPhiTy to_rho + -- The use of tcSplitForAllInvisTVBinders above expands type synonyms, + -- which is important to ensure correct type variable scoping. + -- See "Wrinkle: Use HsOuterExplicit" in + -- Note [GND and QuantifiedConstraints]. + + mk_hs_tvb :: VarBndr TyVar flag -> LHsTyVarBndr flag GhcPs + mk_hs_tvb (Bndr tv flag) = noLoc $ KindedTyVar noExtField + flag + (noLoc (getRdrName tv)) + (nlHsCoreTy (tyVarKind tv)) meth_RDR = getRdrName meth_id loc_meth_RDR = L loc meth_RDR @@ -1950,8 +2055,8 @@ nlHsAppType e s = noLoc (HsAppType noExtField e hs_ty) where hs_ty = mkHsWildCardBndrs $ parenthesizeHsType appPrec $ nlHsCoreTy s -nlHsCoreTy :: Type -> LHsType GhcPs -nlHsCoreTy = noLoc . XHsType . NHsCoreTy +nlHsCoreTy :: HsCoreTy -> LHsType GhcPs +nlHsCoreTy = noLoc . XHsType mkCoerceClassMethEqn :: Class -- the class being derived -> [TyVar] -- the tvs in the instance head (this includes @@ -2079,15 +2184,15 @@ genAuxBindSpecDup loc original_rdr_name dup_spec genAuxBindSpecSig :: SrcSpan -> AuxBindSpec -> LHsSigWcType GhcPs genAuxBindSpecSig loc spec = case spec of DerivCon2Tag tycon _ - -> mk_sig $ L loc $ XHsType $ NHsCoreTy $ + -> mk_sig $ L loc $ XHsType $ mkSpecSigmaTy (tyConTyVars tycon) (tyConStupidTheta tycon) $ mkParentType tycon `mkVisFunTyMany` intPrimTy DerivTag2Con tycon _ -> mk_sig $ L loc $ - XHsType $ NHsCoreTy $ mkSpecForAllTys (tyConTyVars tycon) $ + XHsType $ mkSpecForAllTys (tyConTyVars tycon) $ intTy `mkVisFunTyMany` mkParentType tycon DerivMaxTag _ _ - -> mk_sig (L loc (XHsType (NHsCoreTy intTy))) + -> mk_sig (L loc (XHsType intTy)) DerivDataDataType _ _ _ -> mk_sig (nlHsTyVar dataType_RDR) DerivDataConstr _ _ _ ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -942,8 +942,8 @@ tc_infer_hs_type mode (HsSpliceTy _ (HsSpliced _ _ (HsSplicedTy ty))) tc_infer_hs_type mode (HsDocTy _ ty _) = tc_infer_lhs_type mode ty --- See Note [Typechecking NHsCoreTys] -tc_infer_hs_type _ (XHsType (NHsCoreTy ty)) +-- See Note [Typechecking HsCoreTys] +tc_infer_hs_type _ (XHsType ty) = do env <- getLclEnv -- Raw uniques since we go from NameEnv to TvSubstEnv. let subst_prs :: [(Unique, TcTyVar)] @@ -967,21 +967,21 @@ tc_infer_hs_type mode other_ty ; return (ty', kv) } {- -Note [Typechecking NHsCoreTys] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -NHsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. -As such, there's not much to be done in order to typecheck an NHsCoreTy, +Note [Typechecking HsCoreTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +HsCoreTy is an escape hatch that allows embedding Core Types in HsTypes. +As such, there's not much to be done in order to typecheck an HsCoreTy, since it's already been typechecked to some extent. There is one thing that we must do, however: we must substitute the type variables from the tcl_env. To see why, consider GeneralizedNewtypeDeriving, which is one of the main -clients of NHsCoreTy (example adapted from #14579): +clients of HsCoreTy (example adapted from #14579): newtype T a = MkT a deriving newtype Eq This will produce an InstInfo GhcPs that looks roughly like this: instance forall a_1. Eq a_1 => Eq (T a_1) where - (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an NHsCoreTy + (==) = coerce @( a_1 -> a_1 -> Bool) -- The type within @(...) is an HsCoreTy @(T a_1 -> T a_1 -> Bool) -- So is this (==) @@ -997,9 +997,9 @@ environment (tcl_env) with [a_1 :-> a_2]. This gives us: To ensure that the body of this instance is well scoped, every occurrence of the `a` type variable should refer to a_2, the new skolem. However, the -NHsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the +HsCoreTys mention a_1, not a_2. Luckily, the tcl_env provides exactly the substitution we need ([a_1 :-> a_2]) to fix up the scoping. We apply this -substitution to each NHsCoreTy and all is well: +substitution to each HsCoreTy and all is well: instance forall a_2. Eq a_2 => Eq (T a_2) where (==) = coerce @( a_2 -> a_2 -> Bool) @@ -1196,7 +1196,7 @@ tc_hs_type mode ty@(HsAppTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsAppKindTy{}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsOpTy {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsKindSig {}) ek = tc_infer_hs_type_ek mode ty ek -tc_hs_type mode ty@(XHsType (NHsCoreTy{})) ek = tc_infer_hs_type_ek mode ty ek +tc_hs_type mode ty@(XHsType {}) ek = tc_infer_hs_type_ek mode ty ek tc_hs_type mode ty@(HsWildCardTy _) ek = tcAnonWildCardOcc mode ty ek {- ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -291,7 +291,7 @@ no_anon_wc_ty lty = go lty HsTyLit{} -> True HsTyVar{} -> True HsStarTy{} -> True - XHsType (NHsCoreTy{}) -> True -- Core type, which does not have any wildcard + XHsType{} -> True -- HsCoreTy, which does not have any wildcard gos = all go ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -2002,7 +2002,7 @@ mkDefMethBind dfun_id clas sel_id dm_name mk_vta :: LHsExpr GhcRn -> Type -> LHsExpr GhcRn mk_vta fun ty = noLoc (HsAppType noExtField fun (mkEmptyWildCardBndrs $ nlHsParTy - $ noLoc $ XHsType $ NHsCoreTy ty)) + $ noLoc $ XHsType ty)) -- NB: use visible type application -- See Note [Default methods in instances] ===================================== testsuite/tests/deriving/should_compile/T14578.stderr ===================================== @@ -9,9 +9,8 @@ Derived class instances: GHC.Base.sconcat :: GHC.Base.NonEmpty (T14578.Wat f g a) -> T14578.Wat f g a GHC.Base.stimes :: - forall b. - GHC.Real.Integral b => - b -> T14578.Wat f g a -> T14578.Wat f g a + forall (b :: *). + GHC.Real.Integral b => b -> T14578.Wat f g a -> T14578.Wat f g a (GHC.Base.<>) = GHC.Prim.coerce @(T14578.App (Data.Functor.Compose.Compose f g) a @@ -39,8 +38,10 @@ Derived class instances: instance GHC.Base.Functor f => GHC.Base.Functor (T14578.App f) where GHC.Base.fmap :: - forall a b. (a -> b) -> T14578.App f a -> T14578.App f b - (GHC.Base.<$) :: forall a b. a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + (a -> b) -> T14578.App f a -> T14578.App f b + (GHC.Base.<$) :: + forall (a :: *) (b :: *). a -> T14578.App f b -> T14578.App f a GHC.Base.fmap = GHC.Prim.coerce @((a -> b) -> f a -> f b) @@ -52,17 +53,19 @@ Derived class instances: instance GHC.Base.Applicative f => GHC.Base.Applicative (T14578.App f) where - GHC.Base.pure :: forall a. a -> T14578.App f a + GHC.Base.pure :: forall (a :: *). a -> T14578.App f a (GHC.Base.<*>) :: - forall a b. + forall (a :: *) (b :: *). T14578.App f (a -> b) -> T14578.App f a -> T14578.App f b GHC.Base.liftA2 :: - forall a b c. + forall (a :: *) (b :: *) (c :: *). (a -> b -> c) -> T14578.App f a -> T14578.App f b -> T14578.App f c (GHC.Base.*>) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f b + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f b (GHC.Base.<*) :: - forall a b. T14578.App f a -> T14578.App f b -> T14578.App f a + forall (a :: *) (b :: *). + T14578.App f a -> T14578.App f b -> T14578.App f a GHC.Base.pure = GHC.Prim.coerce @(a -> f a) @(a -> T14578.App f a) (GHC.Base.pure @f) ===================================== testsuite/tests/deriving/should_compile/T18914.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE RankNTypes #-} +module T18914 where + +type T f = forall a. f a + +class C f where + m1 :: T f + m2 :: forall a. f a + +newtype N f a = MkN (f a) + deriving C ===================================== testsuite/tests/deriving/should_compile/all.T ===================================== @@ -127,3 +127,4 @@ test('T17339', normal, compile, test('T17880', normal, compile, ['']) test('T18055', normal, compile, ['']) test('T18321', normal, compile, ['']) +test('T18914', normal, compile, ['']) ===================================== testsuite/tests/rts/all.T ===================================== @@ -359,6 +359,7 @@ test('T14497', [omit_ways(['profasm']), multi_cpu_race], compile_and_run, ['-O'] test('T14695', [normal, ignore_stderr], makefile_test, ['T14695']) test('T14702', [ ignore_stdout , when(unregisterised(), skip) + , when(opsys('mingw32'), fragile(18953)) , only_ways(['threaded1', 'threaded2']) , extra_run_opts('+RTS -A32m -N8 -T -RTS') ] ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 4d0498d503bd51b7d7626497580232685a2691a1 +Subproject commit cbe3946394dbbdf73534bde7e32dd8f33daf31b4 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d08443b3dd6a5343b6485f19a68eae158594446...b826244aaf61cf753449186761e0ad59c4f74eec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d08443b3dd6a5343b6485f19a68eae158594446...b826244aaf61cf753449186761e0ad59c4f74eec 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 Nov 19 23:19:20 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Thu, 19 Nov 2020 18:19:20 -0500 Subject: [Git][ghc/ghc][wip/amg/renamer-refactor] 9 commits: Introduce fieldLabelPrintableName Message-ID: <5fb6fd784c4c9_36a73fd2f1fdd7f83004a0@gitlab.mail> Adam Gundry pushed to branch wip/amg/renamer-refactor at Glasgow Haskell Compiler / GHC Commits: 206aab8b by Adam Gundry at 2020-11-19T16:44:13+00:00 Introduce fieldLabelPrintableName - - - - - 8610da7b by Adam Gundry at 2020-11-19T16:44:43+00:00 Extend DRFHoleFits test to cover case of an imported field label - - - - - bc9e6a97 by Adam Gundry at 2020-11-19T22:11:40+00:00 DRFPatSynExport test - - - - - f8c531fb by Adam Gundry at 2020-11-19T22:11:57+00:00 Clean up -ddump-minimal-imports - - - - - abba93de by Adam Gundry at 2020-11-19T22:13:27+00:00 Cleanup - - - - - e23604e9 by Adam Gundry at 2020-11-19T22:29:13+00:00 Add test for DuplicateRecordFields variant of #9156 - - - - - 4ff3c565 by Adam Gundry at 2020-11-19T22:29:43+00:00 Fix DuplicateRecordFields variant of #9156 - - - - - ea6061c4 by Adam Gundry at 2020-11-19T23:04:59+00:00 Add expect_broken test for #13438 - - - - - c6d41ff4 by Adam Gundry at 2020-11-19T23:18:48+00:00 Fix printing of some DRF pattern synonyms in errors - - - - - 22 changed files: - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Types/FieldLabel.hs - compiler/GHC/Types/Name.hs-boot - compiler/GHC/Types/Name/Reader.hs - + testsuite/tests/overloadedrecflds/ghci/T13438.hs - + testsuite/tests/overloadedrecflds/ghci/T13438.script - + testsuite/tests/overloadedrecflds/ghci/T13438.stdout - testsuite/tests/overloadedrecflds/ghci/all.T - + testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport.hs - + testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport.stdout - + testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport_A.hs - + testsuite/tests/overloadedrecflds/should_compile/Makefile - testsuite/tests/overloadedrecflds/should_compile/all.T - + testsuite/tests/overloadedrecflds/should_fail/DRF9156.hs - + testsuite/tests/overloadedrecflds/should_fail/DRF9156.stderr - testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.hs - testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr - + testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits_A.hs - testsuite/tests/overloadedrecflds/should_fail/all.T Changes: ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1873,8 +1873,8 @@ instance ToHie (Located (TyFamInstDecl GhcRn)) where instance HiePass p => ToHie (Context (FieldOcc (GhcPass p))) where toHie (C c (FieldOcc n (L l _))) = case hiePass @p of - HieTc -> toHie (C c (L l n)) -- AMG TODO: probably wrong - HieRn -> toHie (C c (L l n)) -- AMG TODO: probably wrong + HieTc -> toHie (C c (L l n)) + HieRn -> toHie (C c (L l n)) instance HiePass p => ToHie (PatSynFieldContext (RecordPatSynField (GhcPass p))) where toHie (PSC sp (RecordPatSynField a b)) = concatM $ ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -666,9 +666,11 @@ extendGlobalRdrEnvRn avails new_fixities occ = greOccName gre dups = filter isDupGRE (lookupGlobalRdrEnv env occ) -- Duplicate GREs are those defined locally with the same OccName, - -- except cases where *both* GREs are DuplicateRecordFields (#17965). + -- except cases where *both* GREs are DuplicateRecordFields (#17965) + -- that are distinct (#9156). isDupGRE gre' = isLocalGRE gre' - && not (isOverloadedRecFldGRE gre && isOverloadedRecFldGRE gre') + && (not (isOverloadedRecFldGRE gre && isOverloadedRecFldGRE gre') + || (gre_child gre == gre_child gre')) {- ********************************************************************* @@ -1635,8 +1637,8 @@ getMinimalImports = fmap combine . mapM mk_minimal -- to say "T(A,B,C)". So we have to find out what the module exports. to_ie _ (Avail n) = [IEVar noExtField (to_ie_post_rn $ noLoc n)] - to_ie _ (AvailFL fl) - = [IEVar noExtField (to_ie_post_rn $ noLoc (flSelector fl))] -- AMG TODO Probably wrong + to_ie _ (AvailFL fl) -- Note [Overloaded field import] + = [IEVar noExtField (to_ie_post_rn $ noLoc (fieldLabelPrintableName fl))] to_ie _ (AvailTC n [m] []) | n==m = [IEThingAbs noExtField (to_ie_post_rn $ noLoc n)] to_ie iface (AvailTC n ns fs) @@ -1762,6 +1764,23 @@ then the minimal import for module B must be because when DuplicateRecordFields is enabled, field selectors are not in scope without their enclosing datatype. +On the third hand, if we have + + {-# LANGUAGE DuplicateRecordFields #-} + module A where + pattern MkT { foo } = Just foo + + module B where + import A + f = ...foo... + +then the minimal import for module B must be + import A ( foo ) +because foo doesn't have a parent. This might actually be ambiguous if A +exports another field called foo, but there is no good answer to return and this +is a very obscure corner, so it seems to be the best we can do. See +DRFPatSynExport for a test of this. + ************************************************************************ * * ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -23,8 +23,7 @@ import GHC.Core.Type import GHC.Core.DataCon import GHC.Types.Name import GHC.Types.Name.Reader ( pprNameProvenance , GlobalRdrElt (..) - , globalRdrEnvElts, gre_name - , isOverloadedRecFldGRE ) + , globalRdrEnvElts, gre_name, grePrintableName ) import GHC.Builtin.Names ( gHC_ERR ) import GHC.Types.Id import GHC.Types.Var.Set @@ -473,9 +472,7 @@ pprHoleFit (HFDC sWrp sWrpVars sTy sProv sMs) (HoleFit {..}) = holeDisp = if sMs then holeVs else sep $ replicate (length hfMatches) $ text "_" occDisp = case hfCand of - -- AMG TODO: make OutputableBndr GlobalRdrElt instance that does the right thing? - GreHFCand gre | isOverloadedRecFldGRE gre -> pprPrefixOcc (occName gre) - | otherwise -> pprPrefixOcc (gre_name gre) + GreHFCand gre -> pprPrefixOcc (grePrintableName gre) NameHFCand name -> pprPrefixOcc name IdHFCand id_ -> pprPrefixOcc id_ tyDisp = ppWhen sTy $ dcolon <+> ppr hfType ===================================== compiler/GHC/Tc/Gen/Export.hs ===================================== @@ -613,11 +613,11 @@ checkPatSynParent parent NoParent child ; case mpat_syn_thing of AnId i | isId i , RecSelId { sel_tycon = RecSelPatSyn p } <- idDetails i - -> handle_pat_syn (selErr i) parent_ty_con p + -> handle_pat_syn (selErr child) parent_ty_con p AConLike (PatSynCon p) -> handle_pat_syn (psErr p) parent_ty_con p - _ -> failWithDcErr parent mpat_syn (ppr mpat_syn) [] } + _ -> failWithDcErr parent mpat_syn (ppr child) [] } where psErr = exportErrCtxt "pattern synonym" selErr = exportErrCtxt "pattern synonym record selector" ===================================== compiler/GHC/Types/FieldLabel.hs ===================================== @@ -69,6 +69,7 @@ module GHC.Types.FieldLabel , FieldLbl(..) , FieldLabel , mkFieldLabelOccs + , fieldLabelPrintableName ) where @@ -134,3 +135,12 @@ mkFieldLabelOccs lbl dc is_overloaded str = ":" ++ unpackFS lbl ++ ":" ++ occNameString dc sel_occ | is_overloaded = mkRecFldSelOcc str | otherwise = mkVarOccFS lbl + +-- | Undo the name mangling described in Note [FieldLabel] to produce a Name +-- that has the user-visible OccName (but the selector's unique). This should +-- be used only when generating output, when we want to show the label, but may +-- need to qualify it with a module prefix. +fieldLabelPrintableName :: FieldLabel -> Name +fieldLabelPrintableName fl + | flIsOverloaded fl = tidyNameOcc (flSelector fl) (mkVarOccFS (flLabel fl)) + | otherwise = flSelector fl ===================================== compiler/GHC/Types/Name.hs-boot ===================================== @@ -22,3 +22,4 @@ class NamedThing a where nameUnique :: Name -> Unique setNameUnique :: Name -> Unique -> Name nameOccName :: Name -> OccName +tidyNameOcc :: Name -> OccName -> Name ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -57,7 +57,7 @@ module GHC.Types.Name.Reader ( greRdrNames, greSrcSpan, greQualModName, gresToAvailInfo, greDefinitionModule, greDefinitionSrcSpan, - gre_name, + gre_name, grePrintableName, -- ** Global 'RdrName' mapping elements: 'GlobalRdrElt', 'Provenance', 'ImportSpec' GlobalRdrElt(..), isLocalGRE, isRecFldGRE, isOverloadedRecFldGRE, greLabel, @@ -656,6 +656,13 @@ gre_name gre = case gre_child gre of ChildName name -> name ChildField fl -> flSelector fl +-- | A Name for the GRE's child suitable for output to the user. Its OccName +-- will be the greOccName. +grePrintableName :: GlobalRdrElt -> Name +grePrintableName gre = case gre_child gre of + ChildName name -> name + ChildField fl -> fieldLabelPrintableName fl + -- | The SrcSpan of the name pointed to by the GRE. greDefinitionSrcSpan :: GlobalRdrElt -> SrcSpan greDefinitionSrcSpan = childSrcSpan . gre_child @@ -750,10 +757,10 @@ gresToAvailInfo gres comb :: GlobalRdrElt -> AvailInfo -> AvailInfo comb _ (Avail n) = Avail n -- Duplicated name, should not happen - comb _ (AvailFL fl) = AvailFL fl -- AMG TODO: shouldn't happen either? + comb _ (AvailFL fl) = AvailFL fl comb gre (AvailTC m ns fls) = case (gre_par gre, gre_child gre) of - (NoParent, ChildName me) -> AvailTC m (me:ns) fls -- Not sure this ever happens -- AMG TODO: AvailTC invariant? + (NoParent, ChildName me) -> AvailTC m (me:ns) fls -- Not sure this ever happens (NoParent, ChildField fl) -> AvailTC m ns (fl:fls) (ParentIs {}, ChildName me) -> AvailTC m (insertChildIntoChildren m ns me) fls (ParentIs {}, ChildField fl) -> AvailTC m ns (fl:fls) ===================================== testsuite/tests/overloadedrecflds/ghci/T13438.hs ===================================== @@ -0,0 +1,3 @@ +{-# LANGUAGE DuplicateRecordFields #-} +module T13438 where +data T = MkT { foo :: Int } ===================================== testsuite/tests/overloadedrecflds/ghci/T13438.script ===================================== @@ -0,0 +1,5 @@ +:l T13438.hs +:browse! T13438 +:browse T13438 +:ctags +:!cat tags ===================================== testsuite/tests/overloadedrecflds/ghci/T13438.stdout ===================================== @@ -0,0 +1,10 @@ +-- defined locally +type T :: * +data T = ... +MkT :: Int -> T +foo :: T -> Int +type T :: * +data T = MkT {foo :: Int} +foo T13438.hs 3;" v file: +MkT T13438.hs 3;" d +T T13438.hs 3;" t ===================================== testsuite/tests/overloadedrecflds/ghci/all.T ===================================== @@ -1,2 +1,3 @@ test('duplicaterecfldsghci01', combined_output, ghci_script, ['duplicaterecfldsghci01.script']) test('overloadedlabelsghci01', combined_output, ghci_script, ['overloadedlabelsghci01.script']) +test('T13438', [expect_broken(13438), combined_output], ghci_script, ['T13438.script']) ===================================== testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE DisambiguateRecordFields #-} +module DRFPatSynExport where +import DRFPatSynExport_A +v = MkT { m = () } ===================================== testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport.stdout ===================================== @@ -0,0 +1,3 @@ +[1 of 2] Compiling DRFPatSynExport_A ( DRFPatSynExport_A.hs, DRFPatSynExport_A.o ) +[2 of 2] Compiling DRFPatSynExport ( DRFPatSynExport.hs, DRFPatSynExport.o ) +import DRFPatSynExport_A ( MkT, m ) ===================================== testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport_A.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE PatternSynonyms #-} +module DRFPatSynExport_A where +data S = MkS { m :: Int } +pattern MkT { m } = m ===================================== testsuite/tests/overloadedrecflds/should_compile/Makefile ===================================== @@ -0,0 +1,3 @@ +DRFPatSynExport: + '$(TEST_HC)' $(TEST_HC_OPTS) DRFPatSynExport.hs -fforce-recomp -ddump-minimal-imports + cat DRFPatSynExport.imports ===================================== testsuite/tests/overloadedrecflds/should_compile/all.T ===================================== @@ -2,3 +2,4 @@ test('T11173', [], multimod_compile, ['T11173', '-v0']) test('T12609', normal, compile, ['']) test('T16597', [], multimod_compile, ['T16597', '-v0']) test('T17176', normal, compile, ['']) +test('DRFPatSynExport', [], makefile_test, ['DRFPatSynExport']) ===================================== testsuite/tests/overloadedrecflds/should_fail/DRF9156.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE DuplicateRecordFields #-} +module DRF9156 where +data D = D1 { f1 :: Int } + | D2 { f1, f1 :: Int } ===================================== testsuite/tests/overloadedrecflds/should_fail/DRF9156.stderr ===================================== @@ -0,0 +1,5 @@ + +DRF9156.hs:4:19: error: + Multiple declarations of ‘f1’ + Declared at: DRF9156.hs:3:15 + DRF9156.hs:4:19 ===================================== testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.hs ===================================== @@ -1,7 +1,8 @@ {-# LANGUAGE DuplicateRecordFields #-} - module DRFHoleFits where +import qualified DRFHoleFits_A as A data T = MkT { foo :: Int } bar = _ :: T -> Int +baz = _ :: A.S -> Int ===================================== testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits.stderr ===================================== @@ -1,3 +1,5 @@ +[1 of 2] Compiling DRFHoleFits_A ( DRFHoleFits_A.hs, DRFHoleFits_A.o ) +[2 of 2] Compiling DRFHoleFits ( DRFHoleFits.hs, DRFHoleFits.o ) DRFHoleFits.hs:7:7: error: • Found hole: _ :: T -> Int @@ -8,3 +10,15 @@ DRFHoleFits.hs:7:7: error: Valid hole fits include foo :: T -> Int (defined at DRFHoleFits.hs:5:16) bar :: T -> Int (defined at DRFHoleFits.hs:7:1) + +DRFHoleFits.hs:8:7: error: + • Found hole: _ :: A.S -> Int + • In the expression: _ :: A.S -> Int + In an equation for ‘baz’: baz = _ :: A.S -> Int + • Relevant bindings include + baz :: A.S -> Int (bound at DRFHoleFits.hs:8:1) + Valid hole fits include + baz :: A.S -> Int (defined at DRFHoleFits.hs:8:1) + DRFHoleFits_A.foo :: A.S -> Int + (imported qualified from ‘DRFHoleFits_A’ at DRFHoleFits.hs:3:1-35 + (and originally defined at DRFHoleFits_A.hs:5:16-18)) ===================================== testsuite/tests/overloadedrecflds/should_fail/DRFHoleFits_A.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE DuplicateRecordFields #-} + +module DRFHoleFits_A where + +data S = MkS { foo :: Int } +data U = MkU { foo :: Int } ===================================== testsuite/tests/overloadedrecflds/should_fail/all.T ===================================== @@ -33,6 +33,7 @@ test('T14953', [extra_files(['T14953_A.hs', 'T14953_B.hs'])], multimod_compile_fail, ['T14953', '']) test('DuplicateExports', normal, compile_fail, ['']) test('T17965', normal, compile_fail, ['']) -test('DRFHoleFits', normal, compile_fail, ['']) +test('DRFHoleFits', extra_files(['DRFHoleFits_A.hs']), multimod_compile_fail, ['DRFHoleFits', '']) test('DRFPartialFields', normal, compile_fail, ['']) test('T16745', extra_files(['T16745C.hs', 'T16745B.hs']), multimod_compile_fail, ['T16745A', '']) +test('DRF9156', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5ceb206d45d7754acedc917af07e7a0646c0ef41...c6d41ff494ef93d5dadc53f0842f109146f36760 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5ceb206d45d7754acedc917af07e7a0646c0ef41...c6d41ff494ef93d5dadc53f0842f109146f36760 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 Nov 19 23:30:34 2020 From: gitlab at gitlab.haskell.org (Alan Zimmerman) Date: Thu, 19 Nov 2020 18:30:34 -0500 Subject: [Git][ghc/ghc][wip/az/exactprint] WIP on delta printing. Message-ID: <5fb7001a45703_36a71600f92c3011e2@gitlab.mail> Alan Zimmerman pushed to branch wip/az/exactprint at Glasgow Haskell Compiler / GHC Commits: b5fe6860 by Alan Zimmerman at 2020-11-19T23:30:04+00:00 WIP on delta printing. Making progress - - - - - 15 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/ThToHs.hs - utils/check-exact/Main.hs - utils/check-exact/Test.hs - + utils/check-exact/cases/RenameCase1.hs - utils/check-exact/check-exact.cabal - utils/check-exact/src/ExactPrint.hs - utils/check-exact/src/Utils.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1925,8 +1925,7 @@ data GRHSs p body } | XGRHSs !(XXGRHSs p body) - -- MatchContext dependent, as per 'matchSeparator' -type instance XCGRHSs (GhcPass _) b = ApiAnn' AddApiAnn +type instance XCGRHSs (GhcPass _) b = NoExtField type instance XXGRHSs (GhcPass _) b = NoExtCon ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1120,7 +1120,7 @@ data HsType pass -- For adding new constructors via Trees that Grow | XHsType - (XXType pass) + !(XXType pass) data NewHsTypeX = NHsCoreTy Type -- An escape hatch for tunnelling a *closed* ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -185,10 +185,10 @@ mkSimpleMatch ctxt pats rhs unguardedGRHSs :: Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan - => LocatedA (body (GhcPass p)) -> ApiAnn' AddApiAnn + => LocatedA (body (GhcPass p)) -> ApiAnn' GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) unguardedGRHSs rhs@(L loc _) ann - = GRHSs ann (unguardedRHS noAnn (locA loc) rhs) emptyLocalBinds + = GRHSs noExtField (unguardedRHS ann (locA loc) rhs) emptyLocalBinds unguardedRHS :: Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan @@ -907,7 +907,7 @@ mkMatch ctxt pats expr binds = noLocA (Match { m_ext = noAnn , m_ctxt = ctxt , m_pats = map paren pats - , m_grhss = GRHSs noAnn (unguardedRHS noAnn noSrcSpan expr) binds }) + , m_grhss = GRHSs noExtField (unguardedRHS noAnn noSrcSpan expr) binds }) where paren :: LPat (GhcPass p) -> LPat (GhcPass p) paren lp@(L l p) ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -504,7 +504,7 @@ dsExpr (HsMultiIf res_ty alts) = mkErrorExpr | otherwise - = do { let grhss = GRHSs noAnn alts emptyLocalBinds + = do { let grhss = GRHSs noExtField alts emptyLocalBinds ; rhss_nablas <- pmcGRHSs IfAlt grhss ; match_result <- dsGRHSs IfAlt grhss res_ty rhss_nablas ; error_expr <- mkErrorExpr ===================================== compiler/GHC/Parser.y ===================================== @@ -2486,10 +2486,10 @@ rhs :: { Located (GRHSs GhcPs (LHsExpr GhcPs)) } : '=' exp wherebinds {% runPV (unECP $2) >>= \ $2 -> do { let loc = (comb3 $1 (reLoc $2) (adaptWhereBinds $3)) ; acs (\cs -> - sL loc (GRHSs (ApiAnn (rs loc) (mj AnnEqual $1) cs) (unguardedRHS (ApiAnn (rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) []) loc $2) + sL loc (GRHSs NoExtField (unguardedRHS (ApiAnn (rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) cs) loc $2) (unLoc $ (adaptWhereBinds $3)))) } } | gdrhs wherebinds { sL (comb2 $1 (adaptWhereBinds $>)) - (GRHSs noAnn (reverse (unLoc $1)) (unLoc $ (adaptWhereBinds $2))) } + (GRHSs noExtField (reverse (unLoc $1)) (unLoc $ (adaptWhereBinds $2))) } gdrhs :: { Located [LGRHS GhcPs (LHsExpr GhcPs)] } : gdrhs gdrh { sLL $1 $> ($2 : unLoc $1) } @@ -2755,7 +2755,7 @@ aexp :: { ECP } $ Match { m_ext = ApiAnn (glR $1) [mj AnnLam $1] cs , m_ctxt = LambdaExpr , m_pats = $2:$3 - , m_grhss = unguardedGRHSs $5 (ApiAnn (glR $4) (mu AnnRarrow $4) []) }])) } + , m_grhss = unguardedGRHSs $5 (ApiAnn (glR $4) (GrhsAnn Nothing (mu AnnRarrow $4)) []) }])) } | 'let' binds 'in' exp { ECP $ unECP $4 >>= \ $4 -> mkHsLetPV (comb2A $1 $>) (unLoc $2) $4 @@ -3181,7 +3181,7 @@ alt :: { forall b. DisambECP b => PV (LMatch GhcPs (LocatedA b)) } alt_rhs :: { forall b. DisambECP b => PV (Located (GRHSs GhcPs (LocatedA b))) } : ralt wherebinds { $1 >>= \alt -> - return $ sLL alt (adaptWhereBinds $>) (GRHSs noAnn (unLoc alt) (unLoc $ adaptWhereBinds $2)) } + return $ sLL alt (adaptWhereBinds $>) (GRHSs noExtField (unLoc alt) (unLoc $ adaptWhereBinds $2)) } ralt :: { forall b. DisambECP b => PV (Located [LGRHS GhcPs (LocatedA b)]) } : '->' exp { unECP $2 >>= \ $2 -> ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -498,6 +498,13 @@ defined. -- AnnKeywordId elements. Note: we may reduce the usage of -- AnnKeywordId, and use locations only, as captured in that -- structure. +-- +-- The spacing between the items under the scope of a given ApiAnn' is +-- derived from the original 'anchor'. But there is no requirement +-- that the items included in the sub-element have a "matching" +-- location in their relative anchors. This allows us to freely move +-- elements around, and stitch together new AST fragments out of old +-- ones, and have them still printed out in a reasonable way. data ApiAnn' ann = ApiAnn { anchor :: RealSrcSpan -- ^ Base location for the start of -- the syntactic element holding the @@ -514,6 +521,9 @@ data ApiAnn' ann type ApiAnn = ApiAnn' [AddApiAnn] type ApiAnnComments = [RealLocated AnnotationComment] +-- +| Relative positions, row then column +-- newtype DeltaPos = DP (Int,Int) deriving (Show,Eq,Ord,Typeable,Data) + data NoApiAnns = NoApiAnns deriving (Data,Eq,Ord) ===================================== compiler/GHC/Rename/Bind.hs ===================================== @@ -1232,7 +1232,7 @@ rnGRHSs :: AnnoBody body rnGRHSs ctxt rnBody (GRHSs _ grhss binds) = rnLocalBindsAndThen binds $ \ binds' _ -> do (grhss', fvGRHSs) <- mapFvRn (rnGRHS ctxt rnBody) grhss - return (GRHSs noAnn grhss' binds', fvGRHSs) + return (GRHSs noExtField grhss' binds', fvGRHSs) rnGRHS :: AnnoBody body => HsMatchContext GhcRn ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -276,7 +276,7 @@ tcGRHSs ctxt (GRHSs _ grhss binds) res_ty mapM (tcCollectingUsage . wrapLocM (tcGRHS ctxt res_ty)) grhss ; let (usages, grhss') = unzip ugrhss ; tcEmitBindingUsage $ supUEs usages - ; return (GRHSs noAnn grhss' binds') } + ; return (GRHSs noExtField grhss' binds') } ------------- tcGRHS :: TcMatchCtxt body -> ExpRhoType -> GRHS GhcRn (LocatedA (body GhcRn)) ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -190,7 +190,7 @@ cvtDec (TH.ValD pat body ds) ; ds' <- cvtLocalDecs (text "a where clause") ds ; returnJustLA $ Hs.ValD noExtField $ PatBind { pat_lhs = pat' - , pat_rhs = GRHSs noAnn body' ds' + , pat_rhs = GRHSs noExtField body' ds' , pat_ext = noAnn , pat_ticks = ([],[]) } } @@ -904,7 +904,7 @@ cvtClause ctxt (Clause ps body wheres) ; let pps = map (parenthesizePat appPrec) ps' ; g' <- cvtGuard body ; ds' <- cvtLocalDecs (text "a where clause") wheres - ; returnLA $ Hs.Match noAnn ctxt pps (GRHSs noAnn g' ds') } + ; returnLA $ Hs.Match noAnn ctxt pps (GRHSs noExtField g' ds') } cvtImplicitParamBind :: String -> TH.Exp -> CvtM (LIPBind GhcPs) cvtImplicitParamBind n e = do @@ -1213,7 +1213,7 @@ cvtMatch ctxt (TH.Match p body decs) _ -> p' ; g' <- cvtGuard body ; decs' <- cvtLocalDecs (text "a where clause") decs - ; returnLA $ Hs.Match noAnn ctxt [lp] (GRHSs noAnn g' decs') } + ; returnLA $ Hs.Match noAnn ctxt [lp] (GRHSs noExtField g' decs') } cvtGuard :: TH.Body -> CvtM [LGRHS GhcPs (LHsExpr GhcPs)] cvtGuard (GuardedB pairs) = mapM cvtpair pairs ===================================== utils/check-exact/Main.hs ===================================== @@ -6,9 +6,9 @@ import GHC hiding (moduleName) import GHC.Driver.Ppr import GHC.Driver.Session import GHC.Hs.Dump -import GHC.Types.SourceText +-- import GHC.Types.SourceText -- import GHC.Hs.Exact hiding (ExactPrint()) -import GHC.Utils.Outputable hiding (space) +-- import GHC.Utils.Outputable hiding (space) import System.Environment( getArgs ) import System.Exit import System.FilePath @@ -21,7 +21,6 @@ import ExactPrint tt :: IO () -- tt = testOneFile "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/lib" tt = testOneFile "/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib" - -- "Test.hs" -- "../../testsuite/tests/printer/Ppr001.hs" -- "../../testsuite/tests/printer/Ppr002.hs" -- "../../testsuite/tests/printer/Ppr003.hs" ===================================== utils/check-exact/Test.hs ===================================== @@ -1,34 +1,184 @@ -{-# LANGUAGE ParallelListComp #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE MagicHash, NoImplicitPrelude, TypeFamilies, UnboxedTuples #-} -module - Main - ( - main - , - foo - ) - where - -import {-# SOURCE #-} qualified Data.List as L -import Data.Map hiding ( Map(..) ) - -main = - putStrLn "hello" - -foo = 1 - - --- | '(' qconsym ')' {% amsr (sLL $1 $> (unLoc $2)) --- [mop $1,mjA AnnVal $2,mcp $3] } -f1 = ( Main.::: ) 0 1 - --- | '(' consym ')' {% amsr (sLL $1 $> (unLoc $2)) --- [mop $1,mjA AnnVal $2,mcp $3] } -f2 = ( ::: ) 0 1 - --- | '`' conid '`' {% amsr (sLL $1 $> (unLoc $2)) --- [mj AnnBackquote $1,mjA AnnVal $2 --- ,mj AnnBackquote $3] } --- data GG = GG Int Int --- gg = 0 ` GG ` 1 +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} + +-- import Data.List +import Data.Data +import Data.Typeable +-- import GHC.Types.SrcLoc +import GHC.Types.Name.Occurrence +import GHC.Types.Name.Reader +import GHC hiding (moduleName) +import GHC.Driver.Ppr +import GHC.Driver.Session +import GHC.Hs.Dump +-- import GHC.Types.SourceText +-- import GHC.Hs.Exact hiding (ExactPrint()) +-- import GHC.Utils.Outputable hiding (space) +import System.Environment( getArgs ) +import System.Exit +import System.FilePath + +import Types +import Utils +import ExactPrint +-- exactPrint = undefined +-- showPprUnsafe = undefined + +-- --------------------------------------------------------------------- + +tt :: IO () +-- tt = testOneFile "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/lib" +tt = testOneFile "/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib" + "cases/RenameCase1.hs" + +-- exact = ppr + +-- --------------------------------------------------------------------- + +usage :: String +usage = unlines + [ "usage: check-ppr (libdir) (file)" + , "" + , "where libdir is the GHC library directory (e.g. the output of" + , "ghc --print-libdir) and file is the file to parse." + ] + +main :: IO() +main = do + args <- getArgs + case args of + [libdir,fileName] -> testOneFile libdir fileName + _ -> putStrLn usage + +testOneFile :: FilePath -> String -> IO () +testOneFile libdir fileName = do + p <- parseOneFile libdir fileName + -- putStrLn $ "\n\ngot p" + let + origAst = showSDocUnsafe + $ showAstData BlankSrcSpanFile NoBlankApiAnnotations + (pm_parsed_source p) + anns' = pm_annotations p + -- pped = pragmas ++ "\n" ++ (exactPrint $ pm_parsed_source p) + pped = exactPrint (pm_parsed_source p) anns' + -- pragmas = getPragmas anns' + + newFile = dropExtension fileName <.> "ppr" <.> takeExtension fileName + newFileChanged = dropExtension fileName <.> "changed" <.> takeExtension fileName + astFile = fileName <.> "ast" + newAstFile = fileName <.> "ast.new" + + pped' <- exactprintWithChange changeRenameCase1 (pm_parsed_source p) anns' + -- putStrLn $ "\n\nabout to writeFile" + writeFile astFile origAst + -- putStrLn $ "\n\nabout to pp" + writeFile newFile pped + writeFile newFileChanged pped' + + -- putStrLn $ "anns':" ++ showPprUnsafe (apiAnnRogueComments anns') + + p' <- parseOneFile libdir newFile + + let newAstStr :: String + newAstStr = showSDocUnsafe + $ showAstData BlankSrcSpanFile NoBlankApiAnnotations + (pm_parsed_source p') + writeFile newAstFile newAstStr + + -- putStrLn $ "\n\nanns':" ++ showPprUnsafe (apiAnnRogueComments anns') + + if origAst == newAstStr + then do + -- putStrLn "ASTs matched" + exitSuccess + else do + putStrLn "AST Match Failed" + -- putStrLn "\n===================================\nOrig\n\n" + -- putStrLn origAst + putStrLn "\n===================================\nNew\n\n" + putStrLn newAstStr + exitFailure + + +parseOneFile :: FilePath -> FilePath -> IO ParsedModule +parseOneFile libdir fileName = do + let modByFile m = + case ml_hs_file $ ms_location m of + Nothing -> False + Just fn -> fn == fileName + runGhc (Just libdir) $ do + dflags <- getSessionDynFlags + let dflags2 = dflags `gopt_set` Opt_KeepRawTokenStream + _ <- setSessionDynFlags dflags2 + addTarget Target { targetId = TargetFile fileName Nothing + , targetAllowObjCode = True + , targetContents = Nothing } + _ <- load LoadAllTargets + graph <- getModuleGraph + let + modSum = case filter modByFile (mgModSummaries graph) of + [x] -> x + xs -> error $ "Can't find module, got:" + ++ show (map (ml_hs_file . ms_location) xs) + parseModule modSum + +-- getPragmas :: ApiAnns -> String +-- getPragmas anns' = pragmaStr +-- where +-- tokComment (L _ (AnnBlockComment s)) = s +-- tokComment (L _ (AnnLineComment s)) = s +-- tokComment _ = "" + +-- comments' = map tokComment $ sortRealLocated $ apiAnnRogueComments anns' +-- pragmas = filter (\c -> isPrefixOf "{-#" c ) comments' +-- pragmaStr = intercalate "\n" pragmas + +-- pp :: (Outputable a) => a -> String +-- pp a = showPpr unsafeGlobalDynFlags a + +-- --------------------------------------------------------------------- + +exactprintWithChange :: Changer -> ParsedSource -> ApiAnns -> IO String +exactprintWithChange f p anns = do + (anns',p') <- f anns p + return $ exactPrint p' anns' + + +type Changer = (ApiAnns -> ParsedSource -> IO (ApiAnns,ParsedSource)) + +noChange :: Changer +noChange ans parsed = return (ans,parsed) + +changeRenameCase1 :: Changer +changeRenameCase1 ans parsed = return (ans,rename "bazLonger" [((3,15),(3,18))] parsed) + +rename :: (Data a) => String -> [(Pos, Pos)] -> a -> a +rename newNameStr spans' a + = everywhere (mkT replaceRdr) a + where + newName = mkRdrUnqual (mkVarOcc newNameStr) + + cond :: SrcSpan -> Bool + cond ln = ss2range ln `elem` spans' + + replaceRdr :: LocatedN RdrName -> LocatedN RdrName + replaceRdr (L ln _) + | cond (locA ln) = L ln newName + replaceRdr x = x + +-- --------------------------------------------------------------------- +-- From SYB + +-- | Apply transformation on each level of a tree. +-- +-- Just like 'everything', this is stolen from SYB package. +everywhere :: (forall a. Data a => a -> a) -> (forall a. Data a => a -> a) +everywhere f = f . gmapT (everywhere f) + +-- | Create generic transformation. +-- +-- Another function stolen from SYB package. +mkT :: (Typeable a, Typeable b) => (b -> b) -> (a -> a) +mkT f = case cast f of + Just f' -> f' + Nothing -> id ===================================== utils/check-exact/cases/RenameCase1.hs ===================================== @@ -0,0 +1,5 @@ +module RenameCase1 where + +foo x = case (baz x) of + 1 -> "a" + _ -> "b" ===================================== utils/check-exact/check-exact.cabal ===================================== @@ -26,7 +26,7 @@ Executable check-exact Build-Depends: base >= 4 && < 5, bytestring, containers, - Cabal >= 3.0 && < 3.4, + Cabal >= 3.0 && < 3.6, directory, filepath, ghc ===================================== utils/check-exact/src/ExactPrint.hs ===================================== @@ -83,6 +83,10 @@ defaultEPState as = EPState , epLHS = 0 , epMarkLayout = False , priorEndPosition = (1,1) + , priorEndPositionE = (1,1) + , priorEndPositionU = (1,1) + , anchorSpan = badRealSrcSpan + , origPos = (1,1) , epComments = rogueComments as } @@ -142,6 +146,12 @@ data EPState = EPState , epLHS :: LayoutStartCol , priorEndPosition :: !Pos -- ^ Position reached when -- processing the last element + , priorEndPositionE :: !Pos -- ^ End of Position reached when + , priorEndPositionU :: !Pos -- ^ last priorEndPositionE used when calculating EDP + , anchorSpan :: !RealSrcSpan -- ^ in pre-changed AST reference frame, from Annotation + , origPos :: !Pos -- ^ Current output position in + -- original annotation, used to + -- calculate DPs , epComments :: ![Comment] } @@ -181,11 +191,26 @@ enterAnn NoEntryVal a = do p <- getPos debugM $ "enterAnn:NO ANN:p =" ++ show p exact a -enterAnn (Entry anchor cs) a = do +enterAnn (Entry anchor' cs) a = do + -- NOTE: in time anchor will note if it has moved, for now we assume + -- both values are the same + let topAnchor = anchor' -- To control spacing to get into this AST element + let curAnchor = anchor' -- As a base for the current AST element + -- -- ----------------------------------------------- + -- -- Advance by any discrepance between origPos and topAnchor + -- op <- getOrigPos + -- p <- getPos + -- let dp = pos2delta op (ss2pos topAnchor) + -- debugM $ "enterAnn:(op,p,topAnchor,dp)=" ++ show (op,p,rs2range topAnchor,dp) + -- advance dp + -- -- We are now cleanly in the current context + -- -- ------------------------------------------- + setAnchor curAnchor + setOrigPos (ss2pos curAnchor) -- We assume we are now aligned with the anchor + p' <- getPos addCommentsA cs - printComments anchor + printComments curAnchor p <- getPos - debugM $ "enterAnn:(anchor(pos),p)=" ++ show (ss2pos(anchor),p) -- do all the machinery of advancing to the anchor, with a local etc -- modelled on exactpc (which is normally called via withast @@ -193,16 +218,35 @@ enterAnn (Entry anchor cs) a = do -- the current position, and the anchor. -- off <- gets apLayoutStart off <- gets epLHS - priorEndAfterComments <- getPos - let ss = anchor - let edp = adjustDeltaForOffset + -- priorEndAfterComments <- getPos + let ss = curAnchor +--------------------------- + priorEndAfterComments <- getPriorEnd + priorEndAfterCommentsE <- getPriorEndE + peu <- getPriorEndU + debugM $ "enterAnn:(curAnchor,pe,pec,p,p')=" ++ show (ss2pos curAnchor,priorEndAfterComments,priorEndAfterCommentsE,p,p') +---------------------------- + -- NOTE: edp only uses the *original* ast spacing, i.e. the gap + -- between the end of the previous leaf span, and the start of the + -- next leaf span + let edp' = adjustDeltaForOffset -- Use the propagated offset if one is set -- Note that we need to use the new offset if it has -- changed. - off (ss2delta priorEndAfterComments ss) + -- off (ss2delta priorEndAfterComments ss) + off (ss2delta priorEndAfterCommentsE curAnchor) + edp = if peu /= priorEndAfterCommentsE -- new leaf node + then edp' else DP (0,0) + debugM $ "enterAnn:(p,ss,edp,pec)=" ++ show (p,ss2pos ss,edp,priorEndAfterCommentsE) + -- when (priorEndAfterComments < ss2pos ss) (do + -- modify (\s -> s { priorEndPosition = ss2pos ss + -- , priorEndPositionU = priorEndAfterCommentsE } )) + modify (\s -> s { priorEndPosition = ss2pos ss + , priorEndPositionU = priorEndAfterCommentsE } ) let st = annNone { annEntryDelta = edp } + withOffset st (advance edp >> exact a) -- --------------------------------------------------------------------- @@ -248,7 +292,7 @@ sr s = RealSrcSpan s Nothing -- Temporary function to simply reproduce the "normal" pretty printer output withPpr :: (Outputable a) => a -> Annotated () -withPpr a = printString False (showPprUnsafe a) +withPpr a = printStringAdvance (showPprUnsafe a) -- --------------------------------------------------------------------- -- Modeled on Outputable @@ -273,6 +317,7 @@ instance (ExactPrint a) => ExactPrint (Located a) where instance (ExactPrint a) => ExactPrint (LocatedA a) where getAnnotationEntry = entryFromLocatedA exact (L la a) = do + debugM $ "LocatedA a:la loc=" ++ show (ss2range $ locA la) markAnnotated a markALocatedA (ann la) @@ -301,13 +346,15 @@ instance ExactPrint HsModule where Just (L ln mn) -> do markApiAnn' an am_main AnnModule -- debugM $ "HsModule name: (ss,ln)=" ++ show (ss2pos ss,ss2pos (realSrcSpan ln)) - printStringAtSs ln (moduleNameString mn) + -- printStringAtSs ln (moduleNameString mn) + markAnnotated (L ln mn) -- forM_ mdeprec markLocated markAnnotated mdeprec markAnnotated mexports + debugM $ "HsModule.AnnWhere coming" markApiAnn' an am_main AnnWhere -- markApiAnn (am_main anns) AnnWhere @@ -334,23 +381,19 @@ instance ExactPrint HsModule where -- --------------------------------------------------------------------- printSourceText :: SourceText -> String -> EPP () -printSourceText NoSourceText txt = printString False txt -printSourceText (SourceText txt) _ = printString False txt +printSourceText NoSourceText txt = printStringAdvance txt +printSourceText (SourceText txt) _ = printStringAdvance txt -- --------------------------------------------------------------------- +printStringAtRs :: RealSrcSpan -> String -> EPP () +printStringAtRs ss str = printStringAtKw' ss str + printStringAtSs :: SrcSpan -> String -> EPP () printStringAtSs ss str = printStringAtKw' (realSrcSpan ss) str -- --------------------------------------------------------------------- --- printStringAtKw :: ApiAnn' ann -> AnnKeywordId -> String -> EPP () --- printStringAtKw ApiAnnNotUsed _ str = printString True str --- printStringAtKw (ApiAnn anchor anns _cs) kw str = do --- case find (\(AddApiAnn k _) -> k == kw) anns of --- Nothing -> printString True str --- Just (AddApiAnn _ ss) -> printStringAtKw' ss str - -- AZ:TODO get rid of this printStringAtMkw :: Maybe RealSrcSpan -> String -> EPP () printStringAtMkw (Just r) s = printStringAtKw' r s @@ -359,11 +402,35 @@ printStringAtMkw Nothing s = printStringAtLsDelta [] (DP (0,1)) s printStringAtKw' :: RealSrcSpan -> String -> EPP () printStringAtKw' ss str = do printComments ss - dp <- nextDP ss + -- dp <- nextDP ss + anchor <- getAnchor + op <- getOrigPos + dp <- nextDPAnchor ss p <- getPos - debugM $ "printStringAtKw': (dp,p) = " ++ show (dp,p) + debugM $ "printStringAtKw': (dp,p,pe,a,op) = " ++ show (dp,p,ss2posEnd ss,rs2range anchor,op) + setPriorEndE (ss2posEnd ss) + setOrigPos (ss2posEnd ss) printStringAtLsDelta [] dp str +-- | Print a string, advancing origPos by the same amount as the pos +-- advances. Complicated because the string may have newlines in it +printStringAdvance :: String -> EPP () +printStringAdvance str = do + op <- getOrigPos + p1 <- getPos + printString False str + p2 <- getPos + let dp = pos2delta p1 p2 + colOffset <- getLayoutOffset + let op2 = undelta op dp colOffset + setOrigPos op2 + +adaptPos dp = do + op <- getOrigPos + colOffset <- getLayoutOffset + let op2 = undelta op dp colOffset + setOrigPos op2 + -- --------------------------------------------------------------------- markExternalSourceText :: SrcSpan -> SourceText -> String -> EPP () @@ -418,13 +485,6 @@ markLocatedAALS (ApiAnn _ a _) f kw (Just str) = go (f a) markArrow :: ApiAnn' TrailingAnn -> (HsArrow GhcPs) -> EPP () markArrow ApiAnnNotUsed _ = pure () markArrow an mult = markKwT (anns an) - -- = case mult of - -- HsLinearArrow -> markApiAnn an AnnLolly - -- HsUnrestrictedArrow -> markApiAnn an AnnRarrow - -- HsExplicitMult p -> do - -- printString False "#" - -- markAnnotated p - -- markApiAnn an AnnRarrow -- --------------------------------------------------------------------- @@ -517,9 +577,14 @@ markKw' :: AnnKeywordId -> RealSrcSpan -> EPP () markKw' kw ss = do p' <- getPos printComments ss - dp <- nextDP ss + -- AZ:TODO instead of using nextDP, we need to use the original DP. how? + -- dp <- nextDP ss + dp <- nextDPAnchor ss p <- getPos - debugM $ "markKw: (dp,p,p') = " ++ show (dp,p,p') + anchor <- getAnchor + setPriorEndE (ss2posEnd ss) + setOrigPos (ss2posEnd ss) + debugM $ "markKw: (dp,p,p',pe,anchor) = " ++ show (dp,p,p',rs2range ss,rs2range anchor) printStringAtLsDelta [] dp (keywordToString (G kw)) -- --------------------------------------------------------------------- @@ -594,6 +659,15 @@ nextDP ss = do p <- getPos return $ pos2delta p (ss2pos ss) +nextDPAnchor :: RealSrcSpan -> EPP DeltaPos +nextDPAnchor ss = do + anchor <- getAnchor + op <- getOrigPos + let dp = pos2delta op (ss2pos ss) + -- return $ pos2delta (ss2pos anchor) (ss2pos ss) + debugM $ "nextDPAnchor:(dp,op,ss,anchor)=" ++ show (dp,op,rs2range ss,rs2range anchor) + return dp + -- --------------------------------------------------------------------- markListWithLayout :: ExactPrint (LocatedA ast) => [LocatedA ast] -> EPP () @@ -948,7 +1022,7 @@ instance ExactPrint FastString where getAnnotationEntry = const NoEntryVal -- TODO: https://ghc.haskell.org/trac/ghc/ticket/10313 applies. - exact fs = printString False (show (unpackFS fs)) + exact fs = printStringAdvance (show (unpackFS fs)) -- --------------------------------------------------------------------- @@ -1048,7 +1122,7 @@ instance ExactPrint DocDecl where (DocCommentNamed _s ds) -> unpackHDS ds (DocGroup _i ds) -> unpackHDS ds in - printString False str + printStringAdvance str -- --------------------------------------------------------------------- @@ -1426,7 +1500,7 @@ exactMatch (Match an mctxt pats grhss) = do markApiAnn an AnnLam mapM_ markAnnotated pats GHC.CaseAlt -> do - mapM_ markAnnotated pats + markAnnotated pats _ -> withPpr mctxt markAnnotated grhss @@ -1434,21 +1508,21 @@ exactMatch (Match an mctxt pats grhss) = do -- --------------------------------------------------------------------- instance ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) where - getAnnotationEntry (GRHSs an _ _) = fromAnn an + getAnnotationEntry (GRHSs _ _ _) = NoEntryVal exact (GRHSs an grhss binds) = do debugM $ "GRHSs: before matchSeparator" - markLocatedAA an id -- Mark the matchSeparator for these GRHSs + -- markLocatedAA an id -- Mark the matchSeparator for these GRHSs debugM $ "GRHSs: after matchSeparator" markAnnotated grhss markAnnotated binds instance ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) where - getAnnotationEntry (GRHSs an _ _) = fromAnn an + getAnnotationEntry (GRHSs _ _ _) = NoEntryVal exact (GRHSs an grhss binds) = do debugM $ "GRHSs: before matchSeparator" - markLocatedAA an id -- Mark the matchSeparator for these GRHSs + -- markLocatedAA an id -- Mark the matchSeparator for these GRHSs debugM $ "GRHSs: after matchSeparator" markAnnotated grhss markAnnotated binds @@ -1499,7 +1573,7 @@ instance ExactPrint (IPBind GhcPs) where instance ExactPrint HsIPName where getAnnotationEntry = const NoEntryVal - exact (HsIPName fs) = printString False ("?" ++ (unpackFS fs)) + exact (HsIPName fs) = printStringAdvance ("?" ++ (unpackFS fs)) -- --------------------------------------------------------------------- @@ -1507,7 +1581,7 @@ instance ExactPrint (HsValBindsLR GhcPs GhcPs) where getAnnotationEntry _ = NoEntryVal exact (ValBinds sortkey binds sigs) = do - -- printString False "ValBinds" + -- printStringAdvance "ValBinds" applyListAnnotations (prepareListAnnotationA (bagToList binds) ++ prepareListAnnotationA sigs @@ -1848,7 +1922,7 @@ instance ExactPrint (HsExpr GhcPs) where -- exact x@(HsRecFld{}) = withPpr x -- exact x@(HsOverLabel ann _ _) = withPpr x exact (HsIPVar _ (HsIPName n)) - = printString False ("?" ++ unpackFS n) + = printStringAdvance ("?" ++ unpackFS n) exact x@(HsOverLit ann ol) = do let str = case ol_val ol of @@ -1857,7 +1931,7 @@ instance ExactPrint (HsExpr GhcPs) where HsIsString src _ -> src -- markExternalSourceText l str "" case str of - SourceText s -> printString False s + SourceText s -> printStringAdvance s NoSourceText -> withPpr x exact (HsLit ann lit) = withPpr lit @@ -1897,9 +1971,9 @@ instance ExactPrint (HsExpr GhcPs) where exact x@(HsPar an e) = do markOpeningParen an markAnnotated e - -- debugM $ "HsPar closing paren" + debugM $ "HsPar closing paren" markClosingParen an - -- debugM $ "HsPar done" + debugM $ "HsPar done" -- exact (SectionL an expr op) = do exact (SectionR an op expr) = do @@ -2142,7 +2216,7 @@ instance ExactPrint (HsSplice GhcPs) where -- = ppr_splice empty n e empty exact (HsQuasiQuote _ _ q _ss fs) = do - printString False + printStringAdvance -- Note: Lexer.x does not provide unicode alternative. 2017-02-26 ("[" ++ (showPprUnsafe q) ++ "|" ++ (unpackFS fs) ++ "|]") @@ -2222,7 +2296,7 @@ instance ExactPrint (HsTupArg GhcPs) where exact (Present _ e) = markAnnotated e exact (Missing ApiAnnNotUsed) = return () - exact (Missing _) = printString False "," + exact (Missing _) = printStringAdvance "," -- --------------------------------------------------------------------- @@ -2402,12 +2476,12 @@ instance ExactPrint (HsCmd GhcPs) where instance (ExactPrint (LocatedA body)) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA body)) where -- instance ExactPrint (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) where - getAnnotationEntry (LastStmt _ _ _ _) = NoEntryVal + getAnnotationEntry (LastStmt _ _ _ _) = NoEntryVal getAnnotationEntry (BindStmt an _ _) = fromAnn an - getAnnotationEntry (ApplicativeStmt an _ _) = NoEntryVal - getAnnotationEntry (BodyStmt an _ _ _) = NoEntryVal + getAnnotationEntry (ApplicativeStmt _ _ _) = NoEntryVal + getAnnotationEntry (BodyStmt _ _ _ _) = NoEntryVal getAnnotationEntry (LetStmt an _) = fromAnn an - getAnnotationEntry (ParStmt an _ _ _) = NoEntryVal + getAnnotationEntry (ParStmt _ _ _ _) = NoEntryVal getAnnotationEntry (TransStmt an _ _ _ _ _ _ _ _) = fromAnn an getAnnotationEntry (RecStmt an _ _ _ _ _ _) = fromAnn an @@ -2515,7 +2589,7 @@ instance (ExactPrint (LocatedA body)) -- markTrailingSemi -- exact x = error $ "exact CmdLStmt for:" ++ showAst x - exact x = error $ "exact CmdLStmt for:" + -- exact x = error $ "exact CmdLStmt for:" -- --------------------------------------------------------------------- @@ -2690,7 +2764,7 @@ instance ExactPrint (TyClDecl GhcPs) where -- = error "extension hit for TyClDecl" -- markAST _ (GHC.XTyClDecl _) -- = error "extension hit for TyClDecl" - exact x = error $ "exact TyClDecl for:" ++ showAst x + -- exact x = error $ "exact TyClDecl for:" ++ showAst x -- --------------------------------------------------------------------- @@ -2719,7 +2793,7 @@ instance ExactPrint (FamilyDecl GhcPs) where markApiAnn an AnnWhere markApiAnn an AnnOpenC case mb_eqns of - Nothing -> printString False ".." + Nothing -> printStringAdvance ".." Just eqns -> markAnnotated eqns markApiAnn an AnnCloseC _ -> return () @@ -2887,7 +2961,7 @@ instance ExactPrint (HsType GhcPs) where getAnnotationEntry (HsWildCardTy _) = NoEntryVal - exact (HsForAllTy { hst_xforall = an + exact (HsForAllTy { hst_xforall = _an , hst_tele = tele, hst_body = ty }) = do markAnnotated tele markAnnotated ty @@ -2900,9 +2974,9 @@ instance ExactPrint (HsType GhcPs) where when (promoted == IsPromoted) $ markApiAnn an AnnSimpleQuote markAnnotated name - exact x@(HsAppTy _ t1 t2) = markAnnotated t1 >> markAnnotated t2 - exact x@(HsAppKindTy an _ _) = withPpr x - exact x@(HsFunTy an mult ty1 ty2) = do + exact (HsAppTy _ t1 t2) = markAnnotated t1 >> markAnnotated t2 + exact x@(HsAppKindTy _an _ _) = withPpr x + exact (HsFunTy an mult ty1 ty2) = do markAnnotated ty1 markArrow an mult markAnnotated ty2 @@ -2918,7 +2992,7 @@ instance ExactPrint (HsType GhcPs) where markOpeningParen an markAnnotated tys markClosingParen an - exact (HsOpTy an t1 lo t2) = do + exact (HsOpTy _an t1 lo t2) = do markAnnotated t1 markAnnotated lo markAnnotated t2 @@ -2926,14 +3000,14 @@ instance ExactPrint (HsType GhcPs) where markOpeningParen an markAnnotated ty markClosingParen an - exact x@(HsIParamTy an n t) = do + exact (HsIParamTy an n t) = do markAnnotated n markApiAnn an AnnDcolon markAnnotated t - exact (HsStarTy an isUnicode) + exact (HsStarTy _an isUnicode) = if isUnicode - then printString False "\x2605" -- Unicode star - else printString False "*" + then printStringAdvance "\x2605" -- Unicode star + else printStringAdvance "*" exact (HsKindSig an ty k) = do exact ty markApiAnn an AnnDcolon @@ -2969,7 +3043,7 @@ instance ExactPrint (HsType GhcPs) where case lit of (HsNumTy src v) -> printSourceText src (show v) (HsStrTy src v) -> printSourceText src (show v) - exact (HsWildCardTy _) = printString False "_" + exact (HsWildCardTy _) = printStringAdvance "_" exact x = error $ "missing match for HsType:" ++ showAst x -- --------------------------------------------------------------------- @@ -3076,8 +3150,10 @@ instance ExactPrint (HsSigType GhcPs) where instance ExactPrint (LocatedN RdrName) where getAnnotationEntry (L sann _) = fromAnn sann - exact (L (SrcSpanAnn ApiAnnNotUsed _) n) = do - printString False (showPprUnsafe n) + exact (L (SrcSpanAnn ApiAnnNotUsed l) n) = do + p <- getPos + debugM $ "LocatedN RdrName:NOANN: (p,l,str)=" ++ show (p,ss2range l, showPprUnsafe n) + printStringAtSs l (showPprUnsafe n) exact (L (SrcSpanAnn (ApiAnn _anchor ann _cs) ll) n) = do case ann of NameAnn a o l c t -> do @@ -3100,7 +3176,7 @@ instance ExactPrint (LocatedN RdrName) where markAnnotated (L (SrcSpanAnn name ll) n) markTrailing t NameAnnTrailing t -> do - printString False (showPprUnsafe n) + printStringAdvance (showPprUnsafe n) markTrailing t markName :: NameAdornment @@ -3133,12 +3209,12 @@ exact_condecls an cs | gadt_syntax -- In GADT syntax -- = hang (text "where") 2 (vcat (map ppr cs)) = do - -- printString False "exact_condecls:gadt" + -- printStringAdvance "exact_condecls:gadt" mapM_ markAnnotated cs | otherwise -- In H98 syntax -- = equals <+> sep (punctuate (text " |") (map ppr cs)) = do - -- printString False "exact_condecls:not gadt" + -- printStringAdvance "exact_condecls:not gadt" markApiAnn an AnnEqual mapM_ markAnnotated cs where @@ -3210,8 +3286,8 @@ instance ExactPrint (ConDecl GhcPs) where when (isJust mcxt) $ markApiAnn an AnnDarrow -- mapM_ markAnnotated args case args of - (PrefixConGADT args) -> mapM_ markAnnotated args - (RecConGADT fields) -> markAnnotated fields + (PrefixConGADT args') -> mapM_ markAnnotated args' + (RecConGADT fields) -> markAnnotated fields -- mapM_ markAnnotated (unLoc fields) markAnnotated res_ty -- markAST _ (GHC.ConDeclGADT _ lns (GHC.L l forall) qvars mbCxt args typ _) = do @@ -3315,7 +3391,7 @@ instance ExactPrint (LocatedP CType) where getAnnotationEntry = entryFromLocatedA exact (L (SrcSpanAnn ApiAnnNotUsed _) ct) = withPpr ct - exact (L (SrcSpanAnn an ll) + exact (L (SrcSpanAnn an _ll) (CType stp mh (stct,ct))) = do markAnnOpenP an stp "{-# CTYPE" case mh of @@ -3345,7 +3421,7 @@ instance ExactPrint (SourceText, RuleName) where getAnnotationEntry = const NoEntryVal exact (st, rn) - = printString False (toSourceTextWithSuffix st (unpackFS rn) "") + = printStringAdvance (toSourceTextWithSuffix st (unpackFS rn) "") -- ===================================================================== @@ -3408,7 +3484,7 @@ instance ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr Gh markAnnList an $ do -- markLocatedMAA an al_open case snocView stmts of - Just (initStmts, ls@(L _ (LastStmt _ body _ _))) -> do + Just (initStmts, ls@(L _ (LastStmt _ _body _ _))) -> do debugM $ "LocatedL [ExprLStmt: snocView" markAnnotated ls markAnnotated initStmts @@ -3459,7 +3535,7 @@ instance ExactPrint (IE GhcPs) where markApiAnn an AnnDotdot markApiAnn an AnnCloseP - exact (IEThingWith an thing wc withs flds) = do + exact (IEThingWith an thing wc withs _flds) = do markAnnotated thing markApiAnn an AnnOpenP case wc of @@ -3529,8 +3605,10 @@ instance ExactPrint (Pat GhcPs) where getAnnotationEntry (NPlusKPat an _ _ _ _ _) = fromAnn an getAnnotationEntry (SigPat an _ _) = fromAnn an - - exact (WildPat _) = printString False "_" + exact (WildPat _) = do + anchor <- getAnchor + debugM $ "WildPat:anchor=" ++ show anchor + printStringAtRs anchor "_" exact (VarPat _ n) = do -- The parser inserts a placeholder value for a record pun rhs. This must be -- filtered. @@ -3558,7 +3636,7 @@ instance ExactPrint (Pat GhcPs) where Boxed -> markApiAnn an AnnCloseP Unboxed -> markApiAnn an AnnClosePH - exact (SumPat an pat alt arity) = do + exact (SumPat an pat _alt _arity) = do markLocatedAAL an sumPatParens AnnOpenPH markAnnKwAll an sumPatVbarsBefore AnnVbar markAnnotated pat @@ -3578,7 +3656,7 @@ instance ExactPrint (Pat GhcPs) where markApiAnn an AnnRarrow markAnnotated pat exact (SplicePat _ splice) = markAnnotated splice - exact (LitPat _ lit) = printString False (hsLit2String lit) + exact (LitPat _ lit) = printStringAdvance (hsLit2String lit) exact (NPat an ol mn _) = do when (isJust mn) $ markApiAnn an AnnMinus markAnnotated ol @@ -3699,7 +3777,7 @@ instance ExactPrint (HsOverLit GhcPs) where HsIsString src _ -> src in case str of - SourceText s -> printString False s + SourceText s -> printStringAdvance s NoSourceText -> return () -- --------------------------------------------------------------------- @@ -3961,6 +4039,43 @@ getPos = gets epPos setPos :: (Monad m, Monoid w) => Pos -> EP w m () setPos l = modify (\s -> s {epPos = l}) +getPriorEnd :: (Monad m, Monoid w) => EP w m Pos +getPriorEnd = gets priorEndPosition + +getPriorEndE :: (Monad m, Monoid w) => EP w m Pos +getPriorEndE = gets priorEndPositionE + +getPriorEndU :: (Monad m, Monoid w) => EP w m Pos +getPriorEndU = gets priorEndPositionU + +getAnchor :: (Monad m, Monoid w) => EP w m RealSrcSpan +getAnchor = gets anchorSpan + +getOrigPos :: (Monad m, Monoid w) => EP w m Pos +getOrigPos = gets origPos + +setPriorEnd :: (Monad m, Monoid w) => Pos -> EP w m () +setPriorEnd pe = + modify (\s -> s { priorEndPosition = pe }) + +setPriorEndE :: (Monad m, Monoid w) => Pos -> EP w m () +setPriorEndE pe = + modify (\s -> s { priorEndPositionE = pe }) + +setPriorEndU :: (Monad m, Monoid w) => Pos -> EP w m () +setPriorEndU pe = + modify (\s -> s { priorEndPositionU = pe }) + +setAnchor :: (Monad m, Monoid w) => RealSrcSpan -> EP w m () +setAnchor rss = do + debugM $ "setAnchor:" ++ show (rs2range rss) + modify (\s -> s { anchorSpan = rss }) + +setOrigPos :: (Monad m, Monoid w) => Pos -> EP w m () +setOrigPos p = do + debugM $ "setOrigPos:" ++ show p + modify (\s -> s { origPos = p }) + getUnallocatedComments :: (Monad m, Monoid w) => EP w m [Comment] getUnallocatedComments = gets epComments @@ -4014,7 +4129,7 @@ advance :: (Monad m, Monoid w) => DeltaPos -> EP w m () advance cl = do p <- getPos colOffset <- getLayoutOffset - debugM $ "advance:(p,colOffset,ws)=" ++ show (p,colOffset,undelta p cl colOffset) + debugM $ "advance:(p,cl,colOffset,ws)=" ++ show (p,cl,colOffset,undelta p cl colOffset) printWhitespace (undelta p cl colOffset) -- getAndRemoveAnnotation :: (Monad m, Monoid w, Data a) => GHC.Located a -> EP w m (Maybe Annotation) @@ -4034,9 +4149,6 @@ adjustDeltaForOffset (LayoutStartCol colOffset) (DP (l,c)) = DP (l,c - colOffset -- --------------------------------------------------------------------- -- Printing functions - - - printString :: (Monad m, Monoid w) => Bool -> String -> EP w m () printString layout str = do EPState{epPos = (_,c), epMarkLayout} <- get ===================================== utils/check-exact/src/Utils.hs ===================================== @@ -37,6 +37,7 @@ import GHC.Types.Name import GHC.Types.Name.Reader import GHC.Types.SrcLoc import GHC.Driver.Ppr +import GHC.Data.FastString -- import GHC.Types.Var -- import GHC.Types.Name.Occurrence @@ -164,6 +165,22 @@ ss2pos ss = (srcSpanStartLine ss,srcSpanStartCol ss) ss2posEnd :: RealSrcSpan -> Pos ss2posEnd ss = (srcSpanEndLine ss,srcSpanEndCol ss) +ss2range :: SrcSpan -> (Pos,Pos) +ss2range ss = (ss2pos $ rs ss, ss2posEnd $ rs ss) + +rs2range :: RealSrcSpan -> (Pos,Pos) +rs2range ss = (ss2pos ss, ss2posEnd ss) + +rs :: SrcSpan -> RealSrcSpan +rs (RealSrcSpan s _) = s +rs _ = badRealSrcSpan + +badRealSrcSpan :: RealSrcSpan +badRealSrcSpan = mkRealSrcSpan bad bad + where + bad = mkRealSrcLoc (fsLit "ghc-exactprint-nospan") 0 0 + + -- srcSpanEndColumn :: SrcSpan -> Int -- srcSpanEndColumn (RealSrcSpan s) = srcSpanEndCol s -- srcSpanEndColumn _ = 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b5fe6860a300604a43059d372ac56b504a9d704e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b5fe6860a300604a43059d372ac56b504a9d704e 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 Fri Nov 20 01:41:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 19 Nov 2020 20:41:38 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/base-no-foreignptr Message-ID: <5fb71ed22991a_36a73fd2f1d864003038a7@gitlab.mail> Ben Gamari pushed new branch wip/base-no-foreignptr at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/base-no-foreignptr 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 Fri Nov 20 07:08:42 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:08:42 -0500 Subject: [Git][ghc/ghc][master] Export indexError from GHC.Ix (#18579) Message-ID: <5fb76b7adf7e8_36a71600f92c3104be@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: Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - [...] Content analysis details: (5.0 points, 5.0 required) pts rule name description ---- ---------------------- -------------------------------------------------- 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.8 RDNS_NONE Delivered to internal network by a host with no rDNS 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: Marge Bot Subject: [Git][ghc/ghc][master] Export indexError from GHC.Ix (#18579) Date: Fri, 20 Nov 2020 02:08:42 -0500 Size: 12040 URL: From gitlab at gitlab.haskell.org Fri Nov 20 07:09:22 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:09:22 -0500 Subject: [Git][ghc/ghc][master] Clarify interruptible FFI wrt masking state Message-ID: <5fb76ba294792_36a73fd2f1fdd7f8313570@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 1 changed file: - docs/users_guide/exts/ffi.rst Changes: ===================================== docs/users_guide/exts/ffi.rst ===================================== @@ -330,9 +330,10 @@ be annotated with ``interruptible`` instead of ``safe`` or ``unsafe``: :: "sleep" sleepBlock :: CUint -> IO CUint ``interruptible`` behaves exactly as ``safe``, except that when a -``throwTo`` is directed at a thread in an interruptible foreign call, an -OS-specific mechanism will be used to attempt to cause the foreign call -to return: +``throwTo`` is directed at a thread in an interruptible foreign call, +irrespective of the masking state, the exception is added to the blocked +exceptions queue of the target thread and an OS-specific mechanism will be +used to attempt to cause the foreign call to return: Unix systems The thread making the foreign call is sent a ``SIGPIPE`` signal @@ -348,7 +349,9 @@ Windows systems Once the system call is successfully interrupted, the surrounding code must return control out of the ``foreign import``, back into Haskell code, -so that the ``throwTo`` Haskell exception can be raised there. +so that any blocked exception can be raised if the masking state +of the thread allows it. Being under mask gives the Haskell code an opportunity +to detect and react to the interrupt error code from the c call. If the foreign code simply retries the system call directly without returning back to Haskell, then the intended effect of `interruptible` disappears View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b57845c3d80f5bed8f498f27fb7a318f2b2f8b2c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b57845c3d80f5bed8f498f27fb7a318f2b2f8b2c 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 Fri Nov 20 07:10:00 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:10:00 -0500 Subject: [Git][ghc/ghc][master] 3 commits: Fix strictness signatures of `prefetchValue*#` primops Message-ID: <5fb76bc8e7a0_36a73fd2f1d86400318854@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id.hs - compiler/GHC/Types/Id/Info.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/exts/instances.rst - docs/users_guide/using-optimisation.rst - testsuite/tests/arityanal/should_compile/Arity01.stderr - testsuite/tests/arityanal/should_compile/Arity02.stderr - testsuite/tests/arityanal/should_compile/Arity03.stderr - testsuite/tests/arityanal/should_compile/Arity04.stderr - testsuite/tests/arityanal/should_compile/Arity05.stderr - testsuite/tests/arityanal/should_compile/Arity09.stderr - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity14.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b57845c3d80f5bed8f498f27fb7a318f2b2f8b2c...3a55b3a2574f913d046f3a6f82db48d7f6df32e3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b57845c3d80f5bed8f498f27fb7a318f2b2f8b2c...3a55b3a2574f913d046f3a6f82db48d7f6df32e3 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 Fri Nov 20 07:10:39 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:10:39 -0500 Subject: [Git][ghc/ghc][master] Find hadrian location more reliably in cabal-install output Message-ID: <5fb76bef425a8_36a71579be443219fb@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 1 changed file: - validate Changes: ===================================== validate ===================================== @@ -165,7 +165,7 @@ else then hadrian/build --help > /dev/null cd hadrian - hadrian_cmd=$(cabal new-exec -- which hadrian) + hadrian_cmd=$(cabal new-exec -- which hadrian | grep 'hadrian$') else if [ $no_clean -eq 0 ]; then rm -rf hadrian/.stack-work View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc963932018ccf5445613ec0932d726b51887769 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc963932018ccf5445613ec0932d726b51887769 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 Fri Nov 20 07:11:14 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:11:14 -0500 Subject: [Git][ghc/ghc][master] rts/linker: Align bssSize to page size when mapping symbol extras Message-ID: <5fb76c12e04f6_36a73fd2f208ef8032466a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - 1 changed file: - rts/linker/SymbolExtras.c Changes: ===================================== rts/linker/SymbolExtras.c ===================================== @@ -77,7 +77,9 @@ int ocAllocateExtras(ObjectCode* oc, int count, int first, int bssSize) /* N.B. We currently can't mark symbol extras as non-executable in this * case. */ size_t n = roundUpToPage(oc->fileSize); - bssSize = roundUpToAlign(bssSize, 8); + // round bssSize up to the nearest page size since we need to ensure that + // symbol_extras is aligned to a page boundary so it can be mprotect'd. + bssSize = roundUpToPage(bssSize); size_t allocated_size = n + bssSize + extras_size; void *new = mmapForLinker(allocated_size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); if (new) { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251 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 Fri Nov 20 07:11:51 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:11:51 -0500 Subject: [Git][ghc/ghc][master] 2 commits: gitlab-ci: Add usage message to ci.sh Message-ID: <5fb76c37330d1_36a73fd2f1d864003275aa@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -2,6 +2,8 @@ # shellcheck disable=SC2230 # This is the primary driver of the GitLab CI infrastructure. +# Run `ci.sh usage` for usage information. + set -e -o pipefail @@ -17,6 +19,62 @@ fi source $TOP/.gitlab/common.sh +function usage() { + cat < /dev/null; then @@ -341,6 +399,11 @@ function build_make() { if [[ -z "$BIN_DIST_PREP_TAR_COMP" ]]; then fail "BIN_DIST_PREP_TAR_COMP is not set" fi + if [[ -n "$VERBOSE" ]]; then + MAKE_ARGS="$MAKE_ARGS V=1" + else + MAKE_ARGS="$MAKE_ARGS V=0" + fi echo "include mk/flavours/${BUILD_FLAVOUR}.mk" > mk/build.mk echo 'GhcLibHcOpts+=-haddock' >> mk/build.mk @@ -434,6 +497,7 @@ function clean() { function run_hadrian() { if [ -z "$BIGNUM_BACKEND" ]; then BIGNUM_BACKEND="gmp"; fi + if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi run hadrian/build-cabal \ --flavour="$BUILD_FLAVOUR" \ -j"$cores" \ @@ -476,6 +540,7 @@ esac set_toolchain_paths case $1 in + usage) usage ;; setup) setup && cleanup_submodules ;; configure) configure ;; build_make) build_make ;; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251...802e9180dd9a9a88c4e8869f0de1048e1edd6343 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251...802e9180dd9a9a88c4e8869f0de1048e1edd6343 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 Fri Nov 20 07:42:49 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 02:42:49 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 18 commits: Export indexError from GHC.Ix (#18579) Message-ID: <5fb7737994b7f_36a715ae31b033274c@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - fd944acd by Ben Gamari at 2020-11-20T02:42:33-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 04f339c4 by Ben Gamari at 2020-11-20T02:42:33-05:00 testsuite: Refactor CountParserDeps - - - - - b432e24d by Ben Gamari at 2020-11-20T02:42:33-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - c62d03d0 by Ben Gamari at 2020-11-20T02:42:33-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 753e50df by Sylvain Henry at 2020-11-20T02:42:38-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 676df3e3 by Sylvain Henry at 2020-11-20T02:42:38-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - 48348e9a by Ryan Scott at 2020-11-20T02:42:38-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - fdeefbc2 by Ben Gamari at 2020-11-20T02:42:39-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 3188122f by Ben Gamari at 2020-11-20T02:42:39-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/841b0fdfaeab70319926ee743969d8a1e4d40d1e...3188122f6111c21151381f014837b5ea80eb5a5c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/841b0fdfaeab70319926ee743969d8a1e4d40d1e...3188122f6111c21151381f014837b5ea80eb5a5c 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 Fri Nov 20 08:35:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 20 Nov 2020 03:35:30 -0500 Subject: [Git][ghc/ghc][ghc-8.10] 3 commits: macOS: Load frameworks without stating them first. Message-ID: <5fb77fd266f91_36a73fd2f208ef80340974@gitlab.mail> Ben Gamari pushed to branch ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: 3571cc41 by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - 57b5f130 by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 07c5acae by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - 1 changed file: - compiler/ghci/Linker.hs Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1679,6 +1679,38 @@ addEnvPaths name list -- ---------------------------------------------------------------------------- -- Loading a dynamic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32) +{- +Note [macOS Big Sur dynamic libraries] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +macOS Big Sur makes the following change to how frameworks are shipped +with the OS: + +> New in macOS Big Sur 11 beta, the system ships with a built-in +> dynamic linker cache of all system-provided libraries. As part of +> this change, copies of dynamic libraries are no longer present on +> the filesystem. Code that attempts to check for dynamic library +> presence by looking for a file at a path or enumerating a directory +> will fail. Instead, check for library presence by attempting to +> dlopen() the path, which will correctly check for the library in the +> cache. (62986286) + +(https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/) + +Therefore, the previous method of checking whether a library exists +before attempting to load it makes GHC.Runtime.Linker.loadFramework +fail to find frameworks installed at /System/Library/Frameworks. +Instead, any attempt to load a framework at runtime, such as by +passing -framework OpenGL to runghc or running code loading such a +framework with GHCi, fails with a 'not found' message. + +GHC.Runtime.Linker.loadFramework now opportunistically loads the +framework libraries without checking for their existence first, +failing only if all attempts to load a given framework from any of the +various possible locations fail. See also #18446, which this change +addresses. +-} + -- Darwin / MacOS X only: load a framework -- a framework is a dynamic library packaged inside a directory of the same -- name. They are searched for in different paths than normal libraries. @@ -1689,17 +1721,29 @@ loadFramework hsc_env extraPaths rootname Left _ -> [] Right dir -> [dir "Library/Frameworks"] ps = extraPaths ++ homeFrameworkPath ++ defaultFrameworkPaths - ; mb_fwk <- findFile ps fwk_file - ; case mb_fwk of - Just fwk_path -> loadDLL hsc_env fwk_path - Nothing -> return (Just "not found") } - -- Tried all our known library paths, but dlopen() - -- has no built-in paths for frameworks: give up + ; errs <- findLoadDLL ps [] + ; return $ fmap (intercalate ", ") errs + } where fwk_file = rootname <.> "framework" rootname - -- sorry for the hardcoded paths, I hope they won't change anytime soon: + + -- sorry for the hardcoded paths, I hope they won't change anytime soon: defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"] + -- Try to call loadDLL for each candidate path. + -- + -- See Note [macOS Big Sur dynamic libraries] + findLoadDLL [] errs = + -- Tried all our known library paths, but dlopen() + -- has no built-in paths for frameworks: give up + return $ Just errs + findLoadDLL (p:ps) errs = + do { dll <- loadDLL hsc_env (p fwk_file) + ; case dll of + Nothing -> return Nothing + Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs) + } + {- ********************************************************************** Helper functions View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65be3832f3aa48bbde896ee846c18fcba1f16b42...07c5acae150f8b8ed79275ab12774eda58979c69 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65be3832f3aa48bbde896ee846c18fcba1f16b42...07c5acae150f8b8ed79275ab12774eda58979c69 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 Fri Nov 20 08:48:13 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Fri, 20 Nov 2020 03:48:13 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18885 Message-ID: <5fb782cdabd66_36a71579be44341534@gitlab.mail> Sebastian Graf pushed new branch wip/T18885 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18885 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 Fri Nov 20 09:49:12 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Fri, 20 Nov 2020 04:49:12 -0500 Subject: [Git][ghc/ghc][wip/amg/renamer-refactor] 2 commits: Fix Makefile for new DRFPatSynExport test Message-ID: <5fb7911860962_36a73fd2ff413ea03435e0@gitlab.mail> Adam Gundry pushed to branch wip/amg/renamer-refactor at Glasgow Haskell Compiler / GHC Commits: 818c2895 by Adam Gundry at 2020-11-20T09:39:31+00:00 Fix Makefile for new DRFPatSynExport test - - - - - 13d13a60 by Adam Gundry at 2020-11-20T09:48:27+00:00 Remove an unused extension - - - - - 3 changed files: - compiler/GHC/Hs/Binds.hs - testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport.stdout - testsuite/tests/overloadedrecflds/should_compile/Makefile Changes: ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -5,7 +5,6 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} -- Wrinkle in Note [Trees That Grow] ===================================== testsuite/tests/overloadedrecflds/should_compile/DRFPatSynExport.stdout ===================================== @@ -1,3 +1 @@ -[1 of 2] Compiling DRFPatSynExport_A ( DRFPatSynExport_A.hs, DRFPatSynExport_A.o ) -[2 of 2] Compiling DRFPatSynExport ( DRFPatSynExport.hs, DRFPatSynExport.o ) import DRFPatSynExport_A ( MkT, m ) ===================================== testsuite/tests/overloadedrecflds/should_compile/Makefile ===================================== @@ -1,3 +1,10 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + DRFPatSynExport: - '$(TEST_HC)' $(TEST_HC_OPTS) DRFPatSynExport.hs -fforce-recomp -ddump-minimal-imports + $(RM) DRFPatSynExport.hi DRFPatSynExport.o DRFPatSynExport.imports + $(RM) DRFPatSynExport_A.hi DRFPatSynExport_A.o + '$(TEST_HC)' $(TEST_HC_OPTS) -c DRFPatSynExport_A.hs + '$(TEST_HC)' $(TEST_HC_OPTS) -c DRFPatSynExport.hs -ddump-minimal-imports cat DRFPatSynExport.imports View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6d41ff494ef93d5dadc53f0842f109146f36760...13d13a60c0ebc63adc0432f6fac835023c09a3a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6d41ff494ef93d5dadc53f0842f109146f36760...13d13a60c0ebc63adc0432f6fac835023c09a3a3 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 Fri Nov 20 13:13:18 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 20 Nov 2020 08:13:18 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: users-guide: A bit of clean-up in profiling flag documentation Message-ID: <5fb7c0ee29225_36a7643e30037287@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c4ba4207 by Ben Gamari at 2020-11-20T08:13:01-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - fcde3801 by Ben Gamari at 2020-11-20T08:13:01-05:00 testsuite: Refactor CountParserDeps - - - - - 202ae646 by Ben Gamari at 2020-11-20T08:13:01-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 696807e5 by Sylvain Henry at 2020-11-20T08:13:06-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 2cc09bd9 by Sylvain Henry at 2020-11-20T08:13:06-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - dd0c3b63 by Ryan Scott at 2020-11-20T08:13:07-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a9ec11f1 by Ben Gamari at 2020-11-20T08:13:08-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 412fd500 by Ben Gamari at 2020-11-20T08:13:08-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/extending_ghc.rst - docs/users_guide/profiling.rst - ghc/GHCi/UI.hs - ghc/Main.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3188122f6111c21151381f014837b5ea80eb5a5c...412fd5000d947b6bb7f4285cb58936295a9b426f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3188122f6111c21151381f014837b5ea80eb5a5c...412fd5000d947b6bb7f4285cb58936295a9b426f 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 Fri Nov 20 16:02:15 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 20 Nov 2020 11:02:15 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 3 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fb7e8875c4ca_36a7643e3003885db@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 4fd06dd5 by Moritz Angermann at 2020-11-19T21:21:26-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Metric Increase: T13701 - - - - - 1472ce77 by Ben Gamari at 2020-11-20T11:01:11-05:00 Fix unreg - - - - - e286eeb9 by Ben Gamari at 2020-11-20T11:01:15-05:00 Outputable instances - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/base/base.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c4f9fdc97e4cc9c5e7b91820ead844344fce9354...e286eeb9c0020c7b83185b07e96575ece01d8c41 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c4f9fdc97e4cc9c5e7b91820ead844344fce9354...e286eeb9c0020c7b83185b07e96575ece01d8c41 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 Fri Nov 20 22:33:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 20 Nov 2020 17:33:44 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/dump-c Message-ID: <5fb8444860fef_36a7643e30044493b@gitlab.mail> Ben Gamari pushed new branch wip/dump-c at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/dump-c 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 Fri Nov 20 22:35:53 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 20 Nov 2020 17:35:53 -0500 Subject: [Git][ghc/ghc][wip/dump-c] Implement -ddump-c-backend argument Message-ID: <5fb844c95f2_36a73fd2ff413ea044879d@gitlab.mail> Ben Gamari pushed to branch wip/dump-c at Glasgow Haskell Compiler / GHC Commits: 612b4f9a by Ben Gamari at 2020-11-20T17:35:46-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 4 changed files: - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debugging.rst Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -138,7 +138,13 @@ outputC dflags filenm cmm_stream packages = hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n") hPutStr h "#include \"Stg.h\"\n" let platform = targetPlatform dflags - writeC = printForC dflags h . cmmToC platform + writeC cmm = do + let doc = cmmToC platform cmm + dumpIfSet_dyn dflags Opt_D_dump_c_backend + "C backend output" + FormatC + doc + printForC dflags h doc Stream.consume cmm_stream writeC {- ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -49,6 +49,7 @@ data DumpFlag | Opt_D_dump_asm_conflicts | Opt_D_dump_asm_stats | Opt_D_dump_asm_expanded + | Opt_D_dump_c_backend | Opt_D_dump_llvm | Opt_D_dump_core_stats | Opt_D_dump_deriv ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2551,6 +2551,8 @@ dynamic_flags_deps = [ (setDumpFlag Opt_D_dump_asm_expanded) , make_ord_flag defGhcFlag "ddump-llvm" (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm) + , make_ord_flag defGhcFlag "ddump-c-backend" + (NoArg $ setDumpFlag' Opt_D_dump_c_backend) , make_ord_flag defGhcFlag "ddump-deriv" (setDumpFlag Opt_D_dump_deriv) , make_ord_flag defGhcFlag "ddump-ds" ===================================== docs/users_guide/debugging.rst ===================================== @@ -547,6 +547,15 @@ LLVM code generator LLVM code from the :ref:`LLVM code generator ` +C code generator +~~~~~~~~~~~~~~~~ + +.. ghc-flag:: -ddump-c-backend + :shortdesc: Dump C code produced by the C (unregisterised) backend. + :type: dynamic + + :shortdesc: Dump C code produced by the C (unregisterised) backend. + Native code generator ~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/612b4f9a296cf6634a3e85ab16befe1435f64fc6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/612b4f9a296cf6634a3e85ab16befe1435f64fc6 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 Fri Nov 20 23:57:58 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 20 Nov 2020 18:57:58 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 13 commits: Add Addr# atomic primops (#17751) Message-ID: <5fb85806eaa56_36a73fd2caa64b9045324f@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 4cd5408f by Moritz Angermann at 2020-11-20T18:57:24-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 - - - - - 0949e4e4 by Ben Gamari at 2020-11-20T18:57:36-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Pmc.hs - compiler/GHC/HsToCore/Pmc/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e286eeb9c0020c7b83185b07e96575ece01d8c41...0949e4e4f5c903ce24ba5e7c1e58e76ed2e0b8b8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e286eeb9c0020c7b83185b07e96575ece01d8c41...0949e4e4f5c903ce24ba5e7c1e58e76ed2e0b8b8 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 Sat Nov 21 06:13:36 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 01:13:36 -0500 Subject: [Git][ghc/ghc][master] 3 commits: users-guide: A bit of clean-up in profiling flag documentation Message-ID: <5fb8b010e61d4_36a73fd2f1fdd7f8476777@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - 20 changed files: - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/profiling.rst - testsuite/tests/parser/should_run/CountParserDeps.hs - + testsuite/tests/parser/should_run/CountParserDeps.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample - + testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout - + testsuite/tests/profiling/should_run/caller-cc/Main.hs - + testsuite/tests/profiling/should_run/caller-cc/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -355,6 +355,7 @@ coreDumpFlag CoreTidy = Just Opt_D_dump_simpl coreDumpFlag CorePrep = Just Opt_D_dump_prep coreDumpFlag CoreOccurAnal = Just Opt_D_dump_occur_anal +coreDumpFlag CoreAddCallerCcs = Nothing coreDumpFlag CoreDoPrintCore = Nothing coreDumpFlag (CoreDoRuleCheck {}) = Nothing coreDumpFlag CoreDoNothing = Nothing ===================================== compiler/GHC/Core/Opt/CallerCC.hs ===================================== @@ -0,0 +1,223 @@ +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveAnyClass #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE TupleSections #-} + +-- | Adds cost-centers to call sites selected with the @-fprof-caller=...@ +-- flag. +module GHC.Core.Opt.CallerCC + ( addCallerCostCentres + , CallerCcFilter + , parseCallerCcFilter + ) where + +import Data.Bifunctor +import Data.Word (Word8) +import Data.Maybe +import qualified Text.Parsec as P + +import Control.Applicative +import Control.Monad.Trans.State.Strict +import Data.Either +import Control.Monad + +import GHC.Prelude +import GHC.Utils.Outputable as Outputable +import GHC.Driver.Session +import GHC.Driver.Ppr +import GHC.Types.CostCentre +import GHC.Types.CostCentre.State +import GHC.Types.Name hiding (varName) +import GHC.Unit.Module.Name +import GHC.Unit.Module.ModGuts +import GHC.Types.SrcLoc +import GHC.Types.Var +import GHC.Unit.Types +import GHC.Data.FastString +import GHC.Core +import GHC.Core.Opt.Monad +import GHC.Utils.Panic +import qualified GHC.Utils.Binary as B + +addCallerCostCentres :: ModGuts -> CoreM ModGuts +addCallerCostCentres guts = do + dflags <- getDynFlags + let filters = callerCcFilters dflags + let env :: Env + env = Env + { thisModule = mg_module guts + , ccState = newCostCentreState + , dflags = dflags + , revParents = [] + , filters = filters + } + let guts' = guts { mg_binds = doCoreProgram env (mg_binds guts) + } + return guts' + +doCoreProgram :: Env -> CoreProgram -> CoreProgram +doCoreProgram env binds = flip evalState newCostCentreState $ do + mapM (doBind env) binds + +doBind :: Env -> CoreBind -> M CoreBind +doBind env (NonRec b rhs) = NonRec b <$> doExpr (addParent b env) rhs +doBind env (Rec bs) = Rec <$> mapM doPair bs + where + doPair (b,rhs) = (b,) <$> doExpr (addParent b env) rhs + +doExpr :: Env -> CoreExpr -> M CoreExpr +doExpr env e@(Var v) + | needsCallSiteCostCentre env v = do + let nameDoc :: SDoc + nameDoc = withUserStyle alwaysQualify DefaultDepth $ + hcat (punctuate dot (map ppr (parents env))) <> parens (text "calling:" <> ppr v) + + ccName :: CcName + ccName = mkFastString $ showSDoc (dflags env) nameDoc + ccIdx <- getCCIndex' ccName + let span = case revParents env of + top:_ -> nameSrcSpan $ varName top + _ -> noSrcSpan + cc = NormalCC (ExprCC ccIdx) ccName (thisModule env) span + tick :: Tickish Id + tick = ProfNote cc True True + pure $ Tick tick e + | otherwise = pure e +doExpr _env e@(Lit _) = pure e +doExpr env (f `App` x) = App <$> doExpr env f <*> doExpr env x +doExpr env (Lam b x) = Lam b <$> doExpr env x +doExpr env (Let b rhs) = Let <$> doBind env b <*> doExpr env rhs +doExpr env (Case scrut b ty alts) = + Case <$> doExpr env scrut <*> pure b <*> pure ty <*> mapM doAlt alts + where + doAlt (con, bs, rhs) = (con, bs,) <$> doExpr env rhs +doExpr env (Cast expr co) = Cast <$> doExpr env expr <*> pure co +doExpr env (Tick t e) = Tick t <$> doExpr env e +doExpr _env e@(Type _) = pure e +doExpr _env e@(Coercion _) = pure e + +type M = State CostCentreState + +getCCIndex' :: FastString -> M CostCentreIndex +getCCIndex' name = state (getCCIndex name) + +data Env = Env + { thisModule :: Module + , dflags :: DynFlags + , ccState :: CostCentreState + , revParents :: [Id] + , filters :: [CallerCcFilter] + } + +addParent :: Id -> Env -> Env +addParent i env = env { revParents = i : revParents env } + +parents :: Env -> [Id] +parents env = reverse (revParents env) + +needsCallSiteCostCentre :: Env -> Id -> Bool +needsCallSiteCostCentre env i = + any matches (filters env) + where + matches :: CallerCcFilter -> Bool + matches ccf = + checkModule && checkFunc + where + checkModule = + case ccfModuleName ccf of + Just modFilt + | Just iMod <- nameModule_maybe (varName i) + -> moduleName iMod == modFilt + | otherwise -> False + Nothing -> True + checkFunc = + occNameMatches (ccfFuncName ccf) (getOccName i) + +data NamePattern + = PChar Char NamePattern + | PWildcard NamePattern + | PEnd + +instance Outputable NamePattern where + ppr (PChar c rest) = char c <> ppr rest + ppr (PWildcard rest) = char '*' <> ppr rest + ppr PEnd = Outputable.empty + +instance B.Binary NamePattern where + get bh = do + tag <- B.get bh + case tag :: Word8 of + 0 -> PChar <$> B.get bh <*> B.get bh + 1 -> PWildcard <$> B.get bh + 2 -> pure PEnd + _ -> panic "Binary(NamePattern): Invalid tag" + put_ bh (PChar x y) = B.put_ bh (0 :: Word8) >> B.put_ bh x >> B.put_ bh y + put_ bh (PWildcard x) = B.put_ bh (1 :: Word8) >> B.put_ bh x + put_ bh PEnd = B.put_ bh (2 :: Word8) + +occNameMatches :: NamePattern -> OccName -> Bool +occNameMatches pat = go pat . occNameString + where + go :: NamePattern -> String -> Bool + go PEnd "" = True + go (PChar c rest) (d:s) + = d == c && go rest s + go (PWildcard rest) s + = go rest s || go (PWildcard rest) (tail s) + go _ _ = False + +type Parser = P.Parsec String () + +parseNamePattern :: Parser NamePattern +parseNamePattern = pattern + where + pattern = star <|> wildcard <|> char <|> end + star = PChar '*' <$ P.string "\\*" <*> pattern + wildcard = do + void $ P.char '*' + PWildcard <$> pattern + char = PChar <$> P.anyChar <*> pattern + end = PEnd <$ P.eof + +data CallerCcFilter + = CallerCcFilter { ccfModuleName :: Maybe ModuleName + , ccfFuncName :: NamePattern + } + +instance Outputable CallerCcFilter where + ppr ccf = + maybe (char '*') ppr (ccfModuleName ccf) + <> char '.' + <> ppr (ccfFuncName ccf) + +instance B.Binary CallerCcFilter where + get bh = CallerCcFilter <$> B.get bh <*> B.get bh + put_ bh (CallerCcFilter x y) = B.put_ bh x >> B.put_ bh y + +parseCallerCcFilter :: String -> Either String CallerCcFilter +parseCallerCcFilter = + first show . P.parse parseCallerCcFilter' "caller-CC filter" + +parseCallerCcFilter' :: Parser CallerCcFilter +parseCallerCcFilter' = + CallerCcFilter + <$> moduleFilter + <* P.char '.' + <*> parseNamePattern + where + moduleFilter :: Parser (Maybe ModuleName) + moduleFilter = + (Just . mkModuleName <$> moduleName) + <|> + (Nothing <$ P.char '*') + + moduleName :: Parser String + moduleName = do + c <- P.upper + cs <- some $ P.upper <|> P.lower <|> P.digit <|> P.oneOf "_" + rest <- optional $ P.try $ P.char '.' >> fmap ('.':) moduleName + return $ c : (cs ++ fromMaybe "" rest) + ===================================== compiler/GHC/Core/Opt/CallerCC.hs-boot ===================================== @@ -0,0 +1,8 @@ +module GHC.Core.Opt.CallerCC where + +import GHC.Prelude + +-- Necessary due to import in GHC.Driver.Session. +data CallerCcFilter + +parseCallerCcFilter :: String -> Either String CallerCcFilter ===================================== compiler/GHC/Core/Opt/Monad.hs ===================================== @@ -129,6 +129,7 @@ data CoreToDo -- These are diff core-to-core passes, | CoreTidy | CorePrep + | CoreAddCallerCcs | CoreOccurAnal instance Outputable CoreToDo where @@ -149,6 +150,7 @@ instance Outputable CoreToDo where ppr CoreDesugar = text "Desugar (before optimization)" ppr CoreDesugarOpt = text "Desugar (after optimization)" ppr CoreTidy = text "Tidy Core" + ppr CoreAddCallerCcs = text "Add caller cost-centres" ppr CorePrep = text "CorePrep" ppr CoreOccurAnal = text "Occurrence analysis" ppr CoreDoPrintCore = text "Print core" ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -16,6 +16,7 @@ import GHC.Driver.Session import GHC.Driver.Ppr import GHC.Driver.Plugins ( withPlugins, installCoreToDos ) import GHC.Driver.Env +import GHC.Platform.Ways ( hasWay, Way(WayProf) ) import GHC.Core import GHC.Core.Opt.CSE ( cseProgram ) @@ -44,6 +45,7 @@ import GHC.Core.Opt.CprAnal ( cprAnalProgram ) import GHC.Core.Opt.CallArity ( callArityAnalProgram ) import GHC.Core.Opt.Exitify ( exitifyProgram ) import GHC.Core.Opt.WorkWrap ( wwTopBinds ) +import GHC.Core.Opt.CallerCC ( addCallerCostCentres ) import GHC.Core.Seq (seqBinds) import GHC.Core.FamInstEnv @@ -155,6 +157,7 @@ getCoreToDo dflags pre_inline_on = gopt Opt_SimplPreInlining dflags ww_on = gopt Opt_WorkerWrapper dflags static_ptrs = xopt LangExt.StaticPointers dflags + profiling = ways dflags `hasWay` WayProf maybe_rule_check phase = runMaybe rule_check (CoreDoRuleCheck phase) @@ -221,12 +224,16 @@ getCoreToDo dflags } ] + add_caller_ccs = + runWhen (profiling && not (null $ callerCcFilters dflags)) CoreAddCallerCcs + core_todo = if opt_level == 0 then [ static_ptrs_float_outwards, CoreDoSimplify max_iter (base_mode { sm_phase = FinalPhase , sm_names = ["Non-opt simplification"] }) + , add_caller_ccs ] else {- opt_level >= 1 -} [ @@ -370,7 +377,9 @@ getCoreToDo dflags -- can become /exponentially/ more expensive. See #11731, #12996. runWhen (strictness || late_dmd_anal) CoreDoDemand, - maybe_rule_check FinalPhase + maybe_rule_check FinalPhase, + + add_caller_ccs ] -- Remove 'CoreDoNothing' and flatten 'CoreDoPasses' for clarity. @@ -509,6 +518,9 @@ doCorePass CoreDoSpecialising = {-# SCC "Specialise" #-} doCorePass CoreDoSpecConstr = {-# SCC "SpecConstr" #-} specConstrProgram +doCorePass CoreAddCallerCcs = {-# SCC "AddCallerCcs" #-} + addCallerCostCentres + doCorePass CoreDoPrintCore = observe printCore doCorePass (CoreDoRuleCheck phase pat) = ruleCheckPass phase pat doCorePass CoreDoNothing = return ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -263,6 +263,7 @@ import GHC.Utils.Fingerprint import GHC.Utils.Outputable import GHC.Settings import GHC.CmmToAsm.CFG.Weight +import {-# SOURCE #-} GHC.Core.Opt.CallerCC import GHC.Types.Error import {-# SOURCE #-} GHC.Utils.Error @@ -699,6 +700,7 @@ data DynFlags = DynFlags { -- | what kind of {-# SCC #-} to add automatically profAuto :: ProfAuto, + callerCcFilters :: [CallerCcFilter], interactivePrint :: Maybe String, @@ -1313,6 +1315,7 @@ defaultDynFlags mySettings llvmConfig = canUseColor = False, colScheme = Col.defaultScheme, profAuto = NoProfAuto, + callerCcFilters = [], interactivePrint = Nothing, nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum", sseVersion = Nothing, @@ -2947,6 +2950,10 @@ dynamic_flags_deps = [ , make_ord_flag defGhcFlag "fno-prof-auto" (noArg (\d -> d { profAuto = NoProfAuto } )) + -- Caller-CC + , make_ord_flag defGhcFlag "fprof-callers" + (HasArg setCallerCcFilters) + ------ Compiler flags ----------------------------------------------- , make_ord_flag defGhcFlag "fasm" (NoArg (setObjBackend NCG)) @@ -4548,6 +4555,12 @@ checkOptLevel n dflags | otherwise = Right dflags +setCallerCcFilters :: String -> DynP () +setCallerCcFilters arg = + case parseCallerCcFilter arg of + Right filt -> upd $ \d -> d { callerCcFilters = filt : callerCcFilters d } + Left err -> addErr err + setMainIs :: String -> DynP () setMainIs arg | not (null main_fn) && isLower (head main_fn) ===================================== compiler/GHC/Iface/Recomp/Flags.hs ===================================== @@ -17,7 +17,7 @@ import GHC.Types.Name import GHC.Types.SafeHaskell import GHC.Utils.Fingerprint import GHC.Iface.Recomp.Binary --- import GHC.Utils.Outputable +import GHC.Core.Opt.CallerCC () -- for Binary instances import GHC.Data.EnumSet as EnumSet import System.FilePath (normalise) @@ -61,7 +61,7 @@ fingerprintDynFlags dflags at DynFlags{..} this_mod nameio = ticky = map (`gopt` dflags) [Opt_Ticky, Opt_Ticky_Allocd, Opt_Ticky_LNE, Opt_Ticky_Dyn_Thunk] - flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel)) + flags = ((mainis, safeHs, lang, cpp), (paths, prof, ticky, debugLevel, callerCcFilters)) in -- pprTrace "flags" (ppr flags) $ computeFingerprint nameio flags ===================================== compiler/ghc.cabal.in ===================================== @@ -71,6 +71,7 @@ Library hpc == 0.6.*, transformers == 0.5.*, exceptions == 0.10.*, + parsec, ghc-boot == @ProjectVersionMunged@, ghc-heap == @ProjectVersionMunged@, ghci == @ProjectVersionMunged@ @@ -301,6 +302,7 @@ Library GHC.Core.Multiplicity GHC.Core.Opt.Arity GHC.Core.Opt.CallArity + GHC.Core.Opt.CallerCC GHC.Core.Opt.ConstantFold GHC.Core.Opt.CprAnal GHC.Core.Opt.CSE ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,10 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- GHC now supports a flag, :ghc-flag:`-fprof-callers=⟨name⟩`, for requesting + that the compiler automatically insert cost-centres on all call-sites of + the named function. + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -332,19 +332,73 @@ Compiler options for profiling Without a :ghc-flag:`-prof` option, your ``SCC``\ s are ignored; so you can compile ``SCC``-laden code without changing it. +.. ghc-flag:: -fno-prof-count-entries + :shortdesc: Do not collect entry counts + :type: dynamic + :reverse: -fprof-count-entries + :category: + + Tells GHC not to collect information about how often functions are + entered at runtime (the "entries" column of the time profile), for + this module. This tends to make the profiled code run faster, and + hence closer to the speed of the unprofiled code, because GHC is + able to optimise more aggressively if it doesn't have to maintain + correct entry counts. This option can be useful if you aren't + interested in the entry counts (for example, if you only intend to + do heap profiling). + + There are a few other profiling-related compilation options. Use them *in addition to* :ghc-flag:`-prof`. These do not have to be used consistently for all modules in a program. +Automatically placing cost-centres +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +GHC has a number of flags for automatically inserting cost-centres into the +compiled program. + +.. ghc-flag:: -fprof-callers=⟨name⟩ + :shortdesc: Auto-add ``SCC``\\ s to all call-sites of the named function. + :type: dynamic + :category: + + Automatically enclose all occurrences of the named function in an ``SCC``. + Note that these cost-centres are added late in compilation (after + simplification) and consequently the names may be slightly different than + they appear in the source program (e.g. a call to ``f`` may inlined with + its wrapper, resulting in an occurrence of its worker, ``$wf``). + + In addition to plain module-qualified names (e.g. ``Data.List.map``), + ⟨name⟩ also accepts a small globbing language using ``*`` as a wildcard + symbol: + + .. code-block:: none + + pattern := '.' + module := '*' + | + identifier := + ident + + For instance, the following are all valid patterns: + + * ``Data.List.map`` + * ``*.map`` + * ``*.parse*`` + * ``*.<\\*>`` + + The ``*`` character can be used literally by escaping (e.g. ``\\*``). + .. ghc-flag:: -fprof-auto :shortdesc: Auto-add ``SCC``\\ s to all bindings not marked INLINE :type: dynamic :reverse: -fno-prof-auto :category: - *All* bindings not marked INLINE, whether exported or not, top level - or nested, will be given automatic ``SCC`` annotations. Functions - marked INLINE must be given a cost centre manually. + *All* bindings not marked :pragma:`INLINE`, whether exported or not, top + level or nested, will be given automatic ``SCC`` annotations. Functions + marked :pragma:`INLINE` must be given a cost centre manually. .. ghc-flag:: -fprof-auto-top :shortdesc: Auto-add ``SCC``\\ s to all top-level bindings not marked INLINE @@ -356,11 +410,11 @@ for all modules in a program. single: cost centres; automatically inserting GHC will automatically add ``SCC`` annotations for all top-level - bindings not marked INLINE. If you want a cost centre on an INLINE - function, you have to add it manually. + bindings not marked :pragma:`INLINE`. If you want a cost centre on an + :pragma:`INLINE` function, you have to add it manually. .. ghc-flag:: -fprof-auto-exported - :shortdesc: Auto-add ``SCC``\\ s to all exported bindings not marked INLINE + :shortdesc: Auto-add ``SCC``\\ s to all exported bindings not marked :pragma:`INLINE` :type: dynamic :reverse: -fno-prof-auto :category: @@ -369,8 +423,8 @@ for all modules in a program. single: cost centres; automatically inserting GHC will automatically add ``SCC`` annotations for all exported - functions not marked INLINE. If you want a cost centre on an INLINE - function, you have to add it manually. + functions not marked :pragma:`INLINE`. If you want a cost centre on an + :pragma:`INLINE` function, you have to add it manually. .. ghc-flag:: -fprof-auto-calls :shortdesc: Auto-add ``SCC``\\ s to all call sites @@ -392,41 +446,7 @@ for all modules in a program. The costs of all CAFs in a module are usually attributed to one "big" CAF cost-centre. With this option, all CAFs get their own - cost-centre. An “if all else fails” option… - -.. ghc-flag:: -fno-prof-auto - :shortdesc: Disables any previous :ghc-flag:`-fprof-auto`, - :ghc-flag:`-fprof-auto-top`, or :ghc-flag:`-fprof-auto-exported` options. - :type: dynamic - :reverse: -fprof-auto - :category: - - Disables any previous :ghc-flag:`-fprof-auto`, :ghc-flag:`-fprof-auto-top`, or - :ghc-flag:`-fprof-auto-exported` options. - -.. ghc-flag:: -fno-prof-cafs - :shortdesc: Disables any previous :ghc-flag:`-fprof-cafs` option. - :type: dynamic - :reverse: -fprof-cafs - :category: - - Disables any previous :ghc-flag:`-fprof-cafs` option. - -.. ghc-flag:: -fno-prof-count-entries - :shortdesc: Do not collect entry counts - :type: dynamic - :reverse: -fprof-count-entries - :category: - - Tells GHC not to collect information about how often functions are - entered at runtime (the "entries" column of the time profile), for - this module. This tends to make the profiled code run faster, and - hence closer to the speed of the unprofiled code, because GHC is - able to optimise more aggressively if it doesn't have to maintain - correct entry counts. This option can be useful if you aren't - interested in the entry counts (for example, if you only intend to - do heap profiling). - + cost-centre. An "if all else fails" option… .. ghc-flag:: -auto-all :shortdesc: *(deprecated)* Alias for :ghc-flag:`-fprof-auto` ===================================== testsuite/tests/parser/should_run/CountParserDeps.hs ===================================== @@ -29,12 +29,8 @@ main = do [libdir] <- getArgs modules <- parserDeps libdir let num = sizeUniqSet modules - max_num = 234 - min_num = max_num - 10 -- so that we don't forget to change the number - -- when the number of dependencies decreases - -- putStrLn $ "Found " ++ show num ++ " parser module dependencies" - -- forM_ (map moduleNameString $ nonDetEltsUniqSet modules) putStrLn - unless (num <= max_num && num >= min_num) $ exitWith (ExitFailure num) + putStrLn $ "Found " ++ show num ++ " parser module dependencies" + forM_ (map moduleNameString $ nonDetEltsUniqSet modules) putStrLn parserDeps :: FilePath -> IO (UniqSet ModuleName) parserDeps libdir = ===================================== testsuite/tests/parser/should_run/CountParserDeps.stdout ===================================== @@ -0,0 +1,236 @@ +Found 235 parser module dependencies +GHC.Builtin.Names +GHC.Builtin.PrimOps +GHC.Builtin.Types +GHC.Builtin.Types.Prim +GHC.Builtin.Uniques +GHC.ByteCode.Types +GHC.Cmm +GHC.Cmm.BlockId +GHC.Cmm.CLabel +GHC.Cmm.Dataflow.Block +GHC.Cmm.Dataflow.Collections +GHC.Cmm.Dataflow.Graph +GHC.Cmm.Dataflow.Label +GHC.Cmm.Expr +GHC.Cmm.MachOp +GHC.Cmm.Node +GHC.Cmm.Switch +GHC.Cmm.Type +GHC.CmmToAsm.CFG.Weight +GHC.CmmToAsm.Config +GHC.Core +GHC.Core.Class +GHC.Core.Coercion +GHC.Core.Coercion.Axiom +GHC.Core.Coercion.Opt +GHC.Core.ConLike +GHC.Core.DataCon +GHC.Core.FVs +GHC.Core.FamInstEnv +GHC.Core.InstEnv +GHC.Core.Lint +GHC.Core.Make +GHC.Core.Map +GHC.Core.Multiplicity +GHC.Core.Opt.Arity +GHC.Core.Opt.CallerCC +GHC.Core.Opt.ConstantFold +GHC.Core.Opt.Monad +GHC.Core.Opt.OccurAnal +GHC.Core.PatSyn +GHC.Core.Ppr +GHC.Core.Predicate +GHC.Core.Seq +GHC.Core.SimpleOpt +GHC.Core.Stats +GHC.Core.Subst +GHC.Core.TyCo.FVs +GHC.Core.TyCo.Ppr +GHC.Core.TyCo.Rep +GHC.Core.TyCo.Subst +GHC.Core.TyCo.Tidy +GHC.Core.TyCon +GHC.Core.TyCon.Env +GHC.Core.TyCon.RecWalk +GHC.Core.Type +GHC.Core.Unfold +GHC.Core.Unfold.Make +GHC.Core.Unify +GHC.Core.UsageEnv +GHC.Core.Utils +GHC.CoreToIface +GHC.Data.Bag +GHC.Data.BooleanFormula +GHC.Data.EnumSet +GHC.Data.FastMutInt +GHC.Data.FastString +GHC.Data.FastString.Env +GHC.Data.FiniteMap +GHC.Data.Graph.Directed +GHC.Data.IOEnv +GHC.Data.List.SetOps +GHC.Data.Maybe +GHC.Data.OrdList +GHC.Data.Pair +GHC.Data.Stream +GHC.Data.StringBuffer +GHC.Data.TrieMap +GHC.Driver.Backend +GHC.Driver.Backpack.Syntax +GHC.Driver.CmdLine +GHC.Driver.Env +GHC.Driver.Flags +GHC.Driver.Hooks +GHC.Driver.Monad +GHC.Driver.Phases +GHC.Driver.Pipeline.Monad +GHC.Driver.Plugins +GHC.Driver.Ppr +GHC.Driver.Session +GHC.Hs +GHC.Hs.Binds +GHC.Hs.Decls +GHC.Hs.Doc +GHC.Hs.Expr +GHC.Hs.Extension +GHC.Hs.ImpExp +GHC.Hs.Instances +GHC.Hs.Lit +GHC.Hs.Pat +GHC.Hs.Type +GHC.Hs.Utils +GHC.Iface.Ext.Fields +GHC.Iface.Recomp.Binary +GHC.Iface.Syntax +GHC.Iface.Type +GHC.Linker.Types +GHC.Parser +GHC.Parser.Annotation +GHC.Parser.CharClass +GHC.Parser.Errors +GHC.Parser.Lexer +GHC.Parser.PostProcess +GHC.Parser.PostProcess.Haddock +GHC.Parser.Types +GHC.Platform +GHC.Platform.AArch64 +GHC.Platform.ARM +GHC.Platform.Constants +GHC.Platform.NoRegs +GHC.Platform.PPC +GHC.Platform.Profile +GHC.Platform.Reg +GHC.Platform.Reg.Class +GHC.Platform.Regs +GHC.Platform.S390X +GHC.Platform.SPARC +GHC.Platform.Ways +GHC.Platform.X86 +GHC.Platform.X86_64 +GHC.Prelude +GHC.Runtime.Context +GHC.Runtime.Eval.Types +GHC.Runtime.Heap.Layout +GHC.Runtime.Interpreter.Types +GHC.Settings +GHC.Settings.Config +GHC.Settings.Constants +GHC.Stg.Syntax +GHC.StgToCmm.Types +GHC.SysTools.BaseDir +GHC.SysTools.FileCleanup +GHC.SysTools.Terminal +GHC.Tc.Errors.Hole.FitTypes +GHC.Tc.Types +GHC.Tc.Types.Constraint +GHC.Tc.Types.Evidence +GHC.Tc.Types.Origin +GHC.Tc.Utils.TcType +GHC.Types.Annotations +GHC.Types.Avail +GHC.Types.Basic +GHC.Types.CompleteMatch +GHC.Types.CostCentre +GHC.Types.CostCentre.State +GHC.Types.Cpr +GHC.Types.Demand +GHC.Types.Error +GHC.Types.FieldLabel +GHC.Types.Fixity +GHC.Types.Fixity.Env +GHC.Types.ForeignCall +GHC.Types.ForeignStubs +GHC.Types.HpcInfo +GHC.Types.Id +GHC.Types.Id.Info +GHC.Types.Id.Make +GHC.Types.Literal +GHC.Types.Meta +GHC.Types.Name +GHC.Types.Name.Cache +GHC.Types.Name.Env +GHC.Types.Name.Occurrence +GHC.Types.Name.Ppr +GHC.Types.Name.Reader +GHC.Types.Name.Set +GHC.Types.RepType +GHC.Types.SafeHaskell +GHC.Types.SourceError +GHC.Types.SourceFile +GHC.Types.SourceText +GHC.Types.SrcLoc +GHC.Types.Target +GHC.Types.TyThing +GHC.Types.TypeEnv +GHC.Types.Unique +GHC.Types.Unique.DFM +GHC.Types.Unique.DSet +GHC.Types.Unique.FM +GHC.Types.Unique.Set +GHC.Types.Unique.Supply +GHC.Types.Var +GHC.Types.Var.Env +GHC.Types.Var.Set +GHC.Unit +GHC.Unit.External +GHC.Unit.Finder.Types +GHC.Unit.Home +GHC.Unit.Home.ModInfo +GHC.Unit.Info +GHC.Unit.Module +GHC.Unit.Module.Deps +GHC.Unit.Module.Env +GHC.Unit.Module.Graph +GHC.Unit.Module.Imported +GHC.Unit.Module.Location +GHC.Unit.Module.ModDetails +GHC.Unit.Module.ModGuts +GHC.Unit.Module.ModIface +GHC.Unit.Module.ModSummary +GHC.Unit.Module.Name +GHC.Unit.Module.Status +GHC.Unit.Module.Warnings +GHC.Unit.Parser +GHC.Unit.Ppr +GHC.Unit.State +GHC.Unit.Types +GHC.Utils.Binary +GHC.Utils.Binary.Typeable +GHC.Utils.BufHandle +GHC.Utils.CliOption +GHC.Utils.Error +GHC.Utils.Exception +GHC.Utils.FV +GHC.Utils.Fingerprint +GHC.Utils.GlobalVars +GHC.Utils.IO.Unsafe +GHC.Utils.Json +GHC.Utils.Lexeme +GHC.Utils.Misc +GHC.Utils.Monad +GHC.Utils.Outputable +GHC.Utils.Panic +GHC.Utils.Panic.Plain +GHC.Utils.Ppr +GHC.Utils.Ppr.Colour ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.prof.sample ===================================== @@ -0,0 +1,79 @@ + Fri Nov 13 01:06 2020 Time and Allocation Profiling Report (Final) + + CallerCc1 +RTS -hc -p -RTS 7 + + total time = 0.09 secs (87 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 35.6 49.5 +insert Main Main.hs:(108,1)-(112,8) 21.8 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 17.2 37.5 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 6.9 2.6 +conjunct Main Main.hs:(70,1)-(71,18) 5.7 0.0 +split.split' Main Main.hs:(165,11)-(166,28) 3.4 2.3 +disin.dp Main Main.hs:80:3-14 3.4 0.0 +unicl Main Main.hs:(176,1)-(180,36) 2.3 1.1 +tautclause Main Main.hs:173:1-49 2.3 3.7 +disin.dq Main Main.hs:81:3-14 1.1 0.0 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling:Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling:Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 35.6 49.5 46.0 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 5.7 0.0 5.7 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 3.4 0.0 3.4 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 1.1 0.0 1.1 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.4 2.3 3.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 2.3 1.1 50.6 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 6.9 2.6 48.3 46.9 + tautclause Main Main.hs:173:1-49 295 37422 2.3 3.7 2.3 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 39.1 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 39.1 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 17.2 37.5 39.1 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 21.8 1.7 21.8 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc1.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.prof.sample ===================================== @@ -0,0 +1,78 @@ + Fri Nov 13 01:06 2020 Time and Allocation Profiling Report (Final) + + CallerCc2 +RTS -hc -p -RTS 7 + + total time = 0.09 secs (91 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 26.4 49.5 +clause.clause' Main Main.hs:(63,12)-(65,57) 23.1 37.5 +insert Main Main.hs:(108,1)-(112,8) 18.7 1.7 +conjunct Main Main.hs:(70,1)-(71,18) 8.8 0.0 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 5.5 2.6 +tautclause Main Main.hs:173:1-49 5.5 3.7 +unicl Main Main.hs:(176,1)-(180,36) 3.3 1.1 +split.split' Main Main.hs:(165,11)-(166,28) 3.3 2.3 +disin.dp Main Main.hs:80:3-14 3.3 0.0 +clause Main Main.hs:(61,1)-(65,57) 2.2 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling:Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling:Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 26.4 49.5 38.5 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 8.8 0.0 8.8 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 3.3 0.0 3.3 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 0.0 0.0 0.0 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 3.3 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 3.3 2.3 3.3 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 3.3 1.1 58.2 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 5.5 2.6 54.9 46.9 + tautclause Main Main.hs:173:1-49 295 37422 5.5 3.7 5.5 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 44.0 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 2.2 1.4 44.0 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 23.1 37.5 41.8 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 18.7 1.7 18.7 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc2.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.prof.sample ===================================== @@ -0,0 +1,78 @@ + Fri Nov 13 01:06 2020 Time and Allocation Profiling Report (Final) + + CallerCc3 +RTS -hc -p -RTS 7 + + total time = 0.09 secs (85 ticks @ 1000 us, 1 processor) + total alloc = 105,486,200 bytes (excludes profiling overheads) + +COST CENTRE MODULE SRC %time %alloc + +disin Main Main.hs:(74,1)-(83,11) 29.4 49.5 +insert Main Main.hs:(108,1)-(112,8) 24.7 1.7 +clause.clause' Main Main.hs:(63,12)-(65,57) 23.5 37.5 +conjunct Main Main.hs:(70,1)-(71,18) 10.6 0.0 +tautclause Main Main.hs:173:1-49 4.7 3.7 +unicl.unicl' Main Main.hs:(178,11)-(180,36) 3.5 2.6 +split.split' Main Main.hs:(165,11)-(166,28) 2.4 2.3 +disin.dp Main Main.hs:80:3-14 1.2 0.0 +unicl Main Main.hs:(176,1)-(180,36) 0.0 1.1 +clause Main Main.hs:(61,1)-(65,57) 0.0 1.4 + + + individual inherited +COST CENTRE MODULE SRC no. entries %time %alloc %time %alloc + +MAIN MAIN 128 0 0.0 0.0 100.0 100.0 + CAF Main 255 0 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 261 1 0.0 0.0 0.0 0.0 + Main.clauses(calling:Data.Foldable.concat) Main Main.hs:68:1-7 263 1 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 256 1 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 279 1 0.0 0.0 0.0 0.0 + spaces Main Main.hs:160:1-19 303 1 0.0 0.0 0.0 0.0 + CAF GHC.Conc.Signal 246 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding 235 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Encoding.Iconv 233 0 0.0 0.0 0.0 0.0 + CAF GHC.IO.Handle.FD 225 0 0.0 0.0 0.0 0.0 + main Main Main.hs:(42,1)-(44,23) 257 0 0.0 0.0 100.0 100.0 + res Main Main.hs:(46,1)-(48,26) 258 1 0.0 0.0 100.0 99.9 + Main.main(calling:Data.Foldable.concat) Main Main.hs:42:1-4 259 1 0.0 0.0 0.0 0.0 + res.xs Main Main.hs:47:8-69 260 1 0.0 0.0 0.0 0.0 + clauses Main Main.hs:68:1-74 262 0 0.0 0.0 100.0 99.9 + disin Main Main.hs:(74,1)-(83,11) 267 857598 29.4 49.5 41.2 49.5 + conjunct Main Main.hs:(70,1)-(71,18) 291 759353 10.6 0.0 10.6 0.0 + disin.dp Main Main.hs:80:3-14 292 380009 1.2 0.0 1.2 0.0 + disin.dq Main Main.hs:81:3-14 293 380009 0.0 0.0 0.0 0.0 + negin Main Main.hs:(119,1)-(124,11) 268 1617 0.0 0.1 0.0 0.1 + elim Main Main.hs:(89,1)-(94,57) 269 1393 0.0 0.1 0.0 0.1 + disp Main Main.hs:86:1-71 301 7 0.0 0.0 0.0 0.0 + interleave Main Main.hs:(115,1)-(116,25) 302 35 0.0 0.0 0.0 0.0 + parse Main Main.hs:135:1-39 270 7 0.0 0.0 0.0 0.0 + parse.(...) Main Main.hs:135:19-39 272 7 0.0 0.0 0.0 0.0 + parse' Main Main.hs:(137,1)-(145,42) 273 280 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 276 56 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 274 56 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 275 49 0.0 0.0 0.0 0.0 + parse'.(...) Main Main.hs:142:20-49 278 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 280 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 282 63 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 283 63 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 281 63 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 284 42 0.0 0.0 0.0 0.0 + parse'.s' Main Main.hs:142:20-49 285 21 0.0 0.0 0.0 0.0 + parse'.x Main Main.hs:142:20-49 277 21 0.0 0.0 0.0 0.0 + redstar Main Main.hs:155:1-35 286 0 0.0 0.0 0.0 0.0 + spri Main Main.hs:(169,1)-(170,10) 288 21 0.0 0.0 0.0 0.0 + opri Main Main.hs:(127,1)-(132,12) 289 14 0.0 0.0 0.0 0.0 + while Main Main.hs:182:1-48 287 21 0.0 0.0 0.0 0.0 + red Main Main.hs:(148,1)-(152,43) 290 14 0.0 0.0 0.0 0.0 + parse.f Main Main.hs:135:19-39 271 7 0.0 0.0 0.0 0.0 + split Main Main.hs:(163,1)-(166,28) 265 7 0.0 0.0 2.4 2.3 + split.split' Main Main.hs:(165,11)-(166,28) 266 74837 2.4 2.3 2.4 2.3 + unicl Main Main.hs:(176,1)-(180,36) 264 7 0.0 1.1 56.5 48.0 + unicl.unicl' Main Main.hs:(178,11)-(180,36) 294 37422 3.5 2.6 56.5 46.9 + tautclause Main Main.hs:173:1-49 295 37422 4.7 3.7 4.7 3.7 + unicl.unicl'.cp Main Main.hs:180:24-36 296 37422 0.0 0.0 48.2 40.6 + clause Main Main.hs:(61,1)-(65,57) 297 37422 0.0 1.4 48.2 40.6 + clause.clause' Main Main.hs:(63,12)-(65,57) 298 696150 23.5 37.5 48.2 39.2 + insert Main Main.hs:(108,1)-(112,8) 299 366786 24.7 1.7 24.7 1.7 + insert Main Main.hs:(108,1)-(112,8) 300 7 0.0 0.0 0.0 0.0 ===================================== testsuite/tests/profiling/should_run/caller-cc/CallerCc3.stdout ===================================== @@ -0,0 +1,7 @@ +a <= +a <= +a <= +a <= +a <= +a <= +a <= ===================================== testsuite/tests/profiling/should_run/caller-cc/Main.hs ===================================== @@ -0,0 +1,182 @@ +{- +From: dw at minster.york.ac.uk +To: partain +Subject: a compiler test +Date: 3 Mar 1992 12:31:00 GMT + +Will, + One of the decisions taken at the FLARE meeting yesterday was that we +(FLARE people) should send you (GRASP people) interesting Haskell programs +to test your new compiler. So allow me to present the following program, +written by Colin Runciman in various functional languages over the years, +which puts propositions into clausal form. The original program was +interactive, but I've made it batch so that you can run it over night. +Here is an example run with the prototype compiler. Note the result is +"a <=". + + hc clausify.hs + Haskell-0.41 (EXPERIMENTAL) + Glasgow University Haskell Compiler, version 0.41 + G-Code version + -71$ a.out + a <= + -71$ + +Cheers, + +David +-} + +------------------------------------------------------------------------------ +-- reducing propositions to clausal form +-- Colin Runciman, University of York, 18/10/90 + +-- an excellent benchmark is: (a = a = a) = (a = a = a) = (a = a = a) +-- batch mode version David Wakeling, February 1992 + +module Main(main) where + +import Data.Ix +import System.Environment + +main = do + (n:_) <- getArgs + putStr (res (read n)) + +res n = concat (map clauses xs) + where xs = take n (repeat "(a = a = a) = (a = a = a) = (a = a = a)") + {-# NOINLINE xs #-} + +data StackFrame = Ast Formula | Lex Char + +data Formula = + Sym Char | + Not Formula | + Dis Formula Formula | + Con Formula Formula | + Imp Formula Formula | + Eqv Formula Formula + +-- separate positive and negative literals, eliminating duplicates +clause p = clause' p ([] , []) + where + clause' (Dis p q) x = clause' p (clause' q x) + clause' (Sym s) (c,a) = (insert s c , a) + clause' (Not (Sym s)) (c,a) = (c , insert s a) + +-- the main pipeline from propositional formulae to printed clauses +clauses = concat . map disp . unicl . split . disin . negin . elim . parse + +conjunct (Con p q) = True +conjunct p = False + +-- shift disjunction within conjunction +disin (Dis p (Con q r)) = Con (disin (Dis p q)) (disin (Dis p r)) +disin (Dis (Con p q) r) = Con (disin (Dis p r)) (disin (Dis q r)) +disin (Dis p q) = + if conjunct dp || conjunct dq then disin (Dis dp dq) + else (Dis dp dq) + where + dp = disin p + dq = disin q +disin (Con p q) = Con (disin p) (disin q) +disin p = p + +-- format pair of lists of propositional symbols as clausal axiom +disp (l,r) = interleave l spaces ++ "<=" ++ interleave spaces r ++ "\n" + +-- eliminate connectives other than not, disjunction and conjunction +elim (Sym s) = Sym s +elim (Not p) = Not (elim p) +elim (Dis p q) = Dis (elim p) (elim q) +elim (Con p q) = Con (elim p) (elim q) +elim (Imp p q) = Dis (Not (elim p)) (elim q) +elim (Eqv f f') = Con (elim (Imp f f')) (elim (Imp f' f)) + +-- the priorities of propositional expressions +{- UNUSED: +fpri (Sym c) = 6 +fpri (Not p) = 5 +fpri (Con p q) = 4 +fpri (Dis p q) = 3 +fpri (Imp p q) = 2 +fpri (Eqv p q) = 1 +-} + +-- insertion of an item into an ordered list +-- Note: this is a corrected version from Colin (94/05/03 WDP) +insert x [] = [x] +insert x p@(y:ys) = + if x < y then x : p + else if x > y then y : insert x ys + else p + + +interleave (x:xs) ys = x : interleave ys xs +interleave [] _ = [] + +-- shift negation to innermost positions +negin (Not (Not p)) = negin p +negin (Not (Con p q)) = Dis (negin (Not p)) (negin (Not q)) +negin (Not (Dis p q)) = Con (negin (Not p)) (negin (Not q)) +negin (Dis p q) = Dis (negin p) (negin q) +negin (Con p q) = Con (negin p) (negin q) +negin p = p + +-- the priorities of symbols during parsing +opri '(' = 0 +opri '=' = 1 +opri '>' = 2 +opri '|' = 3 +opri '&' = 4 +opri '~' = 5 + +-- parsing a propositional formula +parse t = f where [Ast f] = parse' t [] + +parse' [] s = redstar s +parse' (' ':t) s = parse' t s +parse' ('(':t) s = parse' t (Lex '(' : s) +parse' (')':t) s = parse' t (x:s') + where + (x : Lex '(' : s') = redstar s +parse' (c:t) s = if inRange ('a','z') c then parse' t (Ast (Sym c) : s) + else if spri s > opri c then parse' (c:t) (red s) + else parse' t (Lex c : s) + +-- reduction of the parse stack +red (Ast p : Lex '=' : Ast q : s) = Ast (Eqv q p) : s +red (Ast p : Lex '>' : Ast q : s) = Ast (Imp q p) : s +red (Ast p : Lex '|' : Ast q : s) = Ast (Dis q p) : s +red (Ast p : Lex '&' : Ast q : s) = Ast (Con q p) : s +red (Ast p : Lex '~' : s) = Ast (Not p) : s + +-- iterative reduction of the parse stack +redstar = while ((/=) 0 . spri) red + +-- old: partain: +--redstar = while ((/=) (0::Int) . spri) red + +spaces = repeat ' ' + +-- split conjunctive proposition into a list of conjuncts +split p = split' p [] + where + split' (Con p q) a = split' p (split' q a) + split' p a = p : a + +-- priority of the parse stack +spri (Ast x : Lex c : s) = opri c +spri s = 0 + +-- does any symbol appear in both consequent and antecedent of clause +tautclause (c,a) = [x | x <- c, x `elem` a] /= [] + +-- form unique clausal axioms excluding tautologies +unicl a = foldr unicl' [] a + where + unicl' p x = if tautclause cp then x else insert cp x + where + cp = clause p + +while p f x = if p x then while p f (f x) else x ===================================== testsuite/tests/profiling/should_run/caller-cc/all.T ===================================== @@ -0,0 +1,19 @@ +setTestOpts(req_profiling) +setTestOpts(extra_ways(['prof', 'ghci-ext-prof'])) +setTestOpts(only_ways(prof_ways)) +setTestOpts(extra_files(['Main.hs'])) +setTestOpts(extra_run_opts('7')) + +# N.B. Main.hs is stolen from heapprof001. + +test('CallerCc1', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=*.concat -O0']) + +test('CallerCc2', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.concat -O0']) + +test('CallerCc3', normal, + multimod_compile_and_run, + ['Main', '-fprof-callers=Data.Foldable.con*at -O0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/802e9180dd9a9a88c4e8869f0de1048e1edd6343...53ad67eacacde8fde452f1a323d5886183375182 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/802e9180dd9a9a88c4e8869f0de1048e1edd6343...53ad67eacacde8fde452f1a323d5886183375182 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 Sat Nov 21 06:14:19 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 01:14:19 -0500 Subject: [Git][ghc/ghc][master] 2 commits: Move Plugins into HscEnv (#17957) Message-ID: <5fb8b03bed6ca_36a71600f92c479815@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - 24 changed files: - compiler/GHC.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - docs/users_guide/extending_ghc.rst - ghc/GHCi/UI.hs - ghc/Main.hs - testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs - testsuite/tests/plugins/static-plugins.hs - utils/haddock Changes: ===================================== compiler/GHC.hs ===================================== @@ -313,6 +313,7 @@ import GHC.Driver.Monad import GHC.Driver.Ppr import GHC.ByteCode.Types +import GHC.Runtime.Loader import GHC.Runtime.Eval import GHC.Runtime.Eval.Types import GHC.Runtime.Interpreter @@ -729,6 +730,8 @@ getProgramDynFlags :: GhcMonad m => m DynFlags getProgramDynFlags = getSessionDynFlags -- | Set the 'DynFlags' used to evaluate interactive expressions. +-- Also initialise (load) plugins. +-- -- Note: this cannot be used for changes to packages. Use -- 'setSessionDynFlags', or 'setProgramDynFlags' and then copy the -- 'unitState' into the interactive @DynFlags at . @@ -736,7 +739,22 @@ setInteractiveDynFlags :: GhcMonad m => DynFlags -> m () setInteractiveDynFlags dflags = do dflags' <- checkNewDynFlags dflags dflags'' <- checkNewInteractiveDynFlags dflags' - modifySession $ \h -> h{ hsc_IC = (hsc_IC h) { ic_dflags = dflags'' }} + modifySessionM $ \hsc_env0 -> do + let ic0 = hsc_IC hsc_env0 + + -- Initialise (load) plugins in the interactive environment with the new + -- DynFlags + plugin_env <- liftIO $ initializePlugins $ mkInteractiveHscEnv $ + hsc_env0 { hsc_IC = ic0 { ic_dflags = dflags'' }} + + -- Update both plugins cache and DynFlags in the interactive context. + return $ hsc_env0 + { hsc_IC = ic0 + { ic_plugins = hsc_plugins plugin_env + , ic_dflags = hsc_dflags plugin_env + } + } + -- | Get the 'DynFlags' used to evaluate interactive expressions. getInteractiveDynFlags :: GhcMonad m => m DynFlags ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -60,7 +60,6 @@ import GHC.Unit.Module.Env import GHC.Unit.Module.ModGuts import GHC.Unit.Module.Deps -import GHC.Runtime.Loader -- ( initializePlugins ) import GHC.Runtime.Context import GHC.Types.SrcLoc @@ -88,18 +87,14 @@ core2core hsc_env guts@(ModGuts { mg_module = mod , mg_loc = loc , mg_deps = deps , mg_rdr_env = rdr_env }) - = do { -- make sure all plugins are loaded - - ; let builtin_passes = getCoreToDo dflags + = do { let builtin_passes = getCoreToDo dflags orph_mods = mkModuleSet (mod : dep_orphs deps) uniq_mask = 's' ; ; (guts2, stats) <- runCoreM hsc_env hpt_rule_base uniq_mask mod orph_mods print_unqual loc $ do { hsc_env' <- getHscEnv - ; dflags' <- liftIO $ initializePlugins hsc_env' - (hsc_dflags hsc_env') - ; all_passes <- withPlugins dflags' + ; all_passes <- withPlugins hsc_env' installCoreToDos builtin_passes ; runCorePasses all_passes guts } ===================================== compiler/GHC/Driver/Env.hs ===================================== @@ -26,7 +26,7 @@ import GHC.Prelude import GHC.Driver.Ppr import GHC.Driver.Session -import GHC.Unit.Finder.Types +import {-# SOURCE #-} GHC.Driver.Plugins import GHC.Runtime.Context import GHC.Runtime.Interpreter.Types (Interp) @@ -39,6 +39,7 @@ import GHC.Unit.Module.ModDetails import GHC.Unit.Module.Deps import GHC.Unit.Home.ModInfo import GHC.Unit.External +import GHC.Unit.Finder.Types import GHC.Core ( CoreRule ) import GHC.Core.FamInstEnv @@ -94,14 +95,17 @@ runHsc hsc_env (Hsc hsc) = do printOrThrowWarnings (hsc_dflags hsc_env) w return a +-- | Switches in the DynFlags and Plugins from the InteractiveContext mkInteractiveHscEnv :: HscEnv -> HscEnv -mkInteractiveHscEnv hsc_env = hsc_env{ hsc_dflags = interactive_dflags } - where - interactive_dflags = ic_dflags (hsc_IC hsc_env) +mkInteractiveHscEnv hsc_env = + let ic = hsc_IC hsc_env + in hsc_env { hsc_dflags = ic_dflags ic + , hsc_plugins = ic_plugins ic + } -runInteractiveHsc :: HscEnv -> Hsc a -> IO a --- A variant of runHsc that switches in the DynFlags from the +-- | A variant of runHsc that switches in the DynFlags and Plugins from the -- InteractiveContext before running the Hsc computation. +runInteractiveHsc :: HscEnv -> Hsc a -> IO a runInteractiveHsc hsc_env = runHsc (mkInteractiveHscEnv hsc_env) -- | HscEnv is like 'GHC.Driver.Monad.Session', except that some of the fields are immutable. @@ -178,6 +182,21 @@ data HscEnv , hsc_home_unit :: !HomeUnit -- ^ Home-unit + , hsc_plugins :: ![LoadedPlugin] + -- ^ plugins dynamically loaded after processing arguments. What + -- will be loaded here is directed by DynFlags.pluginModNames. + -- Arguments are loaded from DynFlags.pluginModNameOpts. + -- + -- The purpose of this field is to cache the plugins so they + -- don't have to be loaded each time they are needed. See + -- 'GHC.Runtime.Loader.initializePlugins'. + + , hsc_static_plugins :: ![StaticPlugin] + -- ^ static plugins which do not need dynamic loading. These plugins are + -- intended to be added by GHC API users directly to this list. + -- + -- To add dynamically loaded plugins through the GHC API see + -- 'addPluginModuleName' instead. } {- ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -241,18 +241,20 @@ newHscEnv dflags = do nc_var <- newIORef (initNameCache us knownKeyNames) fc_var <- newIORef emptyInstalledModuleEnv emptyLoader <- uninitializedLoader - return HscEnv { hsc_dflags = dflags - , hsc_targets = [] - , hsc_mod_graph = emptyMG - , hsc_IC = emptyInteractiveContext dflags - , hsc_HPT = emptyHomePackageTable - , hsc_EPS = eps_var - , hsc_NC = nc_var - , hsc_FC = fc_var - , hsc_type_env_var = Nothing - , hsc_interp = Nothing - , hsc_loader = emptyLoader - , hsc_home_unit = home_unit + return HscEnv { hsc_dflags = dflags + , hsc_targets = [] + , hsc_mod_graph = emptyMG + , hsc_IC = emptyInteractiveContext dflags + , hsc_HPT = emptyHomePackageTable + , hsc_EPS = eps_var + , hsc_NC = nc_var + , hsc_FC = fc_var + , hsc_type_env_var = Nothing + , hsc_interp = Nothing + , hsc_loader = emptyLoader + , hsc_home_unit = home_unit + , hsc_plugins = [] + , hsc_static_plugins = [] } -- ----------------------------------------------------------------------------- @@ -454,7 +456,8 @@ hscParse' mod_summary -- apply parse transformation of plugins let applyPluginAction p opts = parsedResultAction p opts mod_summary - withPlugins dflags applyPluginAction res + hsc_env <- getHscEnv + withPlugins hsc_env applyPluginAction res -- ----------------------------------------------------------------------------- @@ -764,12 +767,11 @@ hscIncrementalCompile :: Bool -> SourceModified -> Maybe ModIface -> (Int,Int) - -> IO (HscStatus, DynFlags) + -> IO (HscStatus, HscEnv) hscIncrementalCompile always_do_basic_recompilation_check m_tc_result mHscMessage hsc_env' mod_summary source_modified mb_old_iface mod_index = do - dflags <- initializePlugins hsc_env' (hsc_dflags hsc_env') - let hsc_env'' = hsc_env' { hsc_dflags = dflags } + hsc_env'' <- initializePlugins hsc_env' -- One-shot mode needs a knot-tying mutable variable for interface -- files. See GHC.Tc.Utils.TcGblEnv.tcg_type_env_var. @@ -804,14 +806,14 @@ hscIncrementalCompile always_do_basic_recompilation_check m_tc_result -- any further typechecking. It's much more useful -- in make mode, since this HMI will go into the HPT. genModDetails hsc_env' iface - return (HscUpToDate iface details, dflags) + return (HscUpToDate iface details, hsc_env') -- We finished type checking. (mb_old_hash is the hash of -- the interface that existed on disk; it's possible we had -- to retypecheck but the resulting interface is exactly -- the same.) Right (FrontendTypecheck tc_result, mb_old_hash) -> do status <- finish mod_summary tc_result mb_old_hash - return (status, dflags) + return (status, hsc_env) -- Runs the post-typechecking frontend (desugar and simplify). We want to -- generate most of the interface as late as possible. This gets us up-to-date @@ -1424,16 +1426,22 @@ hscGetSafeMode tcg_env = do -- Simplifiers -------------------------------------------------------------- +-- | Run Core2Core simplifier. The list of String is a list of (Core) plugin +-- module names added via TH (cf 'addCorePlugin'). hscSimplify :: HscEnv -> [String] -> ModGuts -> IO ModGuts hscSimplify hsc_env plugins modguts = runHsc hsc_env $ hscSimplify' plugins modguts +-- | Run Core2Core simplifier. The list of String is a list of (Core) plugin +-- module names added via TH (cf 'addCorePlugin'). hscSimplify' :: [String] -> ModGuts -> Hsc ModGuts hscSimplify' plugins ds_result = do hsc_env <- getHscEnv - let hsc_env_with_plugins = hsc_env - { hsc_dflags = foldr addPluginModuleName (hsc_dflags hsc_env) plugins - } + hsc_env_with_plugins <- if null plugins -- fast path + then return hsc_env + else liftIO $ initializePlugins $ hsc_env + { hsc_dflags = foldr addPluginModuleName (hsc_dflags hsc_env) plugins + } {-# SCC "Core2Core" #-} liftIO $ core2core hsc_env_with_plugins ds_result ===================================== compiler/GHC/Driver/Monad.hs ===================================== @@ -16,7 +16,8 @@ module GHC.Driver.Monad ( reflectGhc, reifyGhc, getSessionDynFlags, liftIO, - Session(..), withSession, modifySession, withTempSession, + Session(..), withSession, modifySession, modifySessionM, + withTempSession, -- ** Warnings logWarnings, printException, @@ -73,6 +74,13 @@ modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m () modifySession f = do h <- getSession setSession $! f h +-- | Set the current session to the result of applying the current session to +-- the argument. +modifySessionM :: GhcMonad m => (HscEnv -> m HscEnv) -> m () +modifySessionM f = do h <- getSession + h' <- f h + setSession $! h' + withSavedSession :: GhcMonad m => m a -> m a withSavedSession m = do saved_session <- getSession ===================================== compiler/GHC/Driver/Pipeline.hs ===================================== @@ -197,10 +197,12 @@ compileOne' m_tc_result mHscMessage debugTraceMsg dflags1 2 (text "compile: input file" <+> text input_fnpp) -- Run the pipeline up to codeGen (so everything up to, but not including, STG) - (status, plugin_dflags) <- hscIncrementalCompile + (status, plugin_hsc_env) <- hscIncrementalCompile always_do_basic_recompilation_check m_tc_result mHscMessage hsc_env summary source_modified mb_old_iface (mod_index, nmods) + -- Use an HscEnv updated with the plugin info + let hsc_env' = plugin_hsc_env let flags = hsc_dflags hsc_env0 in do unless (gopt Opt_KeepHiFiles flags) $ @@ -210,10 +212,6 @@ compileOne' m_tc_result mHscMessage addFilesToClean flags TFL_GhcSession $ [ml_obj_file $ ms_location summary] - -- Use an HscEnv with DynFlags updated with the plugin info (returned from - -- hscIncrementalCompile) - let hsc_env' = hsc_env{ hsc_dflags = plugin_dflags } - case (status, bcknd) of (HscUpToDate iface hmi_details, _) -> -- TODO recomp014 triggers this assert. What's going on?! @@ -1259,12 +1257,15 @@ runPhase (RealPhase (Hsc src_flavour)) input_fn dflags0 -- run the compiler! let msg hsc_env _ what _ = oneShotMsg hsc_env what - (result, plugin_dflags) <- + (result, plugin_hsc_env) <- liftIO $ hscIncrementalCompile True Nothing (Just msg) hsc_env' mod_summary source_unchanged Nothing (1,1) - -- In the rest of the pipeline use the dflags with plugin info - setDynFlags plugin_dflags + -- In the rest of the pipeline use the loaded plugins + setPlugins (hsc_plugins plugin_hsc_env) + (hsc_static_plugins plugin_hsc_env) + -- "driver" plugins may have modified the DynFlags so we update them + setDynFlags (hsc_dflags plugin_hsc_env) return (HscOut src_flavour mod_name result, panic "HscOut doesn't have an input filename") ===================================== compiler/GHC/Driver/Pipeline/Monad.hs ===================================== @@ -7,7 +7,7 @@ module GHC.Driver.Pipeline.Monad ( , PhasePlus(..) , PipeEnv(..), PipeState(..), PipelineOutput(..) , getPipeEnv, getPipeState, setDynFlags, setModLocation, setForeignOs, setIface - , pipeStateDynFlags, pipeStateModIface + , pipeStateDynFlags, pipeStateModIface, setPlugins ) where import GHC.Prelude @@ -18,6 +18,7 @@ import GHC.Utils.Outputable import GHC.Driver.Session import GHC.Driver.Phases import GHC.Driver.Env +import GHC.Driver.Plugins import GHC.SysTools.FileCleanup (TempFileLifetime) @@ -69,9 +70,9 @@ data PipeEnv = PipeEnv { -- PipeState: information that might change during a pipeline run data PipeState = PipeState { hsc_env :: HscEnv, - -- ^ only the DynFlags change in the HscEnv. The DynFlags change - -- at various points, for example when we read the OPTIONS_GHC - -- pragmas in the Cpp phase. + -- ^ only the DynFlags and the Plugins change in the HscEnv. The + -- DynFlags change at various points, for example when we read the + -- OPTIONS_GHC pragmas in the Cpp phase. maybe_loc :: Maybe ModLocation, -- ^ the ModLocation. This is discovered during compilation, -- in the Hsc phase where we read the module header. @@ -117,6 +118,11 @@ setDynFlags :: DynFlags -> CompPipeline () setDynFlags dflags = P $ \_env state -> return (state{hsc_env= (hsc_env state){ hsc_dflags = dflags }}, ()) +setPlugins :: [LoadedPlugin] -> [StaticPlugin] -> CompPipeline () +setPlugins dyn static = P $ \_env state -> + let hsc_env' = (hsc_env state){ hsc_plugins = dyn, hsc_static_plugins = static } + in return (state{hsc_env = hsc_env'}, ()) + setModLocation :: ModLocation -> CompPipeline () setModLocation loc = P $ \_env state -> return (state{ maybe_loc = Just loc }, ()) ===================================== compiler/GHC/Driver/Plugins.hs ===================================== @@ -50,7 +50,6 @@ module GHC.Driver.Plugins ( import GHC.Prelude import GHC.Driver.Env -import GHC.Driver.Session import GHC.Driver.Monad import GHC.Driver.Phases @@ -98,13 +97,14 @@ data Plugin = Plugin { , holeFitPlugin :: HoleFitPlugin -- ^ An optional plugin to handle hole fits, which may re-order -- or change the list of valid hole fits and refinement hole fits. - , dynflagsPlugin :: [CommandLineOption] -> DynFlags -> IO DynFlags - -- ^ An optional plugin to update 'DynFlags', right after - -- plugin loading. This can be used to register hooks - -- or tweak any field of 'DynFlags' before doing - -- actual work on a module. + + , driverPlugin :: [CommandLineOption] -> HscEnv -> IO HscEnv + -- ^ An optional plugin to update 'HscEnv', right after plugin loading. This + -- can be used to register hooks or tweak any field of 'DynFlags' before + -- doing actual work on a module. -- -- @since 8.10.1 + , pluginRecompile :: [CommandLineOption] -> IO PluginRecompile -- ^ Specify how the plugin should affect recompilation. , parsedResultAction :: [CommandLineOption] -> ModSummary -> HsParsedModule @@ -214,7 +214,7 @@ defaultPlugin = Plugin { installCoreToDos = const return , tcPlugin = const Nothing , holeFitPlugin = const Nothing - , dynflagsPlugin = const return + , driverPlugin = const return , pluginRecompile = impurePlugin , renamedResultAction = \_ env grp -> return (env, grp) , parsedResultAction = \_ _ -> return @@ -242,25 +242,25 @@ keepRenamedSource _ gbl_env group = type PluginOperation m a = Plugin -> [CommandLineOption] -> a -> m a type ConstPluginOperation m a = Plugin -> [CommandLineOption] -> a -> m () -plugins :: DynFlags -> [PluginWithArgs] -plugins df = - map lpPlugin (cachedPlugins df) ++ - map spPlugin (staticPlugins df) +plugins :: HscEnv -> [PluginWithArgs] +plugins hsc_env = + map lpPlugin (hsc_plugins hsc_env) ++ + map spPlugin (hsc_static_plugins hsc_env) -- | Perform an operation by using all of the plugins in turn. -withPlugins :: Monad m => DynFlags -> PluginOperation m a -> a -> m a -withPlugins df transformation input = foldM go input (plugins df) +withPlugins :: Monad m => HscEnv -> PluginOperation m a -> a -> m a +withPlugins hsc_env transformation input = foldM go input (plugins hsc_env) where go arg (PluginWithArgs p opts) = transformation p opts arg -mapPlugins :: DynFlags -> (Plugin -> [CommandLineOption] -> a) -> [a] -mapPlugins df f = map (\(PluginWithArgs p opts) -> f p opts) (plugins df) +mapPlugins :: HscEnv -> (Plugin -> [CommandLineOption] -> a) -> [a] +mapPlugins hsc_env f = map (\(PluginWithArgs p opts) -> f p opts) (plugins hsc_env) -- | Perform a constant operation by using all of the plugins in turn. -withPlugins_ :: Monad m => DynFlags -> ConstPluginOperation m a -> a -> m () -withPlugins_ df transformation input +withPlugins_ :: Monad m => HscEnv -> ConstPluginOperation m a -> a -> m () +withPlugins_ hsc_env transformation input = mapM_ (\(PluginWithArgs p opts) -> transformation p opts input) - (plugins df) + (plugins hsc_env) type FrontendPluginAction = [String] -> [(String, Maybe Phase)] -> Ghc () data FrontendPlugin = FrontendPlugin { ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -235,9 +235,8 @@ import GHC.Unit.Home import GHC.Unit.Types import GHC.Unit.Parser import GHC.Unit.Module -import {-# SOURCE #-} GHC.Driver.Plugins -import {-# SOURCE #-} GHC.Driver.Hooks import GHC.Builtin.Names ( mAIN_NAME ) +import {-# SOURCE #-} GHC.Driver.Hooks import {-# SOURCE #-} GHC.Unit.State (UnitState, emptyUnitState, UnitDatabase) import GHC.Driver.Phases ( Phase(..), phaseInputExt ) import GHC.Driver.Flags @@ -561,18 +560,6 @@ data DynFlags = DynFlags { frontendPluginOpts :: [String], -- ^ the @-ffrontend-opt@ flags given on the command line, in *reverse* -- order that they're specified on the command line. - cachedPlugins :: [LoadedPlugin], - -- ^ plugins dynamically loaded after processing arguments. What will be - -- loaded here is directed by pluginModNames. Arguments are loaded from - -- pluginModNameOpts. The purpose of this field is to cache the plugins so - -- they don't have to be loaded each time they are needed. See - -- 'GHC.Runtime.Loader.initializePlugins'. - staticPlugins :: [StaticPlugin], - -- ^ static plugins which do not need dynamic loading. These plugins are - -- intended to be added by GHC API users directly to this list. - -- - -- To add dynamically loaded plugins through the GHC API see - -- 'addPluginModuleName' instead. -- GHC API hooks hooks :: Hooks, @@ -1220,8 +1207,6 @@ defaultDynFlags mySettings llvmConfig = pluginModNames = [], pluginModNameOpts = [], frontendPluginOpts = [], - cachedPlugins = [], - staticPlugins = [], hooks = emptyHooks, outputFile_ = Nothing, @@ -1878,7 +1863,7 @@ clearPluginModuleNames :: DynFlags -> DynFlags clearPluginModuleNames d = d { pluginModNames = [] , pluginModNameOpts = [] - , cachedPlugins = [] } + } addPluginModuleNameOption :: String -> DynFlags -> DynFlags addPluginModuleNameOption optflag d = d { pluginModNameOpts = (mkModuleName m, option) : (pluginModNameOpts d) } ===================================== compiler/GHC/HsToCore.hs ===================================== @@ -198,7 +198,7 @@ deSugar hsc_env ; endPassIO hsc_env print_unqual CoreDesugarOpt ds_binds ds_rules_for_imps ; let used_names = mkUsedNames tcg_env - pluginModules = map lpModule (cachedPlugins (hsc_dflags hsc_env)) + pluginModules = map lpModule (hsc_plugins hsc_env) home_unit = hsc_home_unit hsc_env ; deps <- mkDependencies (homeUnitId home_unit) (map mi_module pluginModules) tcg_env ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -433,7 +433,6 @@ loadInterface doc_str mod from ; traceIf (text "Considering whether to load" <+> ppr mod <+> ppr from) -- Check whether we have the interface already - ; dflags <- getDynFlags ; hsc_env <- getTopEnv ; let home_unit = hsc_home_unit hsc_env ; case lookupIfaceByModule hpt (eps_PIT eps) mod of { @@ -551,7 +550,7 @@ loadInterface doc_str mod from ; -- invoke plugins with *full* interface, not final_iface, to ensure -- that plugins have access to declarations, etc. - res <- withPlugins dflags (\p -> interfaceLoadAction p) iface + res <- withPlugins hsc_env (\p -> interfaceLoadAction p) iface ; return (Succeeded res) }}}} ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -193,7 +193,7 @@ mkIfaceTc hsc_env safe_mode mod_details } = do let used_names = mkUsedNames tc_result - let pluginModules = map lpModule (cachedPlugins (hsc_dflags hsc_env)) + let pluginModules = map lpModule (hsc_plugins hsc_env) let home_unit = hsc_home_unit hsc_env deps <- mkDependencies (homeUnitId home_unit) (map mi_module pluginModules) tc_result ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -276,16 +276,16 @@ checkVersions hsc_env mod_summary iface -- | Check if any plugins are requesting recompilation checkPlugins :: HscEnv -> ModIface -> IfG RecompileRequired -checkPlugins hsc iface = liftIO $ do - new_fingerprint <- fingerprintPlugins hsc +checkPlugins hsc_env iface = liftIO $ do + new_fingerprint <- fingerprintPlugins hsc_env let old_fingerprint = mi_plugin_hash (mi_final_exts iface) - pr <- mconcat <$> mapM pluginRecompile' (plugins (hsc_dflags hsc)) + pr <- mconcat <$> mapM pluginRecompile' (plugins hsc_env) return $ pluginRecompileToRecompileRequired old_fingerprint new_fingerprint pr fingerprintPlugins :: HscEnv -> IO Fingerprint fingerprintPlugins hsc_env = - fingerprintPlugins' $ plugins (hsc_dflags hsc_env) + fingerprintPlugins' $ plugins hsc_env fingerprintPlugins' :: [PluginWithArgs] -> IO Fingerprint fingerprintPlugins' plugins = do ===================================== compiler/GHC/Runtime/Context.hs ===================================== @@ -18,6 +18,7 @@ import GHC.Prelude import GHC.Hs import GHC.Driver.Session +import {-# SOURCE #-} GHC.Driver.Plugins import GHC.Runtime.Eval.Types ( Resume ) @@ -240,8 +241,12 @@ data InteractiveContext -- ^ The function that is used for printing results -- of expressions in ghci and -e mode. - ic_cwd :: Maybe FilePath - -- virtual CWD of the program + ic_cwd :: Maybe FilePath, + -- ^ virtual CWD of the program + + ic_plugins :: ![LoadedPlugin] + -- ^ Cache of loaded plugins. We store them here to avoid having to + -- load them everytime we switch to the interctive context. } data InteractiveImport @@ -270,7 +275,9 @@ emptyInteractiveContext dflags ic_int_print = printName, -- System.IO.print by default ic_default = Nothing, ic_resume = [], - ic_cwd = Nothing } + ic_cwd = Nothing, + ic_plugins = [] + } icInteractiveModule :: InteractiveContext -> Module icInteractiveModule (InteractiveContext { ic_mod_index = index }) ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -218,11 +218,9 @@ execStmt' stmt stmt_text ExecOptions{..} = do -- Turn off -fwarn-unused-local-binds when running a statement, to hide -- warnings about the implicit bindings we introduce. - -- (This is basically `mkInteractiveHscEnv hsc_env`, except we unset - -- -wwarn-unused-local-binds) let ic = hsc_IC hsc_env -- use the interactive dflags idflags' = ic_dflags ic `wopt_unset` Opt_WarnUnusedLocalBinds - hsc_env' = mkInteractiveHscEnv (hsc_env{ hsc_IC = ic{ ic_dflags = idflags' } }) + hsc_env' = mkInteractiveHscEnv (hsc_env{ hsc_IC = ic{ ic_dflags = idflags' }}) r <- liftIO $ hscParsedStmt hsc_env' stmt ===================================== compiler/GHC/Runtime/Loader.hs ===================================== @@ -69,21 +69,22 @@ import Unsafe.Coerce ( unsafeCoerce ) -- flags. Should be called after command line arguments are parsed, but before -- actual compilation starts. Idempotent operation. Should be re-called if -- pluginModNames or pluginModNameOpts changes. -initializePlugins :: HscEnv -> DynFlags -> IO DynFlags -initializePlugins hsc_env df - | map lpModuleName (cachedPlugins df) - == pluginModNames df -- plugins not changed - && all (\p -> paArguments (lpPlugin p) - == argumentsForPlugin p (pluginModNameOpts df)) - (cachedPlugins df) -- arguments not changed - = return df -- no need to reload plugins +initializePlugins :: HscEnv -> IO HscEnv +initializePlugins hsc_env + -- plugins not changed + | map lpModuleName (hsc_plugins hsc_env) == pluginModNames dflags + -- arguments not changed + , all same_args (hsc_plugins hsc_env) + = return hsc_env -- no need to reload plugins | otherwise - = do loadedPlugins <- loadPlugins (hsc_env { hsc_dflags = df }) - let df' = df { cachedPlugins = loadedPlugins } - withPlugins df' runDflagsPlugin df' - - where argumentsForPlugin p = map snd . filter ((== lpModuleName p) . fst) - runDflagsPlugin p opts dynflags = dynflagsPlugin p opts dynflags + = do loaded_plugins <- loadPlugins hsc_env + let hsc_env' = hsc_env { hsc_plugins = loaded_plugins } + withPlugins hsc_env' driverPlugin hsc_env' + where + plugin_args = pluginModNameOpts dflags + same_args p = paArguments (lpPlugin p) == argumentsForPlugin p plugin_args + argumentsForPlugin p = map snd . filter ((== lpModuleName p) . fst) + dflags = hsc_dflags hsc_env loadPlugins :: HscEnv -> IO [LoadedPlugin] loadPlugins hsc_env ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -932,7 +932,7 @@ runMeta' show_code ppr_hs run_and_convert expr -- run plugins ; hsc_env <- getTopEnv - ; expr' <- withPlugins (hsc_dflags hsc_env) spliceRunAction expr + ; expr' <- withPlugins hsc_env spliceRunAction expr -- Desugar ; ds_expr <- initDsTc (dsLExpr expr') ===================================== compiler/GHC/Tc/Module.hs ===================================== @@ -326,7 +326,7 @@ tcRnModuleTcRnM hsc_env mod_sum reportUnusedNames tcg_env hsc_src ; -- add extra source files to tcg_dependent_files addDependentFiles src_files - ; tcg_env <- runTypecheckerPlugin mod_sum hsc_env tcg_env + ; tcg_env <- runTypecheckerPlugin mod_sum tcg_env ; -- Dump output and return tcDump tcg_env ; return tcg_env } @@ -3034,10 +3034,10 @@ Type Checker Plugins withTcPlugins :: HscEnv -> TcM a -> TcM a withTcPlugins hsc_env m = - do let plugins = getTcPlugins (hsc_dflags hsc_env) - case plugins of - [] -> m -- Common fast case - _ -> do ev_binds_var <- newTcEvBinds + case getTcPlugins hsc_env of + [] -> m -- Common fast case + plugins -> do + ev_binds_var <- newTcEvBinds (solvers,stops) <- unzip `fmap` mapM (startPlugin ev_binds_var) plugins -- This ensures that tcPluginStop is called even if a type -- error occurs during compilation (Fix of #10078) @@ -3052,13 +3052,13 @@ withTcPlugins hsc_env m = do s <- runTcPluginM start ev_binds_var return (solve s, stop s) -getTcPlugins :: DynFlags -> [GHC.Tc.Utils.Monad.TcPlugin] -getTcPlugins dflags = catMaybes $ mapPlugins dflags (\p args -> tcPlugin p args) +getTcPlugins :: HscEnv -> [GHC.Tc.Utils.Monad.TcPlugin] +getTcPlugins hsc_env = catMaybes $ mapPlugins hsc_env (\p args -> tcPlugin p args) withHoleFitPlugins :: HscEnv -> TcM a -> TcM a withHoleFitPlugins hsc_env m = - case (getHfPlugins (hsc_dflags hsc_env)) of + case getHfPlugins hsc_env of [] -> m -- Common fast case plugins -> do (plugins,stops) <- unzip `fmap` mapM startPlugin plugins -- This ensures that hfPluginStop is called even if a type @@ -3074,18 +3074,19 @@ withHoleFitPlugins hsc_env m = do ref <- init return (plugin ref, stop ref) -getHfPlugins :: DynFlags -> [HoleFitPluginR] -getHfPlugins dflags = - catMaybes $ mapPlugins dflags (\p args -> holeFitPlugin p args) +getHfPlugins :: HscEnv -> [HoleFitPluginR] +getHfPlugins hsc_env = + catMaybes $ mapPlugins hsc_env (\p args -> holeFitPlugin p args) runRenamerPlugin :: TcGblEnv -> HsGroup GhcRn -> TcM (TcGblEnv, HsGroup GhcRn) runRenamerPlugin gbl_env hs_group = do - dflags <- getDynFlags - withPlugins dflags - (\p opts (e, g) -> ( mark_plugin_unsafe dflags >> renamedResultAction p opts e g)) + hsc_env <- getTopEnv + withPlugins hsc_env + (\p opts (e, g) -> ( mark_plugin_unsafe (hsc_dflags hsc_env) + >> renamedResultAction p opts e g)) (gbl_env, hs_group) @@ -3103,11 +3104,11 @@ getRenamedStuff tc_result , tcg_rn_exports tc_result, tcg_doc_hdr tc_result ) ) (tcg_rn_decls tc_result) -runTypecheckerPlugin :: ModSummary -> HscEnv -> TcGblEnv -> TcM TcGblEnv -runTypecheckerPlugin sum hsc_env gbl_env = do - let dflags = hsc_dflags hsc_env - withPlugins dflags - (\p opts env -> mark_plugin_unsafe dflags +runTypecheckerPlugin :: ModSummary -> TcGblEnv -> TcM TcGblEnv +runTypecheckerPlugin sum gbl_env = do + hsc_env <- getTopEnv + withPlugins hsc_env + (\p opts env -> mark_plugin_unsafe (hsc_dflags hsc_env) >> typeCheckResultAction p opts sum env) gbl_env ===================================== docs/users_guide/extending_ghc.rst ===================================== @@ -1341,13 +1341,17 @@ this idea can be seen below: import GHC.Tc.Utils.Monad plugin :: Plugin - plugin = defaultPlugin { dynflagsPlugin = hooksP } - - hooksP :: [CommandLineOption] -> DynFlags -> IO DynFlags - hooksP opts dflags = return $ dflags - { hooks = (hooks dflags) - { runMetaHook = Just (fakeRunMeta opts) } - } + plugin = driverPlugin { driverPlugin = hooksP } + + hooksP :: [CommandLineOption] -> HscEnv -> IO HscEnv + hooksP opts hsc_env = do + let dflags = hsc_dflags hsc_env + dflags' = dflags + { hooks = (hooks dflags) + { runMetaHook = Just (fakeRunMeta opts) } + } + hsc_env' = hsc_env { hsc_dflags = dflags' } + return hsc_env' -- This meta hook doesn't actually care running code in splices, -- it just replaces any expression splice with the "0" ===================================== ghc/GHCi/UI.hs ===================================== @@ -81,8 +81,6 @@ import GHC.Unit.Module.ModSummary import GHC.Data.StringBuffer import GHC.Utils.Outputable -import GHC.Runtime.Loader ( initializePlugins ) - -- Other random utilities import GHC.Types.Basic hiding ( isTopLevel ) import GHC.Settings.Config @@ -2943,10 +2941,7 @@ newDynFlags interactive_only minus_opts = do when (interactive_only && packageFlagsChanged idflags1 idflags0) $ do liftIO $ hPutStrLn stderr "cannot set package flags with :seti; use :set" - -- Load any new plugins - hsc_env0 <- GHC.getSession - idflags2 <- liftIO (initializePlugins hsc_env0 idflags1) - GHC.setInteractiveDynFlags idflags2 + GHC.setInteractiveDynFlags idflags1 installInteractivePrint (interactivePrint idflags1) False dflags0 <- getDynFlags ===================================== ghc/Main.hs ===================================== @@ -36,7 +36,6 @@ import GHC.Platform.Host #if defined(HAVE_INTERNAL_INTERPRETER) import GHCi.UI ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings ) -import GHC.Runtime.Loader ( initializePlugins ) #endif import GHC.Runtime.Loader ( loadFrontendPlugin ) @@ -247,9 +246,8 @@ main' postLoadMode dflags0 args flagWarnings = do DoMake -> doMake srcs DoMkDependHS -> doMkDependHS (map fst srcs) StopBefore p -> liftIO (oneShot hsc_env p srcs) - DoInteractive -> ghciUI hsc_env dflags6 srcs Nothing - DoEval exprs -> ghciUI hsc_env dflags6 srcs $ Just $ - reverse exprs + DoInteractive -> ghciUI srcs Nothing + DoEval exprs -> ghciUI srcs $ Just $ reverse exprs DoAbiHash -> abiHash (map fst srcs) ShowPackages -> liftIO $ showUnits dflags6 DoFrontend f -> doFrontend f srcs @@ -257,16 +255,12 @@ main' postLoadMode dflags0 args flagWarnings = do liftIO $ dumpFinalStats dflags6 -ghciUI :: HscEnv -> DynFlags -> [(FilePath, Maybe Phase)] -> Maybe [String] - -> Ghc () +ghciUI :: [(FilePath, Maybe Phase)] -> Maybe [String] -> Ghc () #if !defined(HAVE_INTERNAL_INTERPRETER) -ghciUI _ _ _ _ = +ghciUI _ _ = throwGhcException (CmdLineError "not built for interactive use") #else -ghciUI hsc_env dflags0 srcs maybe_expr = do - dflags1 <- liftIO (initializePlugins hsc_env dflags0) - _ <- GHC.setSessionDynFlags dflags1 - interactiveUI defaultGhciSettings srcs maybe_expr +ghciUI srcs maybe_expr = interactiveUI defaultGhciSettings srcs maybe_expr #endif ===================================== testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs ===================================== @@ -10,13 +10,17 @@ import GHC.Driver.Hooks import GHC.Tc.Utils.Monad plugin :: Plugin -plugin = defaultPlugin { dynflagsPlugin = hooksP } +plugin = defaultPlugin { driverPlugin = hooksP } -hooksP :: [CommandLineOption] -> DynFlags -> IO DynFlags -hooksP opts dflags = return $ dflags - { hooks = (hooks dflags) - { runMetaHook = Just (fakeRunMeta opts) } - } +hooksP :: [CommandLineOption] -> HscEnv -> IO HscEnv +hooksP opts hsc_env = do + let dflags = hsc_dflags hsc_env + dflags' = dflags + { hooks = (hooks dflags) + { runMetaHook = Just (fakeRunMeta opts) } + } + hsc_env' = hsc_env { hsc_dflags = dflags' } + return hsc_env' -- This meta hook doesn't actually care running code in splices, -- it just replaces any expression splice with the "0" ===================================== testsuite/tests/plugins/static-plugins.hs ===================================== @@ -1,9 +1,13 @@ module Main where -import GHC.Types.Avail -import Control.Monad.IO.Class +import GHC.Driver.Env import GHC.Driver.Session (getDynFlags, parseDynamicFlagsCmdLine, defaultFatalMessager, defaultFlushOut) +import GHC.Driver.Plugins +import GHC.Driver.Monad + +import GHC.Types.Avail +import Control.Monad.IO.Class import GHC import GHC.Fingerprint.Type import GHC.Hs.Decls @@ -12,7 +16,6 @@ import GHC.Hs.Expr import GHC.Hs.Extension import GHC.Hs.ImpExp import GHC.Utils.Outputable -import GHC.Driver.Plugins import System.Environment import GHC.Tc.Types @@ -65,9 +68,10 @@ main = do target <- guessTarget "static-plugins-module.hs" Nothing setTargets [target] + modifySession (\hsc_env -> hsc_env { hsc_static_plugins = the_plugins}) + dflags <- getSessionDynFlags - setSessionDynFlags dflags { staticPlugins = the_plugins - , outputFile_ = Nothing } + setSessionDynFlags dflags { outputFile_ = Nothing } load LoadAllTargets ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 4d0498d503bd51b7d7626497580232685a2691a1 +Subproject commit 25fa8fde84701c010fa466c2648f8f6d10265e8f View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53ad67eacacde8fde452f1a323d5886183375182...72f2257c792e6178933f12ee3401939da11584b6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53ad67eacacde8fde452f1a323d5886183375182...72f2257c792e6178933f12ee3401939da11584b6 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 Sat Nov 21 06:14:51 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 01:14:51 -0500 Subject: [Git][ghc/ghc][master] Add regression test for #10504 Message-ID: <5fb8b05ba46fe_36a73fd2f208ef804839b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - 4 changed files: - + testsuite/tests/typecheck/should_compile/T10504.hs - + testsuite/tests/typecheck/should_compile/T10504.stderr - + testsuite/tests/typecheck/should_compile/T10504a.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== testsuite/tests/typecheck/should_compile/T10504.hs ===================================== @@ -0,0 +1,5 @@ +module T10504 where + +import T10504a + +{-# SPECIALISE myfun :: Double #-} ===================================== testsuite/tests/typecheck/should_compile/T10504.stderr ===================================== @@ -0,0 +1,3 @@ + +T10504.hs:5:1: warning: + SPECIALISE pragma for non-overloaded function ‘myfun’ ===================================== testsuite/tests/typecheck/should_compile/T10504a.hs ===================================== @@ -0,0 +1,6 @@ +module T10504a where + +{-# INLINABLE myfun #-} + +myfun :: a +myfun = undefined ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -468,6 +468,7 @@ test('T10494', normal, compile, ['']) test('T10493', normal, compile, ['']) test('T10428', normal, compile, ['']) test('RepArrow', normal, compile, ['']) +test('T10504', normal, multimod_compile, ['T10504', '-O -v0']) test('T10562', normal, compile, ['']) test('T10564', normal, compile, ['']) test('Vta1', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ddbeeb3c7dc7a2781801cc0e6539d2b4b0e97a20 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ddbeeb3c7dc7a2781801cc0e6539d2b4b0e97a20 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 Sat Nov 21 06:15:29 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 01:15:29 -0500 Subject: [Git][ghc/ghc][master] dwarf: Apply info table offset consistently Message-ID: <5fb8b0816fba0_36a73fd2f90f5f304866b0@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Dwarf/Types.hs Changes: ===================================== compiler/GHC/CmmToAsm/Dwarf/Types.hs ===================================== @@ -178,7 +178,8 @@ pprDwarfInfoOpen platform haveSrc (DwarfCompileUnit _ name producer compDir lowL $$ pprString producer $$ pprData4 dW_LANG_Haskell $$ pprString compDir - $$ pprWord platform (pdoc platform lowLabel) + -- Offset due to Note [Info Offset] + $$ pprWord platform (pdoc platform lowLabel <> text "-1") $$ pprWord platform (pdoc platform highLabel) $$ if haveSrc then sectionOffset platform (ptext lineLbl) (ptext dwarfLineLabel) @@ -189,7 +190,8 @@ pprDwarfInfoOpen platform _ (DwarfSubprogram _ name label parent) = $$ pprString name $$ pprLabelString platform label $$ pprFlag (externallyVisibleCLabel label) - $$ pprWord platform (pdoc platform label) + -- Offset due to Note [Info Offset] + $$ pprWord platform (pdoc platform label <> text "-1") $$ pprWord platform (pdoc platform $ mkAsmTempProcEndLabel label) $$ pprByte 1 $$ pprByte dW_OP_call_frame_cfa @@ -256,7 +258,10 @@ pprDwarfARanges platform arngs unitU = $$ pprWord platform (char '0') pprDwarfARange :: Platform -> DwarfARange -> SDoc -pprDwarfARange platform arng = pprWord platform (pdoc platform $ dwArngStartLabel arng) $$ pprWord platform length +pprDwarfARange platform arng = + -- Offset due to Note [Info offset]. + pprWord platform (pdoc platform (dwArngStartLabel arng) <> text "-1") + $$ pprWord platform length where length = pdoc platform (dwArngEndLabel arng) <> char '-' <> pdoc platform (dwArngStartLabel arng) @@ -356,7 +361,7 @@ pprFrameProc platform frameLbl initUw (DwarfFrameProc procLbl hasInfo blocks) fdeEndLabel = mkAsmTempDerivedLabel procLbl (fsLit "_fde_end") procEnd = mkAsmTempProcEndLabel procLbl ifInfo str = if hasInfo then text str else empty - -- see [Note: Info Offset] + -- see Note [Info Offset] in vcat [ whenPprDebug $ text "# Unwinding for" <+> pdoc platform procLbl <> colon , pprData4' (pdoc platform fdeEndLabel <> char '-' <> pdoc platform fdeLabel) , pdoc platform fdeLabel <> colon @@ -398,7 +403,7 @@ pprFrameBlock platform (DwarfFrameBlock hasInfo uws0) = in if oldUws == uws then (empty, oldUws) - else let -- see [Note: Info Offset] + else let -- see Note [Info Offset] needsOffset = firstDecl && hasInfo lblDoc = pdoc platform lbl <> if needsOffset then text "-1" else empty @@ -407,6 +412,7 @@ pprFrameBlock platform (DwarfFrameBlock hasInfo uws0) = in (doc, uws) -- Note [Info Offset] +-- ~~~~~~~~~~~~~~~~~~ -- -- GDB was pretty much written with C-like programs in mind, and as a -- result they assume that once you have a return address, it is a @@ -426,6 +432,14 @@ pprFrameBlock platform (DwarfFrameBlock hasInfo uws0) = -- correct function name for the frame, as that uses the symbol table, -- which we can not manipulate as easily. -- +-- We apply this offset in several places: +-- +-- * unwind information in .debug_frames +-- * the subprogram and lexical_block DIEs in .debug_info +-- * the ranges in .debug_aranges +-- +-- In the latter two cases we apply the offset unconditionally. +-- -- There's a GDB patch to address this at [1]. At the moment of writing -- it's not merged, so I recommend building GDB with the patch if you -- care about unwinding. The hack above doesn't cover every case. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a4a6dc2a90e28c34054d0cfd4c6fd962bf4adc2e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a4a6dc2a90e28c34054d0cfd4c6fd962bf4adc2e 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 Sat Nov 21 06:16:04 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 01:16:04 -0500 Subject: [Git][ghc/ghc][master] hadrian: Disable stripping when debug information is enabled Message-ID: <5fb8b0a497b9a_36a71579be444893d6@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 1 changed file: - hadrian/src/Flavour.hs Changes: ===================================== hadrian/src/Flavour.hs ===================================== @@ -80,9 +80,11 @@ werror = addArgs (builder Ghc ? notStage0 ? arg "-Werror") -- | Build C and Haskell objects with debugging information. enableDebugInfo :: Flavour -> Flavour -enableDebugInfo = addArgs $ mconcat - [ builder (Ghc CompileHs) ? notStage0 ? arg "-g3" - , builder (Cc CompileC) ? notStage0 ? arg "-g3" +enableDebugInfo = addArgs $ notStage0 ? mconcat + [ builder (Ghc CompileHs) ? arg "-g3" + , builder (Cc CompileC) ? arg "-g3" + , builder (Cabal Setup) ? arg "--disable-library-stripping" + , builder (Cabal Setup) ? arg "--disable-executable-stripping" ] -- | Enable the ticky-ticky profiler in stage2 GHC View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69bfbc216c2278c9796aa999c7815c19c12b0f2c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69bfbc216c2278c9796aa999c7815c19c12b0f2c 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 Sat Nov 21 11:30:28 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sat, 21 Nov 2020 06:30:28 -0500 Subject: [Git][ghc/ghc][wip/T18914] 19 commits: Export indexError from GHC.Ix (#18579) Message-ID: <5fb8fa54b1725_36a73fd2caa64b90498033@gitlab.mail> Ryan Scott pushed to branch wip/T18914 at Glasgow Haskell Compiler / GHC Commits: 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 207c8d41 by Ryan Scott at 2020-11-21T06:29:16-05:00 Use HsOuterExplicit in instance sigs in deriving-generated code Issue #18914 revealed that `GeneralizedNewtypeDeriving` would generate code that mentions unbound type variables, which is dangerously fragile. The problem (and fix) is described in the new `Wrinkle: Use HsOuterExplicit` in `Note [GND and QuantifiedConstraints]`. The gist of it: make sure to put the top-level `forall`s in `deriving`-generated instance signatures in an `HsOuterExplicit` to ensure that they scope over the bodies of methods correctly. A side effect of this process is that it will expand any type synonyms in the instance signature, which will surface any `forall`s that are hidden underneath type synonyms (such as in the test case for #18914). While I was in town, I also performed some maintenance on `NewHsTypeX`, which powers `GeneralizedNewtypeDeriving`: * I renamed `NewHsTypeX` to `HsCoreTy`, which more accurately describes its intended purpose (#15706). I also made `HsCoreTy` a type synonym instead of a newtype, as making it a distinct data type wasn't buying us much. * To make sure that mistakes similar to #18914 do not occur later, I added an additional validity check when renaming `HsCoreTy`s that complains if an `HsCoreTy`s contains an out-of-scope type variable. See the new `Note [Renaming HsCoreTys]` in `GHC.Rename.HsType` for the details. Fixes #15706. Fixes #18914. Bumps the `haddock` submodule. - - - - - dd250208 by Ryan Scott at 2020-11-21T06:29:16-05:00 testsuite: Mark T14702 as fragile on Windows See #18953. - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b826244aaf61cf753449186761e0ad59c4f74eec...dd250208bc14be4919bd151b98d5ddc59f1fd070 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b826244aaf61cf753449186761e0ad59c4f74eec...dd250208bc14be4919bd151b98d5ddc59f1fd070 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 Sat Nov 21 16:00:18 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 11:00:18 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fb939929446b_36a7643e30051537a@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 4927ee21 by Moritz Angermann at 2020-11-21T11:00:11-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4927ee2115139c3aa89ec90492f3c31d388467a1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4927ee2115139c3aa89ec90492f3c31d388467a1 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 Sat Nov 21 16:23:26 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 11:23:26 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/unloading-fixes Message-ID: <5fb93efef15eb_36a73fd2f1d8640051675c@gitlab.mail> Ben Gamari pushed new branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/unloading-fixes 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 Sat Nov 21 16:28:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 11:28:56 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18821-8.8 Message-ID: <5fb940486d14_36a71579be445183f@gitlab.mail> Ben Gamari pushed new branch wip/T18821-8.8 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18821-8.8 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 Sat Nov 21 18:13:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 13:13:38 -0500 Subject: [Git][ghc/ghc][wip/ticky-eventlog] 157 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fb958d2401c9_36a715ae31b05362fc@gitlab.mail> Ben Gamari pushed to branch wip/ticky-eventlog at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Arity.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5517f893601fce0887740d645e6147ef8d8f4868...7e93ae8b2257c17d5ae5ef7832db723e897c8e8b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5517f893601fce0887740d645e6147ef8d8f4868...7e93ae8b2257c17d5ae5ef7832db723e897c8e8b 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 Sat Nov 21 18:34:00 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 13:34:00 -0500 Subject: [Git][ghc/ghc][wip/T18234] 4 commits: hadrian: fix ghc-pkg uses (#17601) Message-ID: <5fb95d9893611_36a71600f92c5599e3@gitlab.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: 0c4199d0 by Sylvain Henry at 2020-11-20T17:34:20+01:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - c3409dd8 by Ben Gamari at 2020-11-21T13:33:46-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 6f403878 by Ben Gamari at 2020-11-21T13:33:46-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - b789f5f9 by Ben Gamari at 2020-11-21T13:33:46-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 3 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - hadrian/src/Settings/Builders/GhcPkg.hs Changes: ===================================== .gitlab-ci.yml ===================================== @@ -257,6 +257,33 @@ validate-x86_64-linux-deb9-unreg-hadrian: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +validate-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV" + variables: + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*cross-compilation.*/' + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build needs: [lint-linters, lint-submods] ===================================== .gitlab/ci.sh ===================================== @@ -2,6 +2,8 @@ # shellcheck disable=SC2230 # This is the primary driver of the GitLab CI infrastructure. +# Run `ci.sh usage` for usage information. + set -e -o pipefail @@ -17,6 +19,62 @@ fi source $TOP/.gitlab/common.sh +function usage() { + cat < /dev/null; then @@ -53,11 +111,11 @@ function setup_locale() { function mingw_init() { case "$MSYSTEM" in MINGW32) - triple="i386-unknown-mingw32" + target_triple="i386-unknown-mingw32" boot_triple="i386-unknown-mingw32" # triple of bootstrap GHC ;; MINGW64) - triple="x86_64-unknown-mingw32" + target_triple="x86_64-unknown-mingw32" boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC ;; *) @@ -320,8 +378,8 @@ function configure() { end_section "booting" local target_args="" - if [[ -n "$triple" ]]; then - target_args="--target=$triple" + if [[ -n "$target_triple" ]]; then + target_args="--target=$target_triple" fi start_section "configuring" @@ -341,6 +399,11 @@ function build_make() { if [[ -z "$BIN_DIST_PREP_TAR_COMP" ]]; then fail "BIN_DIST_PREP_TAR_COMP is not set" fi + if [[ -n "$VERBOSE" ]]; then + MAKE_ARGS="$MAKE_ARGS V=1" + else + MAKE_ARGS="$MAKE_ARGS V=0" + fi echo "include mk/flavours/${BUILD_FLAVOUR}.mk" > mk/build.mk echo 'GhcLibHcOpts+=-haddock' >> mk/build.mk @@ -367,6 +430,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -387,6 +455,11 @@ function build_hadrian() { } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -434,6 +507,7 @@ function clean() { function run_hadrian() { if [ -z "$BIGNUM_BACKEND" ]; then BIGNUM_BACKEND="gmp"; fi + if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi run hadrian/build-cabal \ --flavour="$BUILD_FLAVOUR" \ -j"$cores" \ @@ -473,9 +547,15 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in + usage) usage ;; setup) setup && cleanup_submodules ;; configure) configure ;; build_make) build_make ;; ===================================== hadrian/src/Settings/Builders/GhcPkg.hs ===================================== @@ -8,8 +8,7 @@ ghcPkgBuilderArgs = mconcat verbosity <- expr getVerbosity stage <- getStage pkgDb <- expr $ packageDbPath stage - mconcat [ arg "--global-package-db" - , arg pkgDb + mconcat [ use_db pkgDb , arg "register" , verbosity < Chatty ? arg "-v0" ] @@ -17,8 +16,7 @@ ghcPkgBuilderArgs = mconcat verbosity <- expr getVerbosity stage <- getStage pkgDb <- expr $ packageDbPath stage - mconcat [ arg "--global-package-db" - , arg pkgDb + mconcat [ use_db pkgDb , arg "unregister" , arg "--force" , verbosity < Chatty ? arg "-v0" @@ -29,10 +27,30 @@ ghcPkgBuilderArgs = mconcat config <- expr $ pkgInplaceConfig context stage <- getStage pkgDb <- expr $ packageDbPath stage - mconcat [ notStage0 ? arg "--global-package-db" - , notStage0 ? arg pkgDb + mconcat [ notStage0 ? use_db pkgDb , arg "update" , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs , arg config ] ] + where + use_db db = mconcat + -- We use ghc-pkg's --global-package-db to manipulate our databases. + -- We can't use --package-db (at least with stage0's ghc-pkg) + -- because units in stage0's global package db would be in scope and + -- ghc-pkg would disallow us the register a second "rts" unit in our + -- database. + -- + -- However ghc-pkg uses the path to the global package db to find + -- the compiler "settings" file... So when it finds our newly + -- generated settings file in _build/stageN, it may crash if it + -- isn't the format it expects (#17601). + -- + -- By chance, ghc-pkg only needs the "settings" file to query the + -- arch/os to generate the path to the user package db, which we + -- don't need. So we disable it below to avoid failures. + [ arg "--no-user-package-db" + , arg "--global-package-db" + , arg db + ] + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b2b1ccad1c479557895a978e4e6b01edcafa0dd1...b789f5f997f1873116c52486198520db1abea2e6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b2b1ccad1c479557895a978e4e6b01edcafa0dd1...b789f5f997f1873116c52486198520db1abea2e6 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 Sat Nov 21 19:08:49 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 14:08:49 -0500 Subject: [Git][ghc/ghc][wip/bump-time] 34 commits: testsuite: Add testcase for #18733 Message-ID: <5fb965c17bd8b_36a71579be445634c2@gitlab.mail> Ben Gamari pushed to branch wip/bump-time at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 0d00e3c6 by Ben Gamari at 2020-11-21T14:08:28-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/237d72684b8b9bbd772942d113804e04c0784a97...0d00e3c67ef8f78ff1e7f8ea2009b6fc770b44a4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/237d72684b8b9bbd772942d113804e04c0784a97...0d00e3c67ef8f78ff1e7f8ea2009b6fc770b44a4 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 Sat Nov 21 19:12:54 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 14:12:54 -0500 Subject: [Git][ghc/ghc][wip/T18043] 28 commits: nativeGen/dwarf: Fix procedure end addresses Message-ID: <5fb966b6e24a6_36a73fd2f90f5f3056575@gitlab.mail> Ben Gamari pushed to branch wip/T18043 at Glasgow Haskell Compiler / GHC Commits: 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - a5b6b984 by Ben Gamari at 2020-11-21T14:12:45-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aaaa833b4d1db288b357f6c1c4bea34a6636f5bf...a5b6b9842cc6353dbcf520c3774527be10273096 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aaaa833b4d1db288b357f6c1c4bea34a6636f5bf...a5b6b9842cc6353dbcf520c3774527be10273096 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 Sat Nov 21 20:22:35 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 15:22:35 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 14 commits: users-guide: A bit of clean-up in profiling flag documentation Message-ID: <5fb9770b6c977_36a73fd2f1fdd7f857502b@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 04cf84d7 by Ben Gamari at 2020-11-21T15:22:27-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - 3f128576 by Ben Gamari at 2020-11-21T15:22:27-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 58ed4921 by Ben Gamari at 2020-11-21T15:22:27-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - 08892130 by Ben Gamari at 2020-11-21T15:22:27-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 8837713d by Ben Gamari at 2020-11-21T15:22:27-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 14ce787e by Ben Gamari at 2020-11-21T15:22:27-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Recomp/Flags.hs - compiler/GHC/Runtime/Context.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Runtime/Loader.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Module.hs - compiler/ghc.cabal.in - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debugging.rst - docs/users_guide/extending_ghc.rst The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/412fd5000d947b6bb7f4285cb58936295a9b426f...14ce787eabdb502146ff5c1fa29a0d78bc17bc4e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/412fd5000d947b6bb7f4285cb58936295a9b426f...14ce787eabdb502146ff5c1fa29a0d78bc17bc4e 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 Sat Nov 21 20:53:15 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 21 Nov 2020 15:53:15 -0500 Subject: [Git][ghc/ghc][wip/fix-hadrian-ticky] 47 commits: nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags Message-ID: <5fb97e3b21587_36a71600f92c57649e@gitlab.mail> Ben Gamari pushed to branch wip/fix-hadrian-ticky at Glasgow Haskell Compiler / GHC Commits: fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7566dff3 by Ben Gamari at 2020-11-21T15:41:08-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - 487b48ca by Ben Gamari at 2020-11-21T15:53:07-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 246116f3 by Ben Gamari at 2020-11-21T15:53:07-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - a47974a2 by Ben Gamari at 2020-11-21T15:53:07-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - eb581f0f by Ben Gamari at 2020-11-21T15:53:08-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a1071855094b4578917a1eb53f7b4417ef0a2c3...eb581f0f50bd6c34bcbd8c3518e8d4c44bef495c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a1071855094b4578917a1eb53f7b4417ef0a2c3...eb581f0f50bd6c34bcbd8c3518e8d4c44bef495c 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 Sun Nov 22 01:57:33 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 21 Nov 2020 20:57:33 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: rts: Post ticky entry counts to the eventlog Message-ID: <5fb9c58d2d380_36a73fd2f1d8640058563f@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - 26a7c37f by Ben Gamari at 2020-11-21T20:57:24-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 18 changed files: - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debugging.rst - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/profiling.rst - includes/rts/EventLogFormat.h - includes/rts/Flags.h - rts/Proftimer.c - rts/Proftimer.h - rts/RtsFlags.c - rts/RtsStartup.c - rts/Ticky.c - rts/Ticky.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/sm/GC.c Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -138,7 +138,13 @@ outputC dflags filenm cmm_stream packages = hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n") hPutStr h "#include \"Stg.h\"\n" let platform = targetPlatform dflags - writeC = printForC dflags h . cmmToC platform + writeC cmm = do + let doc = cmmToC platform cmm + dumpIfSet_dyn dflags Opt_D_dump_c_backend + "C backend output" + FormatC + doc + printForC dflags h doc Stream.consume cmm_stream writeC {- ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -49,6 +49,7 @@ data DumpFlag | Opt_D_dump_asm_conflicts | Opt_D_dump_asm_stats | Opt_D_dump_asm_expanded + | Opt_D_dump_c_backend | Opt_D_dump_llvm | Opt_D_dump_core_stats | Opt_D_dump_deriv ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2539,6 +2539,8 @@ dynamic_flags_deps = [ (setDumpFlag Opt_D_dump_asm_expanded) , make_ord_flag defGhcFlag "ddump-llvm" (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm) + , make_ord_flag defGhcFlag "ddump-c-backend" + (NoArg $ setDumpFlag' Opt_D_dump_c_backend) , make_ord_flag defGhcFlag "ddump-deriv" (setDumpFlag Opt_D_dump_deriv) , make_ord_flag defGhcFlag "ddump-ds" ===================================== docs/users_guide/debugging.rst ===================================== @@ -552,6 +552,15 @@ LLVM code generator LLVM code from the :ref:`LLVM code generator ` +C code generator +~~~~~~~~~~~~~~~~ + +.. ghc-flag:: -ddump-c-backend + :shortdesc: Dump C code produced by the C (unregisterised) backend. + :type: dynamic + + :shortdesc: Dump C code produced by the C (unregisterised) backend. + Native code generator ~~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/eventlog-formats.rst ===================================== @@ -755,3 +755,34 @@ intended to provide insight into fragmentation of the non-moving heap. :field Word32: number of live blocks. Describes the occupancy of the *blk_sz* sub-heap. + +Ticky counters +~~~~~~~~~~~~~~ + +Programs compiled with :ghc-flag:`-ticky` and :ghc-flag:`-eventlog` and invoked +with ``+RTS -lT`` will emit periodic samples of the ticky entry counters to the +eventlog. + +.. event-type:: TICKY_COUNTER_DEF + + :tag: 210 + :length: variable + :field Word64: counter ID + :field Word16: arity/field count + :field String: argument kinds. This is the same as the synonymous field in the + textual ticky summary. + :field String: counter name + + Defines a ticky counter. + +.. event-type:: TICKY_COUNTER_SAMPLE + + :tag: 211 + :length: fixed + :field Word64: counter ID + :field Word64: number of times closures of this type has been entered. + :field Word64: number of allocations (words) + :field Word64: number of times this has been allocated (words). Only + produced for modules compiled with :ghc-flag:`-ticky-allocd`. + + Records the counter statistics at a moment in time. ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -118,5 +118,3 @@ -syslib -this-component-id -ticky-LNE --ticky-allocd --ticky-dyn-thunk ===================================== docs/users_guide/profiling.rst ===================================== @@ -1681,11 +1681,27 @@ Using “ticky-ticky” profiling (for implementors) single: ticky-ticky profiling .. ghc-flag:: -ticky - :shortdesc: :ref:`Turn on ticky-ticky profiling ` + :shortdesc: Turn on :ref:`ticky-ticky profiling ` :type: dynamic :category: - Enable ticky-ticky profiling. + Enable ticky-ticky profiling. By default this only tracks the allocations + *by* each closure type. See :ghc-flag:`-ticky-allocd` to keep track of + allocations *of* each closure type as well. + +.. ghc-flag:: -ticky-allocd + :shortdesc: Track the number of times each closure type is allocated. + :type: dynamic + :category: + + Keep track of how much each closure type is allocated. + +.. ghc-flag:: -ticky-dyn-thunk + :shortdesc: Track allocations of dynamic thunks + :type: dynamic + :category: + + Track allocations of dynamic thunks. Because ticky-ticky profiling requires a certain familiarity with GHC internals, we have moved the documentation to the GHC developers wiki. ===================================== includes/rts/EventLogFormat.h ===================================== @@ -154,12 +154,15 @@ #define EVENT_CONC_UPD_REM_SET_FLUSH 206 #define EVENT_NONMOVING_HEAP_CENSUS 207 +#define EVENT_TICKY_COUNTER_DEF 210 +#define EVENT_TICKY_COUNTER_SAMPLE 211 + /* * The highest event code +1 that ghc itself emits. Note that some event * ranges higher than this are reserved but not currently emitted by ghc. * This must match the size of the EventDesc[] array in EventLog.c */ -#define NUM_GHC_EVENT_TAGS 208 +#define NUM_GHC_EVENT_TAGS 212 #if 0 /* DEPRECATED EVENTS: */ /* we don't actually need to record the thread, it's implicit */ ===================================== includes/rts/Flags.h ===================================== @@ -176,6 +176,7 @@ typedef struct _TRACE_FLAGS { bool nonmoving_gc; /* trace nonmoving GC events */ bool sparks_sampled; /* trace spark events by a sampled method */ bool sparks_full; /* trace spark events 100% accurately */ + bool ticky; /* trace ticky-ticky samples */ bool user; /* trace user events (emitted from Haskell code) */ char *trace_output; /* output filename for eventlog */ } TRACE_FLAGS; ===================================== rts/Proftimer.c ===================================== @@ -20,6 +20,12 @@ static bool do_prof_ticks = false; // enable profiling ticks static bool do_heap_prof_ticks = false; // enable heap profiling ticks +// Sampling of Ticky-Ticky profiler to eventlog +#if defined(TICKY_TICKY) && defined(TRACING) +static int ticks_to_ticky_sample = 0; +bool performTickySample = false; +#endif + // Number of ticks until next heap census static int ticks_to_heap_profile; @@ -83,6 +89,16 @@ handleProfTick(void) } #endif +#if defined(TICKY_TICKY) && defined(TRACING) + if (RtsFlags.TraceFlags.ticky) { + ticks_to_ticky_sample--; + if (ticks_to_ticky_sample <= 0) { + ticks_to_ticky_sample = RtsFlags.ProfFlags.heapProfileIntervalTicks; + performTickySample = true; + } + } +#endif + if (RELAXED_LOAD(&do_heap_prof_ticks)) { ticks_to_heap_profile--; if (ticks_to_heap_profile <= 0) { ===================================== rts/Proftimer.h ===================================== @@ -17,5 +17,6 @@ void stopHeapProfTimer ( void ); void startHeapProfTimer ( void ); extern bool performHeapProfile; +extern bool performTickySample; #include "EndPrivate.h" ===================================== rts/RtsFlags.c ===================================== @@ -235,6 +235,7 @@ void initRtsFlagsDefaults(void) RtsFlags.TraceFlags.sparks_sampled= false; RtsFlags.TraceFlags.sparks_full = false; RtsFlags.TraceFlags.user = false; + RtsFlags.TraceFlags.ticky = false; RtsFlags.TraceFlags.trace_output = NULL; #endif @@ -403,6 +404,9 @@ usage_text[] = { " p par spark events (sampled)", " f par spark events (full detail)", " u user events (emitted from Haskell code)", +#if defined(TICKY_TICKY) +" T ticky-ticky counter samples", +#endif " a all event classes above", # if defined(DEBUG) " t add time stamps (only useful with -v)", @@ -1855,6 +1859,11 @@ static void normaliseRtsOpts (void) "the compacting collector."); errorUsage(); } + + if (RtsFlags.TraceFlags.ticky && RtsFlags.TickyFlags.showTickyStats) { + barf("The ticky-ticky eventlog output cannot be used in conjunction with\n" + "+RTS -r."); + } } static void errorUsage (void) @@ -2297,6 +2306,15 @@ static void read_trace_flags(const char *arg) RtsFlags.TraceFlags.user = enabled; enabled = true; break; + case 'T': +#if defined(TICKY_TICKY) + RtsFlags.TraceFlags.ticky = enabled; + enabled = true; + break; +#else + errorBelch("Program not compiled with ticky-ticky support"); + break; +#endif default: errorBelch("unknown trace option: %c",*c); break; ===================================== rts/RtsStartup.c ===================================== @@ -487,6 +487,17 @@ hs_exit_(bool wait_foreign) */ exitTimer(true); + /* + * Dump the ticky counter definitions + * We do this at the end of execution since tickers are registered in the + * course of program execution. + */ +#if defined(TICKY_TICKY) && defined(TRACING) + if (RtsFlags.TraceFlags.ticky) { + emitTickyCounterDefs(); + } +#endif + // set the terminal settings back to what they were #if !defined(mingw32_HOST_OS) resetTerminalSettings(); ===================================== rts/Ticky.c ===================================== @@ -10,6 +10,8 @@ #include "PosixSource.h" #include "Rts.h" +#include "eventlog/EventLog.h" + /* Catch-all top-level counter struct. Allocations from CAFs will go * here. */ @@ -46,6 +48,10 @@ static void printRegisteredCounterInfo (FILE *); /* fwd decl */ void PrintTickyInfo(void) { + if (RtsFlags.TraceFlags.ticky) { + barf("Ticky eventlog output can't be used with +RTS -r"); + } + unsigned long i; unsigned long tot_thk_enters = ENT_STATIC_THK_MANY_ctr + ENT_DYN_THK_MANY_ctr @@ -374,4 +380,19 @@ printRegisteredCounterInfo (FILE *tf) } } + +void emitTickyCounterDefs() +{ +#if defined(TRACING) + postTickyCounterDefs(ticky_entry_ctrs); +#endif +} + +void emitTickyCounterSamples() +{ +#if defined(TRACING) + postTickyCounterSamples(ticky_entry_ctrs); +#endif +} + #endif /* TICKY_TICKY */ ===================================== rts/Ticky.h ===================================== @@ -8,4 +8,11 @@ #pragma once -RTS_PRIVATE void PrintTickyInfo(void); +#include "BeginPrivate.h" + +void PrintTickyInfo(void); + +void emitTickyCounterSamples(void); +void emitTickyCounterDefs(void); + +#include "EndPrivate.h" ===================================== rts/eventlog/EventLog.c ===================================== @@ -119,7 +119,9 @@ char *EventDesc[] = { [EVENT_CONC_SWEEP_BEGIN] = "Begin concurrent sweep", [EVENT_CONC_SWEEP_END] = "End concurrent sweep", [EVENT_CONC_UPD_REM_SET_FLUSH] = "Update remembered set flushed", - [EVENT_NONMOVING_HEAP_CENSUS] = "Nonmoving heap census" + [EVENT_NONMOVING_HEAP_CENSUS] = "Nonmoving heap census", + [EVENT_TICKY_COUNTER_DEF] = "Ticky-ticky entry counter definition", + [EVENT_TICKY_COUNTER_SAMPLE] = "Ticky-ticky entry counter sample", }; // Event type. @@ -487,6 +489,14 @@ init_event_types(void) eventTypes[t].size = 13; break; + case EVENT_TICKY_COUNTER_DEF: // (counter_id, arity, arg_kinds, name) + eventTypes[t].size = EVENT_SIZE_DYNAMIC; + break; + + case EVENT_TICKY_COUNTER_SAMPLE: // (counter_id, entry_count, allocs, allocd) + eventTypes[t].size = 8*4; + break; + default: continue; /* ignore deprecated events */ } @@ -1472,6 +1482,53 @@ void postProfBegin(void) } #endif /* PROFILING */ +#if defined(TICKY_TICKY) +static void postTickyCounterDef(EventsBuf *eb, StgEntCounter *p) +{ + StgWord len = 8 + 2 + strlen(p->arg_kinds)+1 + strlen(p->str)+1; + ensureRoomForVariableEvent(eb, len); + postEventHeader(eb, EVENT_TICKY_COUNTER_DEF); + postPayloadSize(eb, len); + postWord64(eb, (uint64_t) p); + postWord16(eb, (uint16_t) p->arity); + postString(eb, p->arg_kinds); + postString(eb, p->str); +} + +void postTickyCounterDefs(StgEntCounter *counters) +{ + ACQUIRE_LOCK(&eventBufMutex); + for (StgEntCounter *p = counters; p != NULL; p = p->link) { + postTickyCounterDef(&eventBuf, p); + } + RELEASE_LOCK(&eventBufMutex); +} + +static void postTickyCounterSample(EventsBuf *eb, StgEntCounter *p) +{ + if ( p->entry_count == 0 + && p->allocs == 0 + && p->allocd == 0) + return; + + ensureRoomForEvent(eb, EVENT_TICKY_COUNTER_SAMPLE); + postEventHeader(eb, EVENT_TICKY_COUNTER_SAMPLE); + postWord64(eb, (uint64_t) p); + postWord64(eb, p->entry_count); + postWord64(eb, p->allocs); + postWord64(eb, p->allocd); +} + +void postTickyCounterSamples(StgEntCounter *counters) +{ + ACQUIRE_LOCK(&eventBufMutex); + for (StgEntCounter *p = counters; p != NULL; p = p->link) { + postTickyCounterSample(&eventBuf, p); + } + RELEASE_LOCK(&eventBufMutex); +} +#endif /* TICKY_TICKY */ + void printAndClearEventBuf (EventsBuf *ebuf) { closeBlockMarker(ebuf); ===================================== rts/eventlog/EventLog.h ===================================== @@ -173,6 +173,11 @@ void postConcMarkEnd(StgWord32 marked_obj_count); void postNonmovingHeapCensus(int log_blk_size, const struct NonmovingAllocCensus *census); +#if defined(TICKY_TICKY) +void postTickyCounterDefs(StgEntCounter *p); +void postTickyCounterSamples(StgEntCounter *p); +#endif /* TICKY_TICKY */ + #else /* !TRACING */ INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, ===================================== rts/sm/GC.c ===================================== @@ -38,6 +38,7 @@ #include "Sanity.h" #include "BlockAlloc.h" #include "ProfHeap.h" +#include "Proftimer.h" #include "Weak.h" #include "Prelude.h" #include "RtsSignals.h" @@ -52,6 +53,7 @@ #include "CNF.h" #include "RtsFlags.h" #include "NonMoving.h" +#include "Ticky.h" #include // for memset() #include @@ -903,6 +905,16 @@ GarbageCollect (uint32_t collect_gen, ACQUIRE_SM_LOCK; } +#if defined(TICKY_TICKY) + // Post ticky counter sample. + // We do this at the end of execution since tickers are registered in the + // course of program execution. + if (performTickySample) { + emitTickyCounterSamples(); + performTickySample = false; + } +#endif + // send exceptions to any threads which were about to die RELEASE_SM_LOCK; resurrectThreads(resurrected_threads); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14ce787eabdb502146ff5c1fa29a0d78bc17bc4e...26a7c37fa3b176820a52de54daef7b9c8cce91d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/14ce787eabdb502146ff5c1fa29a0d78bc17bc4e...26a7c37fa3b176820a52de54daef7b9c8cce91d0 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 Sun Nov 22 06:27:13 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 01:27:13 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/int64-everywhere-new-float-primops Message-ID: <5fba04c1ec739_36a73fd2f208ef80586435@gitlab.mail> John Ericson pushed new branch wip/int64-everywhere-new-float-primops at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/int64-everywhere-new-float-primops 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 Sun Nov 22 06:28:27 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 01:28:27 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 247 commits: Fall back to types when looking up data constructors (#18740) Message-ID: <5fba050ba63f5_36a73fd2f208ef805866b9@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 2bcd6197 by John Ericson at 2020-11-22T04:40:57+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 ghc-bignum: add support for Word64#/Int64# on 64-bit arch Fix fingerprint Core generation Fix some tests Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 0af14547 by John Ericson at 2020-11-22T04:44:49+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - fdcd8a3c by Sylvain Henry at 2020-11-22T04:44:50+00:00 Fix toArgRep - - - - - aaf7cfdb by Sylvain Henry at 2020-11-22T04:44:50+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 464056f2 by John Ericson at 2020-11-22T04:44:50+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 26b49366 by John Ericson at 2020-11-22T04:44:50+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 45af7400 by John Ericson at 2020-11-22T04:44:50+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - a08e0a13 by Sylvain Henry at 2020-11-22T06:24:03+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 28 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/DebugBlock.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/Parser.y - compiler/GHC/Cmm/Monad.hs → compiler/GHC/Cmm/Parser/Monad.hs - compiler/GHC/Cmm/Pipeline.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6b4bbc2867076310bdaabea03905901697d32c7...a08e0a138375942d87023e7fc8b878f31a1ea26a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c6b4bbc2867076310bdaabea03905901697d32c7...a08e0a138375942d87023e7fc8b878f31a1ea26a 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 Sun Nov 22 11:27:41 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 22 Nov 2020 06:27:41 -0500 Subject: [Git][ghc/ghc][master] rts: Post ticky entry counts to the eventlog Message-ID: <5fba4b2d7f91a_36a73fd2caa64b905925c4@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - 14 changed files: - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/profiling.rst - includes/rts/EventLogFormat.h - includes/rts/Flags.h - rts/Proftimer.c - rts/Proftimer.h - rts/RtsFlags.c - rts/RtsStartup.c - rts/Ticky.c - rts/Ticky.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/sm/GC.c Changes: ===================================== docs/users_guide/eventlog-formats.rst ===================================== @@ -755,3 +755,34 @@ intended to provide insight into fragmentation of the non-moving heap. :field Word32: number of live blocks. Describes the occupancy of the *blk_sz* sub-heap. + +Ticky counters +~~~~~~~~~~~~~~ + +Programs compiled with :ghc-flag:`-ticky` and :ghc-flag:`-eventlog` and invoked +with ``+RTS -lT`` will emit periodic samples of the ticky entry counters to the +eventlog. + +.. event-type:: TICKY_COUNTER_DEF + + :tag: 210 + :length: variable + :field Word64: counter ID + :field Word16: arity/field count + :field String: argument kinds. This is the same as the synonymous field in the + textual ticky summary. + :field String: counter name + + Defines a ticky counter. + +.. event-type:: TICKY_COUNTER_SAMPLE + + :tag: 211 + :length: fixed + :field Word64: counter ID + :field Word64: number of times closures of this type has been entered. + :field Word64: number of allocations (words) + :field Word64: number of times this has been allocated (words). Only + produced for modules compiled with :ghc-flag:`-ticky-allocd`. + + Records the counter statistics at a moment in time. ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -118,5 +118,3 @@ -syslib -this-component-id -ticky-LNE --ticky-allocd --ticky-dyn-thunk ===================================== docs/users_guide/profiling.rst ===================================== @@ -1681,11 +1681,27 @@ Using “ticky-ticky” profiling (for implementors) single: ticky-ticky profiling .. ghc-flag:: -ticky - :shortdesc: :ref:`Turn on ticky-ticky profiling ` + :shortdesc: Turn on :ref:`ticky-ticky profiling ` :type: dynamic :category: - Enable ticky-ticky profiling. + Enable ticky-ticky profiling. By default this only tracks the allocations + *by* each closure type. See :ghc-flag:`-ticky-allocd` to keep track of + allocations *of* each closure type as well. + +.. ghc-flag:: -ticky-allocd + :shortdesc: Track the number of times each closure type is allocated. + :type: dynamic + :category: + + Keep track of how much each closure type is allocated. + +.. ghc-flag:: -ticky-dyn-thunk + :shortdesc: Track allocations of dynamic thunks + :type: dynamic + :category: + + Track allocations of dynamic thunks. Because ticky-ticky profiling requires a certain familiarity with GHC internals, we have moved the documentation to the GHC developers wiki. ===================================== includes/rts/EventLogFormat.h ===================================== @@ -154,12 +154,15 @@ #define EVENT_CONC_UPD_REM_SET_FLUSH 206 #define EVENT_NONMOVING_HEAP_CENSUS 207 +#define EVENT_TICKY_COUNTER_DEF 210 +#define EVENT_TICKY_COUNTER_SAMPLE 211 + /* * The highest event code +1 that ghc itself emits. Note that some event * ranges higher than this are reserved but not currently emitted by ghc. * This must match the size of the EventDesc[] array in EventLog.c */ -#define NUM_GHC_EVENT_TAGS 208 +#define NUM_GHC_EVENT_TAGS 212 #if 0 /* DEPRECATED EVENTS: */ /* we don't actually need to record the thread, it's implicit */ ===================================== includes/rts/Flags.h ===================================== @@ -176,6 +176,7 @@ typedef struct _TRACE_FLAGS { bool nonmoving_gc; /* trace nonmoving GC events */ bool sparks_sampled; /* trace spark events by a sampled method */ bool sparks_full; /* trace spark events 100% accurately */ + bool ticky; /* trace ticky-ticky samples */ bool user; /* trace user events (emitted from Haskell code) */ char *trace_output; /* output filename for eventlog */ } TRACE_FLAGS; ===================================== rts/Proftimer.c ===================================== @@ -20,6 +20,12 @@ static bool do_prof_ticks = false; // enable profiling ticks static bool do_heap_prof_ticks = false; // enable heap profiling ticks +// Sampling of Ticky-Ticky profiler to eventlog +#if defined(TICKY_TICKY) && defined(TRACING) +static int ticks_to_ticky_sample = 0; +bool performTickySample = false; +#endif + // Number of ticks until next heap census static int ticks_to_heap_profile; @@ -83,6 +89,16 @@ handleProfTick(void) } #endif +#if defined(TICKY_TICKY) && defined(TRACING) + if (RtsFlags.TraceFlags.ticky) { + ticks_to_ticky_sample--; + if (ticks_to_ticky_sample <= 0) { + ticks_to_ticky_sample = RtsFlags.ProfFlags.heapProfileIntervalTicks; + performTickySample = true; + } + } +#endif + if (RELAXED_LOAD(&do_heap_prof_ticks)) { ticks_to_heap_profile--; if (ticks_to_heap_profile <= 0) { ===================================== rts/Proftimer.h ===================================== @@ -17,5 +17,6 @@ void stopHeapProfTimer ( void ); void startHeapProfTimer ( void ); extern bool performHeapProfile; +extern bool performTickySample; #include "EndPrivate.h" ===================================== rts/RtsFlags.c ===================================== @@ -235,6 +235,7 @@ void initRtsFlagsDefaults(void) RtsFlags.TraceFlags.sparks_sampled= false; RtsFlags.TraceFlags.sparks_full = false; RtsFlags.TraceFlags.user = false; + RtsFlags.TraceFlags.ticky = false; RtsFlags.TraceFlags.trace_output = NULL; #endif @@ -403,6 +404,9 @@ usage_text[] = { " p par spark events (sampled)", " f par spark events (full detail)", " u user events (emitted from Haskell code)", +#if defined(TICKY_TICKY) +" T ticky-ticky counter samples", +#endif " a all event classes above", # if defined(DEBUG) " t add time stamps (only useful with -v)", @@ -1855,6 +1859,11 @@ static void normaliseRtsOpts (void) "the compacting collector."); errorUsage(); } + + if (RtsFlags.TraceFlags.ticky && RtsFlags.TickyFlags.showTickyStats) { + barf("The ticky-ticky eventlog output cannot be used in conjunction with\n" + "+RTS -r."); + } } static void errorUsage (void) @@ -2297,6 +2306,15 @@ static void read_trace_flags(const char *arg) RtsFlags.TraceFlags.user = enabled; enabled = true; break; + case 'T': +#if defined(TICKY_TICKY) + RtsFlags.TraceFlags.ticky = enabled; + enabled = true; + break; +#else + errorBelch("Program not compiled with ticky-ticky support"); + break; +#endif default: errorBelch("unknown trace option: %c",*c); break; ===================================== rts/RtsStartup.c ===================================== @@ -487,6 +487,17 @@ hs_exit_(bool wait_foreign) */ exitTimer(true); + /* + * Dump the ticky counter definitions + * We do this at the end of execution since tickers are registered in the + * course of program execution. + */ +#if defined(TICKY_TICKY) && defined(TRACING) + if (RtsFlags.TraceFlags.ticky) { + emitTickyCounterDefs(); + } +#endif + // set the terminal settings back to what they were #if !defined(mingw32_HOST_OS) resetTerminalSettings(); ===================================== rts/Ticky.c ===================================== @@ -10,6 +10,8 @@ #include "PosixSource.h" #include "Rts.h" +#include "eventlog/EventLog.h" + /* Catch-all top-level counter struct. Allocations from CAFs will go * here. */ @@ -46,6 +48,10 @@ static void printRegisteredCounterInfo (FILE *); /* fwd decl */ void PrintTickyInfo(void) { + if (RtsFlags.TraceFlags.ticky) { + barf("Ticky eventlog output can't be used with +RTS -r"); + } + unsigned long i; unsigned long tot_thk_enters = ENT_STATIC_THK_MANY_ctr + ENT_DYN_THK_MANY_ctr @@ -374,4 +380,19 @@ printRegisteredCounterInfo (FILE *tf) } } + +void emitTickyCounterDefs() +{ +#if defined(TRACING) + postTickyCounterDefs(ticky_entry_ctrs); +#endif +} + +void emitTickyCounterSamples() +{ +#if defined(TRACING) + postTickyCounterSamples(ticky_entry_ctrs); +#endif +} + #endif /* TICKY_TICKY */ ===================================== rts/Ticky.h ===================================== @@ -8,4 +8,11 @@ #pragma once -RTS_PRIVATE void PrintTickyInfo(void); +#include "BeginPrivate.h" + +void PrintTickyInfo(void); + +void emitTickyCounterSamples(void); +void emitTickyCounterDefs(void); + +#include "EndPrivate.h" ===================================== rts/eventlog/EventLog.c ===================================== @@ -119,7 +119,9 @@ char *EventDesc[] = { [EVENT_CONC_SWEEP_BEGIN] = "Begin concurrent sweep", [EVENT_CONC_SWEEP_END] = "End concurrent sweep", [EVENT_CONC_UPD_REM_SET_FLUSH] = "Update remembered set flushed", - [EVENT_NONMOVING_HEAP_CENSUS] = "Nonmoving heap census" + [EVENT_NONMOVING_HEAP_CENSUS] = "Nonmoving heap census", + [EVENT_TICKY_COUNTER_DEF] = "Ticky-ticky entry counter definition", + [EVENT_TICKY_COUNTER_SAMPLE] = "Ticky-ticky entry counter sample", }; // Event type. @@ -487,6 +489,14 @@ init_event_types(void) eventTypes[t].size = 13; break; + case EVENT_TICKY_COUNTER_DEF: // (counter_id, arity, arg_kinds, name) + eventTypes[t].size = EVENT_SIZE_DYNAMIC; + break; + + case EVENT_TICKY_COUNTER_SAMPLE: // (counter_id, entry_count, allocs, allocd) + eventTypes[t].size = 8*4; + break; + default: continue; /* ignore deprecated events */ } @@ -1472,6 +1482,53 @@ void postProfBegin(void) } #endif /* PROFILING */ +#if defined(TICKY_TICKY) +static void postTickyCounterDef(EventsBuf *eb, StgEntCounter *p) +{ + StgWord len = 8 + 2 + strlen(p->arg_kinds)+1 + strlen(p->str)+1; + ensureRoomForVariableEvent(eb, len); + postEventHeader(eb, EVENT_TICKY_COUNTER_DEF); + postPayloadSize(eb, len); + postWord64(eb, (uint64_t) p); + postWord16(eb, (uint16_t) p->arity); + postString(eb, p->arg_kinds); + postString(eb, p->str); +} + +void postTickyCounterDefs(StgEntCounter *counters) +{ + ACQUIRE_LOCK(&eventBufMutex); + for (StgEntCounter *p = counters; p != NULL; p = p->link) { + postTickyCounterDef(&eventBuf, p); + } + RELEASE_LOCK(&eventBufMutex); +} + +static void postTickyCounterSample(EventsBuf *eb, StgEntCounter *p) +{ + if ( p->entry_count == 0 + && p->allocs == 0 + && p->allocd == 0) + return; + + ensureRoomForEvent(eb, EVENT_TICKY_COUNTER_SAMPLE); + postEventHeader(eb, EVENT_TICKY_COUNTER_SAMPLE); + postWord64(eb, (uint64_t) p); + postWord64(eb, p->entry_count); + postWord64(eb, p->allocs); + postWord64(eb, p->allocd); +} + +void postTickyCounterSamples(StgEntCounter *counters) +{ + ACQUIRE_LOCK(&eventBufMutex); + for (StgEntCounter *p = counters; p != NULL; p = p->link) { + postTickyCounterSample(&eventBuf, p); + } + RELEASE_LOCK(&eventBufMutex); +} +#endif /* TICKY_TICKY */ + void printAndClearEventBuf (EventsBuf *ebuf) { closeBlockMarker(ebuf); ===================================== rts/eventlog/EventLog.h ===================================== @@ -173,6 +173,11 @@ void postConcMarkEnd(StgWord32 marked_obj_count); void postNonmovingHeapCensus(int log_blk_size, const struct NonmovingAllocCensus *census); +#if defined(TICKY_TICKY) +void postTickyCounterDefs(StgEntCounter *p); +void postTickyCounterSamples(StgEntCounter *p); +#endif /* TICKY_TICKY */ + #else /* !TRACING */ INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, ===================================== rts/sm/GC.c ===================================== @@ -38,6 +38,7 @@ #include "Sanity.h" #include "BlockAlloc.h" #include "ProfHeap.h" +#include "Proftimer.h" #include "Weak.h" #include "Prelude.h" #include "RtsSignals.h" @@ -52,6 +53,7 @@ #include "CNF.h" #include "RtsFlags.h" #include "NonMoving.h" +#include "Ticky.h" #include // for memset() #include @@ -903,6 +905,16 @@ GarbageCollect (uint32_t collect_gen, ACQUIRE_SM_LOCK; } +#if defined(TICKY_TICKY) + // Post ticky counter sample. + // We do this at the end of execution since tickers are registered in the + // course of program execution. + if (performTickySample) { + emitTickyCounterSamples(); + performTickySample = false; + } +#endif + // send exceptions to any threads which were about to die RELEASE_SM_LOCK; resurrectThreads(resurrected_threads); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7e93ae8b2257c17d5ae5ef7832db723e897c8e8b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7e93ae8b2257c17d5ae5ef7832db723e897c8e8b 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 Sun Nov 22 11:28:16 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 22 Nov 2020 06:28:16 -0500 Subject: [Git][ghc/ghc][master] Implement -ddump-c-backend argument Message-ID: <5fba4b50b0c51_36a73fd2ff413ea0594678@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 4 changed files: - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debugging.rst Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -138,7 +138,13 @@ outputC dflags filenm cmm_stream packages = hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n") hPutStr h "#include \"Stg.h\"\n" let platform = targetPlatform dflags - writeC = printForC dflags h . cmmToC platform + writeC cmm = do + let doc = cmmToC platform cmm + dumpIfSet_dyn dflags Opt_D_dump_c_backend + "C backend output" + FormatC + doc + printForC dflags h doc Stream.consume cmm_stream writeC {- ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -49,6 +49,7 @@ data DumpFlag | Opt_D_dump_asm_conflicts | Opt_D_dump_asm_stats | Opt_D_dump_asm_expanded + | Opt_D_dump_c_backend | Opt_D_dump_llvm | Opt_D_dump_core_stats | Opt_D_dump_deriv ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2539,6 +2539,8 @@ dynamic_flags_deps = [ (setDumpFlag Opt_D_dump_asm_expanded) , make_ord_flag defGhcFlag "ddump-llvm" (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm) + , make_ord_flag defGhcFlag "ddump-c-backend" + (NoArg $ setDumpFlag' Opt_D_dump_c_backend) , make_ord_flag defGhcFlag "ddump-deriv" (setDumpFlag Opt_D_dump_deriv) , make_ord_flag defGhcFlag "ddump-ds" ===================================== docs/users_guide/debugging.rst ===================================== @@ -552,6 +552,15 @@ LLVM code generator LLVM code from the :ref:`LLVM code generator ` +C code generator +~~~~~~~~~~~~~~~~ + +.. ghc-flag:: -ddump-c-backend + :shortdesc: Dump C code produced by the C (unregisterised) backend. + :type: dynamic + + :shortdesc: Dump C code produced by the C (unregisterised) backend. + Native code generator ~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc9c3916df96a20c58b91fd383a0da77ec83c4b0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bc9c3916df96a20c58b91fd383a0da77ec83c4b0 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 Sun Nov 22 11:59:05 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 22 Nov 2020 06:59:05 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Implement -ddump-c-backend argument Message-ID: <5fba5289bec81_36a73fd2f208ef806008a8@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 8e596cdf by Ben Gamari at 2020-11-22T06:58:56-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 412e039c by Ben Gamari at 2020-11-22T06:58:56-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - 9105f6e8 by Ben Gamari at 2020-11-22T06:58:56-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 4b26b802 by Ben Gamari at 2020-11-22T06:58:56-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - 909934ed by Ben Gamari at 2020-11-22T06:58:56-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - d1f30757 by Ben Gamari at 2020-11-22T06:58:56-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 20 changed files: - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/ghc.cabal.in - docs/users_guide/debugging.rst - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/Main.hs - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -138,7 +138,13 @@ outputC dflags filenm cmm_stream packages = hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n") hPutStr h "#include \"Stg.h\"\n" let platform = targetPlatform dflags - writeC = printForC dflags h . cmmToC platform + writeC cmm = do + let doc = cmmToC platform cmm + dumpIfSet_dyn dflags Opt_D_dump_c_backend + "C backend output" + FormatC + doc + printForC dflags h doc Stream.consume cmm_stream writeC {- ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -49,6 +49,7 @@ data DumpFlag | Opt_D_dump_asm_conflicts | Opt_D_dump_asm_stats | Opt_D_dump_asm_expanded + | Opt_D_dump_c_backend | Opt_D_dump_llvm | Opt_D_dump_core_stats | Opt_D_dump_deriv ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2539,6 +2539,8 @@ dynamic_flags_deps = [ (setDumpFlag Opt_D_dump_asm_expanded) , make_ord_flag defGhcFlag "ddump-llvm" (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm) + , make_ord_flag defGhcFlag "ddump-c-backend" + (NoArg $ setDumpFlag' Opt_D_dump_c_backend) , make_ord_flag defGhcFlag "ddump-deriv" (setDumpFlag Opt_D_dump_deriv) , make_ord_flag defGhcFlag "ddump-ds" ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== docs/users_guide/debugging.rst ===================================== @@ -552,6 +552,15 @@ LLVM code generator LLVM code from the :ref:`LLVM code generator ` +C code generator +~~~~~~~~~~~~~~~~ + +.. ghc-flag:: -ddump-c-backend + :shortdesc: Dump C code produced by the C (unregisterised) backend. + :type: dynamic + + :shortdesc: Dump C code produced by the C (unregisterised) backend. + Native code generator ~~~~~~~~~~~~~~~~~~~~~ ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== hadrian/doc/flavours.md ===================================== @@ -99,16 +99,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O -O2 - - prof - -O0
-H64m - -O0
-H64m - - -O - -O2 - -O - -O - bench -O
-H64m @@ -166,13 +156,66 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -### LLVM variants +## Flavour transformers -In addition to the above, there are LLVM variants for the flavours `quick`, -`prof`, `perf` and `bench`, available by appending a `-llvm` suffix (i.e., -`quick-llvm` for the LLVM variant of `quick`). These differ only in that there -is an additional `-fllvm` flag in `hsDefault` when the stage0 compiler is GHC. -See `src/Settings/Flavours/Llvm.hs` for details. +Each of the flavours described above is intended as a starting-point for +configuring your GHC build. In addition, Hadrian supports a number of "flavour +transformers" which modify the configuration in various ways. + +These can be appended to the flavour name passed via the `--flavour` +command-line flag, separated by the `+` character. For instance, + +``` +hadrian --flavour=perf+thread_sanitizer +``` + +The supported transformers are listed below: + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
Transformer nameEffect
werrorUse the `-Werror` flag for all stage1+ compilation.
debug_infoEnable production of native debugging information (via GHC/GCC's `-g3`) + during stage1+ compilations.
ticky_ghcCompile the GHC executable with Ticky-Ticky profiler support.
split_sectionsEnable section splitting for all libraries (except for the GHC + library due to the long linking times that this causes).
thread_sanitizerBuild the runtime system with ThreadSanitizer support
llvmUse GHC's LLVM backend (`-fllvm`) for all stage1+ compilation.
profiled_ghcBuild the GHC executable with cost-centre profiling support. + It is that you use this in conjunction with `no_dynamic_ghc` since + GHC does not It is support loading of profiled libraries with the + dynamically-linker.
no_dynamic_ghcLinked GHC against the statically-linked RTS. This causes GHC to + default to loading static rather than dynamic library when, + e.g., loading libraries during TemplateHaskell evaluations.
## Ways @@ -184,7 +227,6 @@ information. The following table lists ways that are built in different flavours Flavour Library ways RTS ways - Profiled GHC stage0 @@ -195,7 +237,7 @@ information. The following table lists ways that are built in different flavours stage1+ - default
perf
prof
devel1
devel2
perf-llvm
prof-llvm + default
perf
prof
devel1
devel2 vanilla vanilla
profiling
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -208,11 +250,9 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - Only in
prof
flavour - Only in
prof
flavour - quick
quick-llvm
quick-validate
quick-debug + quick
quick-validate
quick-debug vanilla vanilla
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -223,8 +263,6 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - No - No quickest
bench @@ -232,7 +270,5 @@ information. The following table lists ways that are built in different flavours vanilla vanilla
threaded vanilla
threaded - No - No ===================================== hadrian/hadrian.cabal ===================================== @@ -106,13 +106,10 @@ executable hadrian , Settings.Flavours.Benchmark , Settings.Flavours.Development , Settings.Flavours.GhcInGhci - , Settings.Flavours.Llvm , Settings.Flavours.Performance - , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.QuickCross , Settings.Flavours.Quickest - , Settings.Flavours.ThreadSanitizer , Settings.Flavours.Validate , Settings.Packages , Settings.Parser ===================================== hadrian/src/Flavour.hs ===================================== @@ -1,17 +1,28 @@ module Flavour ( Flavour (..), werror , DocTargets, DocTarget(..) + , parseFlavour -- * Flavour transformers + , flavourTransformers , addArgs , splitSections, splitSectionsIf , enableThreadSanitizer , enableDebugInfo, enableTickyGhc + , viaLlvmBackend + , enableProfiledGhc + , disableDynamicGhcPrograms ) where import Expression import Data.Set (Set) +import Data.Map (Map) +import qualified Data.Map as M import Packages +import Text.Parsec.Prim as P +import Text.Parsec.Combinator as P +import Text.Parsec.Char as P + -- Please update doc/{flavours.md, user-settings.md} when changing this file. -- | 'Flavour' is a collection of build settings that fully define a GHC build. -- Note the following type semantics: @@ -69,6 +80,58 @@ type DocTargets = Set DocTarget data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) +flavourTransformers :: Map String (Flavour -> Flavour) +flavourTransformers = M.fromList + [ "werror" =: werror + , "debug_info" =: enableDebugInfo + , "ticky_ghc" =: enableTickyGhc + , "split_sections" =: splitSections + , "thread_sanitizer" =: enableThreadSanitizer + , "llvm" =: viaLlvmBackend + , "profiled_ghc" =: enableProfiledGhc + , "no_dynamic_ghc" =: disableDynamicGhcPrograms + ] + where (=:) = (,) + +type Parser = Parsec String () + +parseFlavour :: [Flavour] -- ^ base flavours + -> Map String (Flavour -> Flavour) -- ^ modifiers + -> String + -> Either String Flavour +parseFlavour baseFlavours transformers str = + case P.runParser parser () "" str of + Left perr -> Left $ unlines $ + [ "error parsing flavour specifier: " ++ show perr + , "" + , "known flavours:" + ] ++ + [ " " ++ name f | f <- baseFlavours ] ++ + [ "" + , "known flavour transformers:" + ] ++ + [ " " ++ nm | nm <- M.keys transformers ] + Right f -> Right f + where + parser :: Parser Flavour + parser = do + base <- baseFlavour + transs <- P.many flavourTrans + return $ foldr ($) base transs + + baseFlavour :: Parser Flavour + baseFlavour = + P.choice [ f <$ P.try (P.string (name f)) + | f <- baseFlavours + ] + + flavourTrans :: Parser (Flavour -> Flavour) + flavourTrans = do + void $ P.char '+' + P.choice [ trans <$ P.try (P.string nm) + | (nm, trans) <- M.toList transformers + ] + -- | Add arguments to the 'args' of a 'Flavour'. addArgs :: Args -> Flavour -> Flavour addArgs args' fl = fl { args = args fl <> args' } @@ -96,7 +159,13 @@ enableTickyGhc = [ builder (Ghc CompileHs) ? ticky , builder (Ghc LinkHs) ? ticky ] - ticky = arg "-ticky" <> arg "-ticky-allocd" + ticky = mconcat + [ arg "-ticky" + , arg "-ticky-allocd" + -- You generally need STG dumps to interpret ticky profiles + , arg "-ddump-to-file" + , arg "-ddump-stg-final" + ] -- | Transform the input 'Flavour' so as to build with -- @-split-sections@ whenever appropriate. You can @@ -128,3 +197,17 @@ enableThreadSanitizer = addArgs $ mconcat , builder (Cabal Flags) ? arg "thread-sanitizer" , builder RunTest ? arg "--config=have_thread_sanitizer=True" ] + +-- | Use the LLVM backend in stages 1 and later. +viaLlvmBackend :: Flavour -> Flavour +viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm" + +-- | Build the GHC executable with profiling enabled. It is also recommended +-- that you use this with @'dynamicGhcPrograms' = False@ since GHC does not +-- support loading of profiled libraries with the dynamically-linker. +enableProfiledGhc :: Flavour -> Flavour +enableProfiledGhc flavour = flavour { ghcProfiled = True } + +-- | Disable 'dynamicGhcPrograms'. +disableDynamicGhcPrograms :: Flavour -> Flavour +disableDynamicGhcPrograms flavour = flavour { dynamicGhcPrograms = pure False } ===================================== hadrian/src/Settings.hs ===================================== @@ -15,13 +15,10 @@ import {-# SOURCE #-} Settings.Default import Settings.Flavours.Benchmark import Settings.Flavours.Development import Settings.Flavours.GhcInGhci -import Settings.Flavours.Llvm import Settings.Flavours.Performance -import Settings.Flavours.Profiled import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Flavours.QuickCross -import Settings.Flavours.ThreadSanitizer import Settings.Flavours.Validate import Control.Monad.Except @@ -54,13 +51,11 @@ stagePackages stage = do hadrianFlavours :: [Flavour] hadrianFlavours = [ benchmarkFlavour, defaultFlavour, developmentFlavour Stage1 - , developmentFlavour Stage2, performanceFlavour, profiledFlavour + , developmentFlavour Stage2, performanceFlavour , quickFlavour, quickValidateFlavour, quickDebugFlavour , quickestFlavour - , quickCrossFlavour, benchmarkLlvmFlavour - , performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour - , ghcInGhciFlavour, validateFlavour, slowValidateFlavour - , threadSanitizerFlavour ] + , quickCrossFlavour + , ghcInGhciFlavour, validateFlavour, slowValidateFlavour ] -- | This action looks up a flavour with the name given on the -- command line with @--flavour@, defaulting to 'userDefaultFlavour' @@ -75,11 +70,9 @@ flavour = do let flavours = hadrianFlavours ++ userFlavours (_settingErrs, tweak) = applySettings kvs - return $ - case filter (\fl -> name fl == flavourName) flavours of - [] -> error $ "Unknown build flavour: " ++ flavourName - [f] -> tweak f - _ -> error $ "Multiple build flavours named " ++ flavourName + case parseFlavour flavours flavourTransformers flavourName of + Left err -> fail err + Right f -> return $ tweak f -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. ===================================== hadrian/src/Settings/Flavours/Llvm.hs deleted ===================================== @@ -1,29 +0,0 @@ -module Settings.Flavours.Llvm ( - benchmarkLlvmFlavour, - performanceLlvmFlavour, - profiledLlvmFlavour, - quickLlvmFlavour, -) where - -import Expression -import Flavour - -import Settings.Flavours.Benchmark -import Settings.Flavours.Performance -import Settings.Flavours.Profiled -import Settings.Flavours.Quick - --- Please update doc/flavours.md when changing this file. -benchmarkLlvmFlavour, performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour :: Flavour -benchmarkLlvmFlavour = mkLlvmFlavour benchmarkFlavour -performanceLlvmFlavour = mkLlvmFlavour performanceFlavour -profiledLlvmFlavour = mkLlvmFlavour profiledFlavour -quickLlvmFlavour = mkLlvmFlavour quickFlavour - --- | Turn a flavour into an LLVM flavour -mkLlvmFlavour :: Flavour -> Flavour -mkLlvmFlavour flav = flav - { name = name flav ++ "-llvm" - , args = mconcat [ args flav - , builder Ghc ? arg "-fllvm" ] - } ===================================== hadrian/src/Settings/Flavours/Profiled.hs deleted ===================================== @@ -1,22 +0,0 @@ -module Settings.Flavours.Profiled (profiledFlavour) where - -import Expression -import Flavour -import {-# SOURCE #-} Settings.Default - --- Please update doc/flavours.md when changing this file. -profiledFlavour :: Flavour -profiledFlavour = defaultFlavour - { name = "prof" - , args = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs - , ghcProfiled = True - , dynamicGhcPrograms = pure False } - -profiledArgs :: Args -profiledArgs = sourceArgs SourceArgs - { hsDefault = mconcat - [ pure ["-O0", "-H64m"] - ] - , hsLibrary = notStage0 ? arg "-O" - , hsCompiler = mconcat [stage0 ? arg "-O2", notStage0 ? arg "-O"] - , hsGhc = arg "-O" } ===================================== hadrian/src/Settings/Flavours/ThreadSanitizer.hs deleted ===================================== @@ -1,9 +0,0 @@ -module Settings.Flavours.ThreadSanitizer (threadSanitizerFlavour) where - -import Flavour -import Settings.Flavours.Validate - -threadSanitizerFlavour :: Flavour -threadSanitizerFlavour = - enableThreadSanitizer (validateFlavour - { name = "thread-sanitizer" }) ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 0633b48b010093f64f98ee494265436e96456aed ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 59e6ba02f3fa5c8f4901b4ce21777c4a9beb14b6 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit c25d6a76702b454426e149fb590da5cb69f3bd0a ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit e079823775066bcab56b22842be6cce6e060fb9f ===================================== utils/ghc-cabal/Main.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -28,6 +29,7 @@ import Distribution.Verbosity import qualified Distribution.InstalledPackageInfo as Installed import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Utils.ShortText (fromShortText) +import Distribution.Utils.Path (getSymbolicPath) import Control.Exception (bracket) import Control.Monad @@ -433,7 +435,7 @@ generate directory distdir config_args variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd), - variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), + variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/26a7c37fa3b176820a52de54daef7b9c8cce91d0...d1f30757d5a951a342ec6170e84795b8ed3efa5f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/26a7c37fa3b176820a52de54daef7b9c8cce91d0...d1f30757d5a951a342ec6170e84795b8ed3efa5f 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 Sun Nov 22 12:30:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 07:30:09 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] 5 commits: macOS: Load frameworks without stating them first. Message-ID: <5fba59d1a78cc_36a7643e30060108e@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 3571cc41 by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - 57b5f130 by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 07c5acae by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - bde58de9 by Ömer Sinan Ağacan at 2020-11-22T07:29:28-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 180f58cf by Viktor Dukhovni at 2020-11-22T07:29:28-05:00 8.10 - dirty MVAR after mutating TSO queue head While the original head and tail of the TSO queue may be in the same generation as the MVAR, interior elements of the queue could be younger after a GC run and may then be exposed by putMVar operation that updates the queue head. Resolves #18919 (cherry picked from commit 699facec0bc8dd7d5b82cc537fbf131b74f5bd2c) - - - - - 27 changed files: - compiler/ghci/Linker.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/PrimOps.cmm - rts/RtsStartup.c - rts/Threads.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/linker_error.c Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1134,14 +1134,15 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do where unloadObjs :: Linkable -> IO () unloadObjs lnk + -- The RTS's PEi386 linker currently doesn't support unloading. + | isWindowsHost = return () + | dynamicGhc = return () -- We don't do any cleanup when linking objects with the -- dynamic linker. Doing so introduces extra complexity for -- not much benefit. - -- Code unloading currently disabled due to instability. - -- See #16841. - | False -- otherwise + | otherwise = mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk] -- The components of a BCO linkable may contain -- dot-o files. Which is very confusing. @@ -1149,7 +1150,6 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do -- But the BCO parts can be unlinked just by -- letting go of them (plus of course depopulating -- the symbol table which is done in the main body) - | otherwise = return () -- see #16841 {- ********************************************************************** @@ -1679,6 +1679,38 @@ addEnvPaths name list -- ---------------------------------------------------------------------------- -- Loading a dynamic library (dlopen()-ish on Unix, LoadLibrary-ish on Win32) +{- +Note [macOS Big Sur dynamic libraries] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +macOS Big Sur makes the following change to how frameworks are shipped +with the OS: + +> New in macOS Big Sur 11 beta, the system ships with a built-in +> dynamic linker cache of all system-provided libraries. As part of +> this change, copies of dynamic libraries are no longer present on +> the filesystem. Code that attempts to check for dynamic library +> presence by looking for a file at a path or enumerating a directory +> will fail. Instead, check for library presence by attempting to +> dlopen() the path, which will correctly check for the library in the +> cache. (62986286) + +(https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/) + +Therefore, the previous method of checking whether a library exists +before attempting to load it makes GHC.Runtime.Linker.loadFramework +fail to find frameworks installed at /System/Library/Frameworks. +Instead, any attempt to load a framework at runtime, such as by +passing -framework OpenGL to runghc or running code loading such a +framework with GHCi, fails with a 'not found' message. + +GHC.Runtime.Linker.loadFramework now opportunistically loads the +framework libraries without checking for their existence first, +failing only if all attempts to load a given framework from any of the +various possible locations fail. See also #18446, which this change +addresses. +-} + -- Darwin / MacOS X only: load a framework -- a framework is a dynamic library packaged inside a directory of the same -- name. They are searched for in different paths than normal libraries. @@ -1689,17 +1721,29 @@ loadFramework hsc_env extraPaths rootname Left _ -> [] Right dir -> [dir "Library/Frameworks"] ps = extraPaths ++ homeFrameworkPath ++ defaultFrameworkPaths - ; mb_fwk <- findFile ps fwk_file - ; case mb_fwk of - Just fwk_path -> loadDLL hsc_env fwk_path - Nothing -> return (Just "not found") } - -- Tried all our known library paths, but dlopen() - -- has no built-in paths for frameworks: give up + ; errs <- findLoadDLL ps [] + ; return $ fmap (intercalate ", ") errs + } where fwk_file = rootname <.> "framework" rootname - -- sorry for the hardcoded paths, I hope they won't change anytime soon: + + -- sorry for the hardcoded paths, I hope they won't change anytime soon: defaultFrameworkPaths = ["/Library/Frameworks", "/System/Library/Frameworks"] + -- Try to call loadDLL for each candidate path. + -- + -- See Note [macOS Big Sur dynamic libraries] + findLoadDLL [] errs = + -- Tried all our known library paths, but dlopen() + -- has no built-in paths for frameworks: give up + return $ Just errs + findLoadDLL (p:ps) errs = + do { dll <- loadDLL hsc_env (p fwk_file) + ; case dll of + Nothing -> return Nothing + Just err -> findLoadDLL ps ((p ++ ": " ++ err):errs) + } + {- ********************************************************************** Helper functions ===================================== rts/CheckUnload.c ===================================== @@ -17,43 +17,99 @@ #include "CheckUnload.h" #include "sm/Storage.h" #include "sm/GCThread.h" +#include "sm/HeapUtils.h" // -// Code that we unload may be referenced from: -// - info pointers in heap objects and stack frames -// - pointers to static objects from the heap -// - StablePtrs to static objects -// - pointers to cost centres from the cost centre tree +// Note [Object unloading] +// ~~~~~~~~~~~~~~~~~~~~~~~ // -// We can find live static objects after a major GC, so we don't have -// to look at every closure pointer in the heap. However, we do have -// to look at every info pointer. So this is like a heap census -// traversal: we look at the header of every object, but not its -// contents. +// Overview of object unloading: // -// On the assumption that there aren't many different info pointers in -// a typical heap, we insert addresses into a hash table. The -// first time we see an address, we check it against the pending -// unloadable objects and if it lies within any of them, we mark that -// object as referenced so that it won't get unloaded in this round. +// - In a major GC, for every static object we mark the object's object code and +// its dependencies as 'live'. This is done by `markObjectCode`, called by +// `evacuate`. // - -// Note [Speeding up checkUnload] -// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -// In certain circumstances, there may be a lot of unloaded ObjectCode structs -// chained in `unloaded_objects` (such as when users `:load` a module in a very -// big repo in GHCi). To speed up checking whether an address lies within any of -// these objects, we populate the addresses of their mapped sections in -// an array sorted by their `start` address and do binary search for our address -// on that array. Note that this works because the sections are mapped to mutual -// exclusive memory regions, so we can simply find the largest lower bound among -// the `start` addresses of the sections and then check if our address is inside -// that section. In particular, we store the start address and end address of -// each mapped section in a OCSectionIndex, arrange them all on a contiguous -// memory range and then sort by start address. We then put this array in an -// OCSectionIndices struct to be passed into `checkAddress` to do binary search -// on. +// - Marking object code is done using a global "section index table" +// (global_s_indices below). When we load an object code we add its section +// indices to the table. `markObjectCode` does binary search on this table to +// find object code for the marked object, and mark it and its dependencies. +// +// Dependency of an object code is simply other object code that the object +// code refers to in its code. We know these dependencies by the relocations +// present in the referent. This is recorded by lookupSymbolDependent. +// +// - global_s_indices is updated as we load and unload objects. When we load an +// object code we add its section indices to the table, we remove those +// indices when we unload. +// +// The table is sorted and old indices are removed in `checkUnload`, instead +// on every load/unload, to avoid quadratic behavior when we load a list of +// objects. +// +// - After a major GC `checkUnload` unloads objects that are (1) explicitly +// asked for unloading (via `unloadObj`) and (2) are not marked during GC. +// +// Note that, crucially, we don't unload an object code even if it's not +// reachable from the heap, unless it's explicitly asked for unloading (via +// `unloadObj`). This is a feature and not a but! Two use cases: +// +// - The user might request a symbol from a loaded object at any point with +// lookupSymbol (e.g. GHCi might do this). +// +// - Sometimes we load objects that are not Haskell objects. +// +// To avoid unloading objects that are unreachable but are not asked for +// unloading we maintain a "root set" of object code, `loaded_objects` below. +// `loadObj` adds the loaded objects (and its dependencies) to the list. +// `unloadObj` removes. After a major GC, `checkUnload` first marks the root set +// (`loaded_objects`) to avoid unloading objects that are not asked for +// unloading. +// +// Two other lists `objects` and `old_objects` are similar to large object lists +// in GC. Before a major GC we move `objects` to `old_objects`, and move marked +// objects back to `objects` during evacuation and when marking roots in +// `checkUnload`. Any objects in `old_objects` after that is unloaded. +// +// TODO: We currently don't unload objects when non-moving GC is enabled. The +// implementation would be similar to `nonmovingGcCafs`: +// +// - Maintain a "snapshot": +// +// - Copy `loaded_objects` as the root set of the snapshot +// +// - Stash `objects` to `old_objects` as the snapshot. We don't need a new +// list for this as `old_objects` won't be used by any other code when +// non-moving GC is enabled. +// +// - Copy `global_s_indices` table to be able to mark objects while mutators +// call `loadObj_` and `unloadObj_` concurrently. +// +// - Don't mark object code in `evacuate`, marking will be done in the +// non-moving collector. // +// - After preparation, bump the object code mark bit (`object_code_mark_bit` +// below) and mark static objects using a version of `markObjectCode` that +// basically does the same thing but: +// +// - Needs to update `objects` list in a thread-safe way, as mutators will be +// concurrently calling `loadObj_` and add new stuff to `objects`. +// (alternatively we could have a new list for non-moving GC's objects list, +// and then merge it to the global list in the pause before moving to +// concurrent sweep phase) +// +// - Needs to use the copied `global_s_indices` +// +// - After marking anything left in `old_objects` are unreachable objects within +// the snapshot, unload those. The unload loop will be the same as in +// `checkUnload`. This step needs to happen in the final sync (before sweep +// begins) to avoid races when updating `global_s_indices`. +// +// - NOTE: We don't need write barriers in loadObj/unloadObj as we don't +// introduce a dependency from an already-loaded object to a newly loaded +// object and we don't delete existing dependencies. +// + +uint8_t object_code_mark_bit = 0; typedef struct { W_ start; @@ -62,20 +118,85 @@ typedef struct { } OCSectionIndex; typedef struct { + int capacity; // Doubled on resize int n_sections; + bool sorted; // Invalidated on insertion. Sorted in checkUnload. + bool unloaded; // Whether we removed anything from the table in + // removeOCSectionIndices. If this is set we "compact" the + // table (remove unused entries) in `sortOCSectionIndices. OCSectionIndex *indices; } OCSectionIndices; -static OCSectionIndices *createOCSectionIndices(int n_sections) +// List of currently live objects. Moved to `old_objects` before unload check. +// Marked objects moved back to this list in `markObjectLive`. Remaining objects +// are freed at the end of `checkUnload`. +// +// Double-linked list to be able to remove marked objects. List formed with +// `next` and `prev` fields of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *objects = NULL; + +// `objects` list is moved here before unload check. Marked objects are moved +// back to `objects`. Remaining objects are freed. +static ObjectCode *old_objects = NULL; + +// Number of objects that we want to unload. When this value is 0 we skip static +// object marking during GC and `checkUnload`. +// +// Not static: we use this value to skip static object marking in evacuate when +// this is 0. +// +// Incremented in `unloadObj_`, decremented as we unload objects in +// `checkUnload`. +int n_unloaded_objects = 0; + +// List of objects that we don't want to unload (i.e. we haven't called +// unloadObj on these yet). Used as root set for unload check in checkUnload. +// Objects are added with loadObj_ and removed with unloadObj_. +// +// List formed with `next_loaded_object` field of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *loaded_objects; + +// Section index table for currently loaded objects. New indices are added by +// `loadObj_`, indices of unloaded objects are removed in `checkUnload`. Used to +// map static closures to their ObjectCode. +static OCSectionIndices *global_s_indices = NULL; + +static OCSectionIndices *createOCSectionIndices(void) { - OCSectionIndices *s_indices; - s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); - s_indices->n_sections = n_sections; - s_indices->indices = stgMallocBytes(n_sections*sizeof(OCSectionIndex), + // TODO (osa): Maybe initialize as empty (without allocation) and allocate + // on first insertion? + OCSectionIndices *s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); + int capacity = 1024; + s_indices->capacity = capacity; + s_indices->n_sections = 0; + s_indices->sorted = true; + s_indices->unloaded = false; + s_indices->indices = stgMallocBytes(capacity * sizeof(OCSectionIndex), "OCSectionIndices::indices"); return s_indices; } +static void freeOCSectionIndices(OCSectionIndices *s_indices) +{ + free(s_indices->indices); + free(s_indices); +} + +void initUnloadCheck() +{ + global_s_indices = createOCSectionIndices(); +} + +void exitUnloadCheck() +{ + freeOCSectionIndices(global_s_indices); + global_s_indices = NULL; +} + static int cmpSectionIndex(const void* indexa, const void *indexb) { W_ s1 = ((OCSectionIndex*)indexa)->start; @@ -88,44 +209,124 @@ static int cmpSectionIndex(const void* indexa, const void *indexb) return 0; } -static OCSectionIndices* buildOCSectionIndices(ObjectCode *ocs) +static void reserveOCSectionIndices(OCSectionIndices *s_indices, int len) { - int cnt_sections = 0; - ObjectCode *oc; - for (oc = ocs; oc; oc = oc->next) { - cnt_sections += oc->n_sections; + int current_capacity = s_indices->capacity; + int current_len = s_indices->n_sections; + if (current_capacity - current_len >= len) { + return; + } + + // Round up to nearest power of 2 + int new_capacity = 1 << (int)ceil(log2(current_len + len)); + + OCSectionIndex *old_indices = s_indices->indices; + OCSectionIndex *new_indices = stgMallocBytes(new_capacity * sizeof(OCSectionIndex), + "reserveOCSectionIndices"); + + for (int i = 0; i < current_len; ++i) { + new_indices[i] = old_indices[i]; } - OCSectionIndices* s_indices = createOCSectionIndices(cnt_sections); - int s_i = 0, i; - for (oc = ocs; oc; oc = oc->next) { - for (i = 0; i < oc->n_sections; i++) { - if (oc->sections[i].kind != SECTIONKIND_OTHER) { - s_indices->indices[s_i].start = (W_)oc->sections[i].start; - s_indices->indices[s_i].end = (W_)oc->sections[i].start - + oc->sections[i].size; - s_indices->indices[s_i].oc = oc; - s_i++; + + s_indices->capacity = new_capacity; + s_indices->indices = new_indices; + + free(old_indices); +} + +// Insert object section indices of a single ObjectCode. Invalidates 'sorted' +// state. +void insertOCSectionIndices(ObjectCode *oc) +{ + reserveOCSectionIndices(global_s_indices, oc->n_sections); + global_s_indices->sorted = false; + + int s_i = global_s_indices->n_sections; + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + global_s_indices->indices[s_i].start = (W_)oc->sections[i].start; + global_s_indices->indices[s_i].end = (W_)oc->sections[i].start + + oc->sections[i].size; + global_s_indices->indices[s_i].oc = oc; + s_i++; + } + } + + global_s_indices->n_sections = s_i; + + // Add object to 'objects' list + if (objects != NULL) { + objects->prev = oc; + } + oc->next = objects; + objects = oc; +} + +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr); + +static void removeOCSectionIndices(OCSectionIndices *s_indices, ObjectCode *oc) +{ + // To avoid quadratic behavior in checkUnload we set `oc` fields of indices + // of unloaded objects NULL here. Removing unused entries is done in + // `sortOCSectionIndices`. + + s_indices->unloaded = true; + + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + int section_idx = findSectionIdx(s_indices, oc->sections[i].start); + if (section_idx != -1) { + s_indices->indices[section_idx].oc = NULL; } } } - s_indices->n_sections = s_i; +} + +static void sortOCSectionIndices(OCSectionIndices *s_indices) { + if (s_indices->sorted) { + return; + } + qsort(s_indices->indices, s_indices->n_sections, sizeof(OCSectionIndex), cmpSectionIndex); - return s_indices; + + s_indices->sorted = true; } -static void freeOCSectionIndices(OCSectionIndices *section_indices) -{ - free(section_indices->indices); - free(section_indices); +static void removeRemovedOCSections(OCSectionIndices *s_indices) { + if (!s_indices->unloaded) { + return; + } + + int next_free_idx = 0; + for (int i = 0; i < s_indices->n_sections; ++i) { + if (s_indices->indices[i].oc == NULL) { + // free entry, skip + } else if (i == next_free_idx) { + ++next_free_idx; + } else { + s_indices->indices[next_free_idx] = s_indices->indices[i]; + ++next_free_idx; + } + } + + s_indices->n_sections = next_free_idx; + s_indices->unloaded = true; } -static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { +// Returns -1 if not found +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr) { + ASSERT(s_indices->sorted); + W_ w_addr = (W_)addr; - if (s_indices->n_sections <= 0) return NULL; - if (w_addr < s_indices->indices[0].start) return NULL; + if (s_indices->n_sections <= 0) { + return -1; + } + if (w_addr < s_indices->indices[0].start) { + return -1; + } int left = 0, right = s_indices->n_sections; while (left + 1 < right) { @@ -139,330 +340,125 @@ static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { } ASSERT(w_addr >= s_indices->indices[left].start); if (w_addr < s_indices->indices[left].end) { - return s_indices->indices[left].oc; + return left; } - return NULL; + return -1; } -static void checkAddress (HashTable *addrs, const void *addr, - OCSectionIndices *s_indices) -{ - ObjectCode *oc; - - if (!lookupHashTable(addrs, (W_)addr)) { - insertHashTable(addrs, (W_)addr, addr); +static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { + int oc_idx = findSectionIdx(s_indices, addr); - oc = findOC(s_indices, addr); - if (oc != NULL) { - oc->referenced = 1; - return; - } + if (oc_idx == -1) { + return NULL; } + + return s_indices->indices[oc_idx].oc; } -static void searchStackChunk (HashTable *addrs, StgPtr sp, StgPtr stack_end, - OCSectionIndices *s_indices) -{ - StgPtr p; - const StgRetInfoTable *info; +static bool markObjectLive(void *data STG_UNUSED, StgWord key, const void *value STG_UNUSED) { + ObjectCode *oc = (ObjectCode*)key; + if (oc->mark == object_code_mark_bit) { + return true; // for hash table iteration + } + + oc->mark = object_code_mark_bit; + // Remove from 'old_objects' list + if (oc->prev != NULL) { + // TODO(osa): Maybe 'prev' should be a pointer to the referencing + // *field* ? (instead of referencing *object*) + oc->prev->next = oc->next; + } else { + old_objects = oc->next; + } + if (oc->next != NULL) { + oc->next->prev = oc->prev; + } - p = sp; - while (p < stack_end) { - info = get_ret_itbl((StgClosure *)p); + // Add it to 'objects' list + oc->prev = NULL; + oc->next = objects; + if (objects != NULL) { + objects->prev = oc; + } + objects = oc; - switch (info->i.type) { - case RET_SMALL: - case RET_BIG: - checkAddress(addrs, (const void*)info, s_indices); - break; + // Mark its dependencies + iterHashTable(oc->dependencies, NULL, markObjectLive); - default: - break; - } + return true; // for hash table iteration +} + +void markObjectCode(const void *addr) +{ + if (global_s_indices == NULL) { + return; + } - p += stack_frame_sizeW((StgClosure*)p); + // This should be checked at the call site + ASSERT(!HEAP_ALLOCED(addr)); + + ObjectCode *oc = findOC(global_s_indices, addr); + if (oc != NULL) { + // Mark the object code and its dependencies + markObjectLive(NULL, (W_)oc, NULL); } } - -static void searchHeapBlocks (HashTable *addrs, bdescr *bd, - OCSectionIndices *s_indices) +// Returns whether or not the GC that follows needs to mark code for potential +// unloading. +bool prepareUnloadCheck() { - StgPtr p; - const StgInfoTable *info; - uint32_t size; - bool prim; + if (global_s_indices == NULL) { + return false; + } - for (; bd != NULL; bd = bd->link) { + removeRemovedOCSections(global_s_indices); + sortOCSectionIndices(global_s_indices); - if (bd->flags & BF_PINNED) { - // Assume that objects in PINNED blocks cannot refer to - continue; - } + ASSERT(old_objects == NULL); - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); - prim = false; - - switch (info->type) { - - case THUNK: - size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case FUN: - case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR: - case CONSTR_NOCAF: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case BLACKHOLE: - case BLOCKING_QUEUE: - prim = true; - size = sizeW_fromITBL(info); - break; - - case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. - prim = true; - size = BLACKHOLE_sizeW(); - break; - - case BCO: - prim = true; - size = bco_sizeW((StgBCO *)p); - break; - - case MVAR_CLEAN: - case MVAR_DIRTY: - case TVAR: - case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = true; - size = sizeW_fromITBL(info); - break; - - case AP: - prim = true; - size = ap_sizeW((StgAP *)p); - break; - - case PAP: - prim = true; - size = pap_sizeW((StgPAP *)p); - break; - - case AP_STACK: - { - StgAP_STACK *ap = (StgAP_STACK *)p; - prim = true; - size = ap_stack_sizeW(ap); - searchStackChunk(addrs, (StgPtr)ap->payload, - (StgPtr)ap->payload + ap->size, s_indices); - break; - } + object_code_mark_bit = ~object_code_mark_bit; + old_objects = objects; + objects = NULL; + return true; +} - case ARR_WORDS: - prim = true; - size = arr_words_sizeW((StgArrBytes*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN_CLEAN: - case MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = true; - size = sizeofW(StgTSO); - break; - - case STACK: { - StgStack *stack = (StgStack*)p; - prim = true; - searchStackChunk(addrs, stack->sp, - stack->stack + stack->stack_size, s_indices); - size = stack_sizeW(stack); - break; - } +void checkUnload() +{ + if (global_s_indices == NULL) { + return; + } - case TREC_CHUNK: - prim = true; - size = sizeofW(StgTRecChunk); - break; + // At this point we've marked all dynamically loaded static objects + // (including their dependencies) during GC, but not the root set of object + // code (loaded_objects). Mark the roots first, then unload any unmarked + // objects. - default: - barf("searchHeapBlocks, unknown object: %d", info->type); - } + OCSectionIndices *s_indices = global_s_indices; + ASSERT(s_indices->sorted); - if (!prim) { - checkAddress(addrs,info, s_indices); - } - - p += size; - } + // Mark roots + for (ObjectCode *oc = loaded_objects; oc != NULL; oc = oc->next_loaded_object) { + markObjectLive(NULL, (W_)oc, NULL); } -} -#if defined(PROFILING) -// -// Do not unload the object if the CCS tree refers to a CCS or CC which -// originates in the object. -// -static void searchCostCentres (HashTable *addrs, CostCentreStack *ccs, - OCSectionIndices* s_indices) -{ - IndexTable *i; + // Free unmarked objects + ObjectCode *next = NULL; + for (ObjectCode *oc = old_objects; oc != NULL; oc = next) { + next = oc->next; - checkAddress(addrs, ccs, s_indices); - checkAddress(addrs, ccs->cc, s_indices); - for (i = ccs->indexTable; i != NULL; i = i->next) { - if (!i->back_edge) { - searchCostCentres(addrs, i->ccs, s_indices); - } + removeOCSectionIndices(s_indices, oc); + + // Symbols should be removed by unloadObj_. + // NB (osa): If this assertion doesn't hold then freeObjectCode below + // will corrupt symhash as keys of that table live in ObjectCodes. If + // you see a segfault in a hash table operation in linker (in non-debug + // RTS) then it's probably becuse this assertion did not hold. + ASSERT(oc->symbols == NULL); + + freeObjectCode(oc); + n_unloaded_objects -= 1; } -} -#endif -// -// Check whether we can unload any object code. This is called at the -// appropriate point during a GC, where all the heap data is nice and -// packed together and we have a linked list of the static objects. -// -// The check involves a complete heap traversal, but you only pay for -// this (a) when you have called unloadObj(), and (b) at a major GC, -// which is much more expensive than the traversal we're doing here. -// -void checkUnload (StgClosure *static_objects) -{ - uint32_t g, n; - HashTable *addrs; - StgClosure* p; - const StgInfoTable *info; - ObjectCode *oc, *prev, *next; - gen_workspace *ws; - StgClosure* link; - - if (unloaded_objects == NULL) return; - - ACQUIRE_LOCK(&linker_unloaded_mutex); - - OCSectionIndices *s_indices = buildOCSectionIndices(unloaded_objects); - // Mark every unloadable object as unreferenced initially - for (oc = unloaded_objects; oc; oc = oc->next) { - IF_DEBUG(linker, debugBelch("Checking whether to unload %" PATH_FMT "\n", - oc->fileName)); - oc->referenced = false; - } - - addrs = allocHashTable(); - - for (p = static_objects; p != END_OF_STATIC_OBJECT_LIST; p = link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - info = get_itbl(p); - checkAddress(addrs, info, s_indices); - link = *STATIC_LINK(info, p); - } - - // CAFs on revertible_caf_list are not on static_objects - for (p = (StgClosure*)revertible_caf_list; - p != END_OF_CAF_LIST; - p = ((StgIndStatic *)p)->static_link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - } - - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - searchHeapBlocks (addrs, generations[g].blocks, s_indices); - searchHeapBlocks (addrs, generations[g].large_objects, s_indices); - - for (n = 0; n < n_capabilities; n++) { - ws = &gc_threads[n]->gens[g]; - searchHeapBlocks(addrs, ws->todo_bd, s_indices); - searchHeapBlocks(addrs, ws->part_list, s_indices); - searchHeapBlocks(addrs, ws->scavd_list, s_indices); - } - } - -#if defined(PROFILING) - /* Traverse the cost centre tree, calling checkAddress on each CCS/CC */ - searchCostCentres(addrs, CCS_MAIN, s_indices); - - /* Also check each cost centre in the CC_LIST */ - CostCentre *cc; - for (cc = CC_LIST; cc != NULL; cc = cc->link) { - checkAddress(addrs, cc, s_indices); - } -#endif /* PROFILING */ - - freeOCSectionIndices(s_indices); - // Look through the unloadable objects, and any object that is still - // marked as unreferenced can be physically unloaded, because we - // have no references to it. - prev = NULL; - for (oc = unloaded_objects; oc; oc = next) { - next = oc->next; - if (oc->referenced == 0) { - if (prev == NULL) { - unloaded_objects = oc->next; - } else { - prev->next = oc->next; - } - IF_DEBUG(linker, debugBelch("Unloading object file %" PATH_FMT "\n", - oc->fileName)); - freeObjectCode(oc); - } else { - IF_DEBUG(linker, debugBelch("Object file still in use: %" - PATH_FMT "\n", oc->fileName)); - prev = oc; - } - } - - freeHashTable(addrs, NULL); - - RELEASE_LOCK(&linker_unloaded_mutex); + old_objects = NULL; } ===================================== rts/CheckUnload.h ===================================== @@ -12,6 +12,34 @@ #include "BeginPrivate.h" -void checkUnload (StgClosure *static_objects); +#include "LinkerInternals.h" + +// Currently live objects +extern ObjectCode *objects; + +// Root set for object collection +extern ObjectCode *loaded_objects; + +// Mark bit for live objects +extern uint8_t object_code_mark_bit; + +// Number of object code currently marked for unloading. See the definition in +// CheckUnload.c for details. +extern int n_unloaded_objects; + +void initUnloadCheck(void); +void exitUnloadCheck(void); + +// Call before major GC to prepare section index table for marking +bool prepareUnloadCheck(void); + +// Mark object code of a static closure address as 'live' +void markObjectCode(const void *addr); + +// Call after major GC to unload unused and unmarked object code +void checkUnload(void); + +// Call on loaded object code +void insertOCSectionIndices(ObjectCode *oc); #include "EndPrivate.h" ===================================== rts/Hash.c ===================================== @@ -400,6 +400,27 @@ mapHashTable(HashTable *table, void *data, MapHashFn fn) } } +void +iterHashTable(HashTable *table, void *data, IterHashFn fn) +{ + /* The last bucket with something in it is table->max + table->split - 1 */ + long segment = (table->max + table->split - 1) / HSEGSIZE; + long index = (table->max + table->split - 1) % HSEGSIZE; + + while (segment >= 0) { + while (index >= 0) { + for (HashList *hl = table->dir[segment][index]; hl != NULL; hl = hl->next) { + if (!fn(data, hl->key, hl->data)) { + return; + } + } + index--; + } + segment--; + index = HSEGSIZE - 1; + } +} + /* ----------------------------------------------------------------------------- * When we initialize a hash table, we set up the first segment as well, * initializing all of the first segment's hash buckets to NULL. @@ -444,12 +465,6 @@ allocStrHashTable(void) return allocHashTable_(hashStr, compareStr); } -void -exitHashTable(void) -{ - /* nothing to do */ -} - int keyCountHashTable (HashTable *table) { return table->kcount; ===================================== rts/Hash.h ===================================== @@ -33,8 +33,11 @@ int keyCountHashTable (HashTable *table); int keysHashTable(HashTable *table, StgWord keys[], int szKeys); typedef void (*MapHashFn)(void *data, StgWord key, const void *value); +// Return true -> continue; false -> stop +typedef bool (*IterHashFn)(void *data, StgWord key, const void *value); void mapHashTable(HashTable *table, void *data, MapHashFn fn); +void iterHashTable(HashTable *table, void *data, IterHashFn); /* Hash table access where the keys are C strings (the strings are * assumed to be allocated by the caller, and mustn't be deallocated @@ -62,6 +65,32 @@ int hashStr(const HashTable *table, StgWord key); */ void freeHashTable ( HashTable *table, void (*freeDataFun)(void *) ); -void exitHashTable ( void ); +INLINE_HEADER void freeStrHashTable ( StrHashTable *table, void (*freeDataFun)(void *) ) +{ + freeHashTable((HashTable*)table, freeDataFun); +} + +/* + * Hash set API + * + * A hash set is bascially a hash table where values are NULL. + */ + +typedef struct hashtable HashSet; + +INLINE_HEADER HashSet *allocHashSet ( void ) +{ + return (HashSet*)allocHashTable(); +} + +INLINE_HEADER void freeHashSet ( HashSet *set ) +{ + freeHashTable((HashTable*)set, NULL); +} + +INLINE_HEADER void insertHashSet ( HashSet *set, StgWord key ) +{ + insertHashTable((HashTable*)set, key, NULL); +} #include "EndPrivate.h" ===================================== rts/Linker.c ===================================== @@ -32,6 +32,7 @@ #include "linker/CacheFlush.h" #include "linker/SymbolExtras.h" #include "PathUtils.h" +#include "CheckUnload.h" // createOCSectionIndices #if !defined(mingw32_HOST_OS) #include "posix/Signals.h" @@ -161,23 +162,9 @@ */ /*Str*/HashTable *symhash; -/* List of currently loaded objects */ -ObjectCode *objects = NULL; /* initially empty */ - -/* List of objects that have been unloaded via unloadObj(), but are waiting - to be actually freed via checkUnload() */ -ObjectCode *unloaded_objects = NULL; /* initially empty */ - #if defined(THREADED_RTS) -/* This protects all the Linker's global state except unloaded_objects */ +/* This protects all the Linker's global state */ Mutex linker_mutex; -/* - * This protects unloaded_objects. We have a separate mutex for this, because - * the GC needs to access unloaded_objects in checkUnload, while the linker only - * needs to access unloaded_objects in unloadObj(), so this allows most linker - * operations proceed concurrently with the GC. - */ -Mutex linker_unloaded_mutex; #endif /* Generic wrapper function to try and Resolve and RunInit oc files */ @@ -447,12 +434,10 @@ initLinker_ (int retain_cafs) linker_init_done = 1; } - objects = NULL; - unloaded_objects = NULL; + initUnloadCheck(); #if defined(THREADED_RTS) initMutex(&linker_mutex); - initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -538,6 +523,7 @@ exitLinker( void ) { #endif if (linker_init_done == 1) { freeHashTable(symhash, free); + exitUnloadCheck(); } #if defined(THREADED_RTS) closeMutex(&linker_mutex); @@ -864,18 +850,24 @@ HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data) } /* ----------------------------------------------------------------------------- - * lookup a symbol in the hash table + * Lookup a symbol in the hash table + * + * When 'dependent' is not NULL, adds it as a dependent to the owner of the + * symbol. */ #if defined(OBJFORMAT_PEi386) -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + (void)dependent; // TODO + ASSERT_LOCK_HELD(&linker_mutex); return lookupSymbol_PEi386(lbl); } #else -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + ASSERT_LOCK_HELD(&linker_mutex); IF_DEBUG(linker, debugBelch("lookupSymbol: looking up '%s'\n", lbl)); ASSERT(symhash != NULL); @@ -900,10 +892,18 @@ SymbolAddr* lookupSymbol_ (SymbolName* lbl) return internal_dlsym(lbl + 1); # else - ASSERT(2+2 == 5); + ASSERT(false); return NULL; # endif } else { + if (dependent) { + // Add dependent as symbol's owner's dependency + ObjectCode *owner = pinfo->owner; + if (owner) { + // TODO: what does it mean for a symbol to not have an owner? + insertHashSet(dependent->dependencies, (W_)owner); + } + } return loadSymbol(lbl, pinfo); } } @@ -1342,6 +1342,8 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->fileName); stgFree(oc->archiveMemberName); + freeHashSet(oc->dependencies); + stgFree(oc); } @@ -1403,6 +1405,10 @@ mkOc( pathchar *path, char *image, int imageSize, /* chain it onto the list of objects */ oc->next = NULL; + oc->prev = NULL; + oc->next_loaded_object = NULL; + oc->mark = object_code_mark_bit; + oc->dependencies = allocHashSet(); #if RTS_LINKER_USE_MMAP oc->rw_m32 = m32_allocator_new(false); @@ -1421,9 +1427,9 @@ mkOc( pathchar *path, char *image, int imageSize, HsInt isAlreadyLoaded( pathchar *path ) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path) + && o->status != OBJECT_UNLOADED) { return 1; /* already loaded */ } } @@ -1557,21 +1563,16 @@ preloadObjectFile (pathchar *path) */ static HsInt loadObj_ (pathchar *path) { - ObjectCode* oc; - IF_DEBUG(linker, debugBelch("loadObj: %" PATH_FMT "\n", path)); - - /* debugBelch("loadObj %s\n", path ); */ - - /* Check that we haven't already loaded this object. - Ignore requests to load multiple times */ + // Check that we haven't already loaded this object. + // Ignore requests to load multiple times if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); - return 1; /* success */ + return 1; // success } - oc = preloadObjectFile(path); + ObjectCode *oc = preloadObjectFile(path); if (oc == NULL) return 0; if (! loadOc(oc)) { @@ -1582,8 +1583,10 @@ static HsInt loadObj_ (pathchar *path) return 0; } - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); + + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; return 1; } @@ -1778,15 +1781,15 @@ int ocTryLoad (ObjectCode* oc) { */ static HsInt resolveObjs_ (void) { - ObjectCode *oc; - int r; - IF_DEBUG(linker, debugBelch("resolveObjs: start\n")); - for (oc = objects; oc; oc = oc->next) { - r = ocTryLoad(oc); + for (ObjectCode *oc = objects; oc; oc = oc->next) { + int r = ocTryLoad(oc); if (!r) { + errorBelch("Could not load Object Code %" PATH_FMT ".\n", OC_INFORMATIVE_FILENAME(oc)); + IF_DEBUG(linker, printLoadedObjects()); + fflush(stderr); return r; } } @@ -1813,45 +1816,35 @@ HsInt resolveObjs (void) */ static HsInt unloadObj_ (pathchar *path, bool just_purge) { - ObjectCode *oc, *prev, *next; - HsBool unloadedAnyObj = HS_BOOL_FALSE; - ASSERT(symhash != NULL); ASSERT(objects != NULL); IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); - prev = NULL; - for (oc = objects; oc; oc = next) { - next = oc->next; // oc might be freed - - if (!pathcmp(oc->fileName,path)) { + bool unloadedAnyObj = false; + ObjectCode *prev = NULL; + // NOTE (osa): There may be more than one object with the same file name + // (happens when loading archive files) so we don't stop after unloading one + for (ObjectCode *oc = loaded_objects; oc; oc = oc->next_loaded_object) { + if (pathcmp(oc->fileName,path) == 0) { + oc->status = OBJECT_UNLOADED; - // these are both idempotent, so in just_purge mode we can - // later call unloadObj() to really unload the object. + // These are both idempotent, so in just_purge mode we can later + // call unloadObj() to really unload the object. removeOcSymbols(oc); freeOcStablePtrs(oc); + unloadedAnyObj = true; + if (!just_purge) { + n_unloaded_objects += 1; + // Remove object code from root set if (prev == NULL) { - objects = oc->next; + loaded_objects = oc->next_loaded_object; } else { - prev->next = oc->next; + prev->next_loaded_object = oc->next_loaded_object; } - ACQUIRE_LOCK(&linker_unloaded_mutex); - oc->next = unloaded_objects; - unloaded_objects = oc; - oc->status = OBJECT_UNLOADED; - RELEASE_LOCK(&linker_unloaded_mutex); - // We do not own oc any more; it can be released at any time by - // the GC in checkUnload(). - } else { - prev = oc; } - - /* This could be a member of an archive so continue - * unloading other members. */ - unloadedAnyObj = HS_BOOL_TRUE; } else { prev = oc; } @@ -1859,8 +1852,7 @@ static HsInt unloadObj_ (pathchar *path, bool just_purge) if (unloadedAnyObj) { return 1; - } - else { + } else { errorBelch("unloadObj: can't find `%" PATH_FMT "' to unload", path); return 0; } @@ -1884,13 +1876,7 @@ HsInt purgeObj (pathchar *path) static OStatus getObjectLoadStatus_ (pathchar *path) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } - } - for (o = unloaded_objects; o; o = o->next) { + for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { return o->status; } ===================================== rts/LinkerInternals.h ===================================== @@ -191,9 +191,6 @@ typedef struct _ObjectCode { /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; - /* flag used when deciding whether to unload an object file */ - int referenced; - /* record by how much image has been deliberately misaligned after allocation, so that we can use realloc */ int misalignment; @@ -205,8 +202,37 @@ typedef struct _ObjectCode { int n_segments; Segment *segments; - /* Allow a chain of these things */ - struct _ObjectCode * next; + // + // Garbage collection fields + // + + // Next object in `objects` list + struct _ObjectCode *next; + + // Previous object in `objects` list + struct _ObjectCode *prev; + + // Next object in `loaded_objects` list + struct _ObjectCode *next_loaded_object; + + // Mark bit + uint8_t mark; + + // Set of dependencies (ObjectCode*) of the object file. Traverse + // dependencies using `iterHashTable`. + // + // New entries are added as we resolve symbols in an object file, in + // `lookupDependentSymbol`. When an object file uses multiple symbols from + // another object file we add the dependent multiple times, so we use a + // `HashTable` here rather than a list/array to avoid copies. + // + // Used when unloading object files. See Note [Object unloading] in + // CheckUnload.c. + HashSet *dependencies; + + // + // End of garbage collection fields + // /* SANITY CHECK ONLY: a list of the only memory regions which may safely be prodded during relocation. Any attempt to prod @@ -250,12 +276,8 @@ typedef struct _ObjectCode { (OC)->fileName \ ) -extern ObjectCode *objects; -extern ObjectCode *unloaded_objects; - #if defined(THREADED_RTS) extern Mutex linker_mutex; -extern Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -306,8 +328,9 @@ int ghciInsertSymbolTable( HsBool weak, ObjectCode *owner); -/* lock-free version of lookupSymbol */ -SymbolAddr* lookupSymbol_ (SymbolName* lbl); +/* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a + * dependent to the owner of the symbol. */ +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent); extern /*Str*/HashTable *symhash; ===================================== rts/PrimOps.cmm ===================================== @@ -1816,9 +1816,16 @@ loop: // There are readMVar/takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1843,10 +1850,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); @@ -1901,9 +1906,16 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1928,10 +1940,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/RtsStartup.c ===================================== @@ -512,9 +512,6 @@ hs_exit_(bool wait_foreign) shutdownAsyncIO(wait_foreign); #endif - /* free hash table storage */ - exitHashTable(); - // Finally, free all our storage. However, we only free the heap // memory if we have waited for foreign calls to complete; // otherwise a foreign call in progress may still be referencing ===================================== rts/Threads.c ===================================== @@ -790,9 +790,14 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = q->tso; - mvar->head = q->link; - if (mvar->head == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { + mvar->head = q = q->link; + if (q == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { mvar->tail = (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure; + } else { + if (info == &stg_MVAR_CLEAN_info) { + // Resolve #18919. + dirty_MVAR(&cap->r, (StgClosure*)mvar, mvar->value); + } } ASSERT(tso->block_info.closure == (StgClosure*)mvar); @@ -816,10 +821,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = ((StgMVarTSOQueue*)q)->link; + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/linker/Elf.c ===================================== @@ -1099,7 +1099,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) { S = (Elf_Addr)symbol->addr; } else { - S_tmp = lookupSymbol_( symbol->name ); + S_tmp = lookupDependentSymbol( symbol->name, oc ); S = (Elf_Addr)S_tmp; } if (!S) { @@ -1519,7 +1519,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } else { /* No, so look up the name in our global table. */ symbol = strtab + sym.st_name; - S_tmp = lookupSymbol_( symbol ); + S_tmp = lookupDependentSymbol( symbol, oc ); S = (Elf_Addr)S_tmp; } if (!S) { ===================================== rts/linker/LoadArchive.c ===================================== @@ -5,6 +5,7 @@ #include "sm/OSMem.h" #include "RtsUtils.h" #include "LinkerInternals.h" +#include "CheckUnload.h" // loaded_objects, insertOCSectionIndices #include "linker/M32Alloc.h" /* Platform specific headers */ @@ -241,7 +242,6 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, static HsInt loadArchive_ (pathchar *path) { - ObjectCode* oc = NULL; char *image = NULL; HsInt retcode = 0; int memberSize; @@ -520,8 +520,8 @@ static HsInt loadArchive_ (pathchar *path) sprintf(archiveMemberName, "%" PATH_FMT "(%.*s)", path, (int)thisFileNameSize, fileName); - oc = mkOc(path, image, memberSize, false, archiveMemberName - , misalignment); + ObjectCode *oc = mkOc(path, image, memberSize, false, archiveMemberName, + misalignment); #if defined(OBJFORMAT_MACHO) ocInit_MachO( oc ); #endif @@ -536,8 +536,9 @@ static HsInt loadArchive_ (pathchar *path) fclose(f); return 0; } else { - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); // also adds the object to `objects` list + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; } } else if (isGnuIndex) { ===================================== rts/linker/MachO.c ===================================== @@ -242,7 +242,7 @@ resolveImports( addr = (SymbolAddr*) (symbol->nlist->n_value); IF_DEBUG(linker, debugBelch("resolveImports: undefined external %s has value %p\n", symbol->name, addr)); } else { - addr = lookupSymbol_(symbol->name); + addr = lookupDependentSymbol(symbol->name, oc); IF_DEBUG(linker, debugBelch("resolveImports: looking up %s, %p\n", symbol->name, addr)); } @@ -564,12 +564,12 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { /* external symbols should be able to be - * looked up via the lookupSymbol_ function. + * looked up via the lookupDependentSymbol function. * Either through the global symbol hashmap * or asking the system, if not found * in the symbol hashmap */ - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -609,7 +609,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -784,7 +784,7 @@ relocateSection(ObjectCode* oc, int curSection) // symtab, or it is undefined, meaning dlsym must be used // to resolve it. - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); IF_DEBUG(linker, debugBelch("relocateSection: looked up %s, " "external X86_64_RELOC_GOT or X86_64_RELOC_GOT_LOAD\n" " : addr = %p\n", nm, addr)); @@ -845,7 +845,7 @@ relocateSection(ObjectCode* oc, int curSection) nm, (void *)value)); } else { - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); if (addr == NULL) { errorBelch("\nlookupSymbol failed in relocateSection (relocate external)\n" @@ -1345,7 +1345,7 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->nlist[i].n_type & N_EXT) { if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) - && lookupSymbol_(nm)) { + && lookupDependentSymbol(nm, oc)) { // weak definition, and we already have a definition IF_DEBUG(linker, debugBelch(" weak: %s\n", nm)); } @@ -1497,7 +1497,7 @@ ocResolve_MachO(ObjectCode* oc) * have the address. */ if(NULL == symbol->addr) { - symbol->addr = lookupSymbol_((char*)symbol->name); + symbol->addr = lookupDependentSymbol((char*)symbol->name, oc); if(NULL == symbol->addr) barf("Failed to lookup symbol: %s", symbol->name); } else { ===================================== rts/linker/PEi386.c ===================================== @@ -185,6 +185,7 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" #include "GetEnv.h" +#include "CheckUnload.h" #include "linker/PEi386.h" #include "linker/PEi386Types.h" #include "linker/SymbolExtras.h" @@ -1894,7 +1895,7 @@ ocResolve_PEi386 ( ObjectCode* oc ) } else { copyName ( getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1 ); - S = (size_t) lookupSymbol_( (char*)symbol ); + S = (size_t) lookupDependentSymbol( (char*)symbol, oc ); if ((void*)S == NULL) { errorBelch(" | %" PATH_FMT ": unknown symbol `%s'", oc->fileName, symbol); releaseOcInfo (oc); ===================================== rts/linker/elf_got.c ===================================== @@ -88,7 +88,7 @@ fillGot(ObjectCode * oc) { if( STT_NOTYPE == ELF_ST_TYPE(symbol->elf_sym->st_info) || STB_WEAK == ELF_ST_BIND(symbol->elf_sym->st_info)) { if(0x0 == symbol->addr) { - symbol->addr = lookupSymbol_(symbol->name); + symbol->addr = lookupDependentSymbol(symbol->name, oc); if(0x0 == symbol->addr) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; ===================================== rts/sm/Evac.c ===================================== @@ -28,6 +28,7 @@ #include "CNF.h" #include "Scav.h" #include "NonMoving.h" +#include "CheckUnload.h" // n_unloaded_objects and markObjectCode #if defined(THREADED_RTS) && !defined(PARALLEL_GC) #define evacuate(p) evacuate1(p) @@ -593,6 +594,11 @@ loop: if (!HEAP_ALLOCED_GC(q)) { if (!major_gc) return; + // Note [Object unloading] in CheckUnload.c + if (RTS_UNLIKELY(unload_mark_needed)) { + markObjectCode(q); + } + info = get_itbl(q); switch (info->type) { ===================================== rts/sm/GC.c ===================================== @@ -97,6 +97,13 @@ * See also: Note [STATIC_LINK fields] in Storage.h. */ +/* Hot GC globals + * ~~~~~~~~~~~~~~ + * The globals below are quite hot during GC but read-only, initialized during + * the beginning of collection. It is important that they reside in the same + * cache-line to minimize unnecessary cache misses. + */ + /* N is the oldest generation being collected, where the generations * are numbered starting at 0. A major GC (indicated by the major_gc * flag) is when we're collecting all generations. We only attempt to @@ -105,6 +112,7 @@ uint32_t N; bool major_gc; bool deadlock_detect_gc; +bool unload_mark_needed; /* Data used for allocation area sizing. */ @@ -297,6 +305,12 @@ GarbageCollect (uint32_t collect_gen, static_flag == STATIC_FLAG_A ? STATIC_FLAG_B : STATIC_FLAG_A; } + if (major_gc) { + unload_mark_needed = prepareUnloadCheck(); + } else { + unload_mark_needed = false; + } + #if defined(THREADED_RTS) work_stealing = RtsFlags.ParFlags.parGcLoadBalancingEnabled && N >= RtsFlags.ParFlags.parGcLoadBalancingGen; @@ -810,9 +824,12 @@ GarbageCollect (uint32_t collect_gen, resetNurseries(); - // mark the garbage collected CAFs as dead #if defined(DEBUG) - if (major_gc && !RtsFlags.GcFlags.useNonmoving) { gcCAFs(); } + // Mark the garbage collected CAFs as dead. Done in `nonmovingGcCafs()` when + // non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + gcCAFs(); + } #endif // Update the stable name hash table @@ -823,9 +840,14 @@ GarbageCollect (uint32_t collect_gen, // hs_free_stable_ptr(), both of which access the StablePtr table. stablePtrUnlock(); - // Must be after stablePtrUnlock(), because it might free stable ptrs. - if (major_gc) { - checkUnload (gct->scavenged_static_objects); + // Unload dynamically-loaded object code after a major GC. + // See Note [Object unloading] in CheckUnload.c for details. + // + // TODO: Similar to `nonmovingGcCafs` non-moving GC should have its own + // collector for these objects, but that's currently not implemented, so we + // simply don't unload object code when non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + checkUnload(); } #if defined(PROFILING) ===================================== rts/sm/GC.h ===================================== @@ -35,6 +35,7 @@ extern uint32_t N; extern bool major_gc; /* See Note [Deadlock detection under nonmoving collector]. */ extern bool deadlock_detect_gc; +extern bool unload_mark_needed; extern bdescr *mark_stack_bd; extern bdescr *mark_stack_top_bd; ===================================== testsuite/tests/ghci/T16525a/T16525a.script ===================================== @@ -1,6 +1,10 @@ :set -fobject-code :load A import Control.Concurrent -_ <- forkIO $ threadDelay 1000000 >> (print (map v1 value)) +_ <- forkIO $ threadDelay 500000 >> print (map v1 value) :l [] System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC ===================================== testsuite/tests/ghci/T16525a/T16525a.stdout ===================================== @@ -0,0 +1 @@ +["a;lskdfa;lszkfsd;alkfjas"] ===================================== testsuite/tests/ghci/T16525a/all.T ===================================== @@ -1,6 +1,3 @@ test('T16525a', - [extra_files(['A.hs', 'B.hs', ]), - when(compiler_debugged(), extra_run_opts('+RTS -DS -RTS')), - # We don't support unloading with the dynamic linker - when(ghc_dynamic(), skip), ], + [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525a.script']) ===================================== testsuite/tests/ghci/T16525b/A.hs ===================================== @@ -0,0 +1,6 @@ +module A (a) where + +import B + +a :: () -> IO Int +a x = b x ===================================== testsuite/tests/ghci/T16525b/B.hs ===================================== @@ -0,0 +1,5 @@ +module B (b) where + +{-# NOINLINE b #-} +b :: () -> IO Int +b () = return 999999999 ===================================== testsuite/tests/ghci/T16525b/T16525b.script ===================================== @@ -0,0 +1,22 @@ +:set -fobject-code +:load A +import Control.Concurrent +import Control.Monad +:{ +_ <- forkIO $ do + replicateM_ 3 (a () >>= print >> threadDelay 500000) + putStrLn "===== THREAD DONE =====" +:} +:l [] +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 ===================================== testsuite/tests/ghci/T16525b/T16525b.stdout ===================================== @@ -0,0 +1,4 @@ +999999999 +999999999 +999999999 +===== THREAD DONE ===== ===================================== testsuite/tests/ghci/T16525b/all.T ===================================== @@ -0,0 +1,2 @@ +# Tests unloading an object file which is in use in a thread +test('T16525b', [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525b.script']) ===================================== testsuite/tests/rts/linker/linker_error.c ===================================== @@ -57,7 +57,10 @@ int main (int argc, char *argv[]) r = resolveObjs(); if (!r) { debugBelch("resolveObjs failed\n"); + // Mark the object as unloadable: unloadObj(obj); + // Actually unload it: + performMajorGC(); continue; } errorBelch("loading succeeded"); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a4153029347c48be38bace114438b72475e2c40f...180f58cf281e00bf5c9b7a514a799706535dc5b9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a4153029347c48be38bace114438b72475e2c40f...180f58cf281e00bf5c9b7a514a799706535dc5b9 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 Sun Nov 22 15:58:51 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 10:58:51 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/ci-only-tests Message-ID: <5fba8abbe828_36a715ae31b060738@gitlab.mail> Ben Gamari pushed new branch wip/ci-only-tests at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ci-only-tests 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 Sun Nov 22 15:59:31 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 10:59:31 -0500 Subject: [Git][ghc/ghc][wip/ci-only-tests] gitlab-ci: Introduce ONLY_TESTS variable Message-ID: <5fba8ae38451_36a73fd2f1fdd7f8607534@gitlab.mail> Ben Gamari pushed to branch wip/ci-only-tests at Glasgow Haskell Compiler / GHC Commits: 830be013 by Ben Gamari at 2020-11-22T10:59:26-05:00 gitlab-ci: Introduce ONLY_TESTS variable When using ci.sh manually it is often useful to run just a subset of tests. - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -45,6 +45,7 @@ Environment variables affecting both build systems: VERBOSE Set to non-empty for verbose build output MSYSTEM (Windows-only) Which platform to build form (MINGW64 or MINGW32). + ONLY_TESTS Select a subset of tests to run Environment variables determining build configuration of Make system: @@ -430,10 +431,15 @@ function determine_metric_baseline() { } function test_make() { + local tests="" + if [[ -n "$ONLY_TESTS" ]]; then + tests="TEST=$ONLY_TESTS" + fi run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ - JUNIT_FILE=../../junit.xml + JUNIT_FILE=../../junit.xml \ + "$tests" } function build_hadrian() { @@ -450,6 +456,11 @@ function build_hadrian() { } function test_hadrian() { + local tests="" + if [[ -n "$ONLY_TESTS" ]]; then + tests="--only=$ONLY_TESTS" + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -458,7 +469,8 @@ function test_hadrian() { run_hadrian \ test \ --summary-junit=./junit.xml \ - --test-compiler="$TOP"/_build/install/bin/ghc + --test-compiler="$TOP"/_build/install/bin/ghc \ + "$tests" } function cabal_test() { @@ -498,13 +510,15 @@ function clean() { function run_hadrian() { if [ -z "$BIGNUM_BACKEND" ]; then BIGNUM_BACKEND="gmp"; fi if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi - run hadrian/build-cabal \ - --flavour="$BUILD_FLAVOUR" \ - -j"$cores" \ - --broken-test="$BROKEN_TESTS" \ - --bignum=$BIGNUM_BACKEND \ - $HADRIAN_ARGS \ - $@ + local args=( + "--flavour=$BUILD_FLAVOUR" + "-j$cores" + "--broken-test=$BROKEN_TESTS" + "--bignum=$BIGNUM_BACKEND" + "${HADRIAN_ARGS[@]}" + "$@" + ) + run hadrian/build-cabal "${args[@]}" } # A convenience function to allow debugging in the CI environment. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/830be013dfb6dae2eee45cb3fe805d531eab523a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/830be013dfb6dae2eee45cb3fe805d531eab523a 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 Sun Nov 22 16:09:08 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 11:09:08 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 9 commits: users-guide: A bit of clean-up in profiling flag documentation Message-ID: <5fba8d2437065_36a73fd2f90f5f30611228@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - ecbfadef by Moritz Angermann at 2020-11-22T11:08:35-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Load.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4927ee2115139c3aa89ec90492f3c31d388467a1...ecbfadefcc6d71a6981b89ac497b1a62ab957afb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4927ee2115139c3aa89ec90492f3c31d388467a1...ecbfadefcc6d71a6981b89ac497b1a62ab957afb 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 Sun Nov 22 16:12:55 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 11:12:55 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fba8e07a4d7b_36a73fd2f1fdd7f8612650@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 793457d9 by Moritz Angermann at 2020-11-22T11:12:47-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/793457d974556a4c0c0a23ce3b0f0a2f98304c56 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/793457d974556a4c0c0a23ce3b0f0a2f98304c56 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 Sun Nov 22 16:16:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 11:16:09 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fba8ec9ac51b_36a73fd2f208ef80614062@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: b200e0ab by Moritz Angermann at 2020-11-22T11:16:03-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b200e0ab7d03a8fb8c6c6a453f394e75416f3726 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b200e0ab7d03a8fb8c6c6a453f394e75416f3726 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 Sun Nov 22 16:23:43 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 11:23:43 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 10 commits: rts: Post ticky entry counts to the eventlog Message-ID: <5fba908fe2fef_36a71579be44615626@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - f9bf2628 by John Ericson at 2020-11-22T16:22:31+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 ghc-bignum: add support for Word64#/Int64# on 64-bit arch Fix fingerprint Core generation Fix some tests Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - ef1ccf96 by John Ericson at 2020-11-22T16:22:31+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 78f84c1f by Sylvain Henry at 2020-11-22T16:22:31+00:00 Fix toArgRep - - - - - 9fc26bf9 by Sylvain Henry at 2020-11-22T16:22:31+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 7b2648e5 by John Ericson at 2020-11-22T16:22:31+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 197608ef by John Ericson at 2020-11-22T16:22:31+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - f4741fc7 by John Ericson at 2020-11-22T16:22:31+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - f35b3702 by Sylvain Henry at 2020-11-22T16:22:31+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/debugging.rst - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/profiling.rst - includes/rts/EventLogFormat.h - includes/rts/Flags.h - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a08e0a138375942d87023e7fc8b878f31a1ea26a...f35b37023a72a3665ccccbb3f2746239f38c52a2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a08e0a138375942d87023e7fc8b878f31a1ea26a...f35b37023a72a3665ccccbb3f2746239f38c52a2 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 Sun Nov 22 17:39:09 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 22 Nov 2020 12:39:09 -0500 Subject: [Git][ghc/ghc][master] Bump time submodule to 1.11.1 Message-ID: <5fbaa23d903d4_36a73fd2f208ef80623690@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 9 changed files: - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/Cabal - libraries/directory - libraries/hpc - libraries/time - libraries/unix - utils/ghc-cabal/Main.hs - utils/ghc-cabal/ghc.mk Changes: ===================================== compiler/ghc.cabal.in ===================================== @@ -63,7 +63,7 @@ Library process >= 1 && < 1.7, bytestring >= 0.9 && < 0.11, binary == 0.8.*, - time >= 1.4 && < 1.10, + time >= 1.4 && < 1.12, containers >= 0.6.2.1 && < 0.7, array >= 0.1 && < 0.6, filepath >= 1 && < 1.5, ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -63,7 +63,7 @@ Executable ghc ghci == @ProjectVersionMunged@, haskeline == 0.8.*, exceptions == 0.10.*, - time >= 1.8 && < 1.10 + time >= 1.8 && < 1.12 CPP-Options: -DHAVE_INTERNAL_INTERPRETER Other-Modules: GHCi.Leak ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 5aea8a4b8463e1ae95272e190a1022764164294f +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit cecf363bc07004ad314e0297ce34ddba05031c0e +Subproject commit 0633b48b010093f64f98ee494265436e96456aed ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit fecf0496a65c4be275d613eb0632fecd5a123b69 +Subproject commit 59e6ba02f3fa5c8f4901b4ce21777c4a9beb14b6 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit c25d6a76702b454426e149fb590da5cb69f3bd0a ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit 8abd63ea234de02d2b3cb08b5098cd06c1a728f6 +Subproject commit e079823775066bcab56b22842be6cce6e060fb9f ===================================== utils/ghc-cabal/Main.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE CPP #-} {-# OPTIONS_GHC -fno-warn-warnings-deprecations #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -28,6 +29,7 @@ import Distribution.Verbosity import qualified Distribution.InstalledPackageInfo as Installed import qualified Distribution.Simple.PackageIndex as PackageIndex import Distribution.Utils.ShortText (fromShortText) +import Distribution.Utils.Path (getSymbolicPath) import Control.Exception (bracket) import Control.Monad @@ -433,7 +435,7 @@ generate directory distdir config_args variablePrefix ++ "_MODULES = " ++ unwords mods, variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods, variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ fromShortText $ synopsis pd), - variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (hsSourceDirs bi), + variablePrefix ++ "_HS_SRC_DIRS = " ++ unwords (map getSymbolicPath $ hsSourceDirs bi), variablePrefix ++ "_DEPS = " ++ unwords deps, variablePrefix ++ "_DEP_IPIDS = " ++ unwords dep_ipids, variablePrefix ++ "_DEP_NAMES = " ++ unwords depNames, ===================================== utils/ghc-cabal/ghc.mk ===================================== @@ -38,20 +38,20 @@ $(ghc-cabal_INPLACE) : $(ghc-cabal_DIST_BINARY) | $$(dir $$@)/. "$(CP)" $< $@ # Minor hack, since we can't reuse the `hs-suffix-rules-srcdir` macro -ifneq ($(wildcard libraries/Cabal/Cabal/Distribution/Fields/Lexer.x),) +ifneq ($(wildcard libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x),) # Lexer.x exists so we have to call Alex ourselves -CABAL_LEXER_DEP := bootstrapping/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs -bootstrapping/Cabal/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/Distribution/Fields/Lexer.x - mkdir -p bootstrapping/Cabal/Distribution/Fields +bootstrapping/Cabal/src/Distribution/Fields/Lexer.hs: libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.x + mkdir -p bootstrapping/Cabal/src/Distribution/Fields $(call cmd,ALEX) $< -o $@ else -CABAL_LEXER_DEP := libraries/Cabal/Cabal/Distribution/Fields/Lexer.hs +CABAL_LEXER_DEP := libraries/Cabal/Cabal/src/Distribution/Fields/Lexer.hs endif -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*/*.hs) -$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/Distribution/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*/*.hs) +$(ghc-cabal_DIST_BINARY): $(wildcard libraries/Cabal/Cabal/src/Distribution/*.hs) # N.B. Compile with -O0 since this is not a performance-critical executable # and the Cabal takes nearly twice as long to build with -O1. See #16817. @@ -70,7 +70,7 @@ $(ghc-cabal_DIST_BINARY): $(CABAL_LEXER_DEP) utils/ghc-cabal/Main.hs $(TOUCH_DEP -odir bootstrapping \ -hidir bootstrapping \ $(CABAL_LEXER_DEP) \ - -ilibraries/Cabal/Cabal \ + -ilibraries/Cabal/Cabal/src \ -ilibraries/binary/src \ -ilibraries/filepath \ -ilibraries/hpc \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/901bc2208a115e0f8313b3aa9abc76fd05509aaa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/901bc2208a115e0f8313b3aa9abc76fd05509aaa 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 Sun Nov 22 17:39:45 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 22 Nov 2020 12:39:45 -0500 Subject: [Git][ghc/ghc][master] 5 commits: hadrian: Dump STG when ticky is enabled Message-ID: <5fbaa2611a7a1_36a73fd2f208ef806271ac@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 7 changed files: - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs Changes: ===================================== hadrian/doc/flavours.md ===================================== @@ -99,16 +99,6 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -O -O2 - - prof - -O0
-H64m - -O0
-H64m - - -O - -O2 - -O - -O - bench -O
-H64m @@ -166,13 +156,66 @@ when compiling the `compiler` library, and `hsGhc` when compiling/linking the GH -### LLVM variants +## Flavour transformers -In addition to the above, there are LLVM variants for the flavours `quick`, -`prof`, `perf` and `bench`, available by appending a `-llvm` suffix (i.e., -`quick-llvm` for the LLVM variant of `quick`). These differ only in that there -is an additional `-fllvm` flag in `hsDefault` when the stage0 compiler is GHC. -See `src/Settings/Flavours/Llvm.hs` for details. +Each of the flavours described above is intended as a starting-point for +configuring your GHC build. In addition, Hadrian supports a number of "flavour +transformers" which modify the configuration in various ways. + +These can be appended to the flavour name passed via the `--flavour` +command-line flag, separated by the `+` character. For instance, + +``` +hadrian --flavour=perf+thread_sanitizer +``` + +The supported transformers are listed below: + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + + +
Transformer nameEffect
werrorUse the `-Werror` flag for all stage1+ compilation.
debug_infoEnable production of native debugging information (via GHC/GCC's `-g3`) + during stage1+ compilations.
ticky_ghcCompile the GHC executable with Ticky-Ticky profiler support.
split_sectionsEnable section splitting for all libraries (except for the GHC + library due to the long linking times that this causes).
thread_sanitizerBuild the runtime system with ThreadSanitizer support
llvmUse GHC's LLVM backend (`-fllvm`) for all stage1+ compilation.
profiled_ghcBuild the GHC executable with cost-centre profiling support. + It is that you use this in conjunction with `no_dynamic_ghc` since + GHC does not It is support loading of profiled libraries with the + dynamically-linker.
no_dynamic_ghcLinked GHC against the statically-linked RTS. This causes GHC to + default to loading static rather than dynamic library when, + e.g., loading libraries during TemplateHaskell evaluations.
## Ways @@ -184,7 +227,6 @@ information. The following table lists ways that are built in different flavours Flavour Library ways RTS ways - Profiled GHC stage0 @@ -195,7 +237,7 @@ information. The following table lists ways that are built in different flavours stage1+ - default
perf
prof
devel1
devel2
perf-llvm
prof-llvm + default
perf
prof
devel1
devel2 vanilla vanilla
profiling
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -208,11 +250,9 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - Only in
prof
flavour - Only in
prof
flavour - quick
quick-llvm
quick-validate
quick-debug + quick
quick-validate
quick-debug vanilla vanilla
dynamic logging
debug
threaded
threadedDebug
threadedLogging @@ -223,8 +263,6 @@ information. The following table lists ways that are built in different flavours
debugDynamic
threadedDynamic
threadedDebugDynamic
loggingDynamic
threadedLoggingDynamic - No - No quickest
bench @@ -232,7 +270,5 @@ information. The following table lists ways that are built in different flavours vanilla vanilla
threaded vanilla
threaded - No - No ===================================== hadrian/hadrian.cabal ===================================== @@ -106,13 +106,10 @@ executable hadrian , Settings.Flavours.Benchmark , Settings.Flavours.Development , Settings.Flavours.GhcInGhci - , Settings.Flavours.Llvm , Settings.Flavours.Performance - , Settings.Flavours.Profiled , Settings.Flavours.Quick , Settings.Flavours.QuickCross , Settings.Flavours.Quickest - , Settings.Flavours.ThreadSanitizer , Settings.Flavours.Validate , Settings.Packages , Settings.Parser ===================================== hadrian/src/Flavour.hs ===================================== @@ -1,17 +1,28 @@ module Flavour ( Flavour (..), werror , DocTargets, DocTarget(..) + , parseFlavour -- * Flavour transformers + , flavourTransformers , addArgs , splitSections, splitSectionsIf , enableThreadSanitizer , enableDebugInfo, enableTickyGhc + , viaLlvmBackend + , enableProfiledGhc + , disableDynamicGhcPrograms ) where import Expression import Data.Set (Set) +import Data.Map (Map) +import qualified Data.Map as M import Packages +import Text.Parsec.Prim as P +import Text.Parsec.Combinator as P +import Text.Parsec.Char as P + -- Please update doc/{flavours.md, user-settings.md} when changing this file. -- | 'Flavour' is a collection of build settings that fully define a GHC build. -- Note the following type semantics: @@ -69,6 +80,58 @@ type DocTargets = Set DocTarget data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) +flavourTransformers :: Map String (Flavour -> Flavour) +flavourTransformers = M.fromList + [ "werror" =: werror + , "debug_info" =: enableDebugInfo + , "ticky_ghc" =: enableTickyGhc + , "split_sections" =: splitSections + , "thread_sanitizer" =: enableThreadSanitizer + , "llvm" =: viaLlvmBackend + , "profiled_ghc" =: enableProfiledGhc + , "no_dynamic_ghc" =: disableDynamicGhcPrograms + ] + where (=:) = (,) + +type Parser = Parsec String () + +parseFlavour :: [Flavour] -- ^ base flavours + -> Map String (Flavour -> Flavour) -- ^ modifiers + -> String + -> Either String Flavour +parseFlavour baseFlavours transformers str = + case P.runParser parser () "" str of + Left perr -> Left $ unlines $ + [ "error parsing flavour specifier: " ++ show perr + , "" + , "known flavours:" + ] ++ + [ " " ++ name f | f <- baseFlavours ] ++ + [ "" + , "known flavour transformers:" + ] ++ + [ " " ++ nm | nm <- M.keys transformers ] + Right f -> Right f + where + parser :: Parser Flavour + parser = do + base <- baseFlavour + transs <- P.many flavourTrans + return $ foldr ($) base transs + + baseFlavour :: Parser Flavour + baseFlavour = + P.choice [ f <$ P.try (P.string (name f)) + | f <- baseFlavours + ] + + flavourTrans :: Parser (Flavour -> Flavour) + flavourTrans = do + void $ P.char '+' + P.choice [ trans <$ P.try (P.string nm) + | (nm, trans) <- M.toList transformers + ] + -- | Add arguments to the 'args' of a 'Flavour'. addArgs :: Args -> Flavour -> Flavour addArgs args' fl = fl { args = args fl <> args' } @@ -96,7 +159,13 @@ enableTickyGhc = [ builder (Ghc CompileHs) ? ticky , builder (Ghc LinkHs) ? ticky ] - ticky = arg "-ticky" <> arg "-ticky-allocd" + ticky = mconcat + [ arg "-ticky" + , arg "-ticky-allocd" + -- You generally need STG dumps to interpret ticky profiles + , arg "-ddump-to-file" + , arg "-ddump-stg-final" + ] -- | Transform the input 'Flavour' so as to build with -- @-split-sections@ whenever appropriate. You can @@ -128,3 +197,17 @@ enableThreadSanitizer = addArgs $ mconcat , builder (Cabal Flags) ? arg "thread-sanitizer" , builder RunTest ? arg "--config=have_thread_sanitizer=True" ] + +-- | Use the LLVM backend in stages 1 and later. +viaLlvmBackend :: Flavour -> Flavour +viaLlvmBackend = addArgs $ notStage0 ? builder Ghc ? arg "-fllvm" + +-- | Build the GHC executable with profiling enabled. It is also recommended +-- that you use this with @'dynamicGhcPrograms' = False@ since GHC does not +-- support loading of profiled libraries with the dynamically-linker. +enableProfiledGhc :: Flavour -> Flavour +enableProfiledGhc flavour = flavour { ghcProfiled = True } + +-- | Disable 'dynamicGhcPrograms'. +disableDynamicGhcPrograms :: Flavour -> Flavour +disableDynamicGhcPrograms flavour = flavour { dynamicGhcPrograms = pure False } ===================================== hadrian/src/Settings.hs ===================================== @@ -15,13 +15,10 @@ import {-# SOURCE #-} Settings.Default import Settings.Flavours.Benchmark import Settings.Flavours.Development import Settings.Flavours.GhcInGhci -import Settings.Flavours.Llvm import Settings.Flavours.Performance -import Settings.Flavours.Profiled import Settings.Flavours.Quick import Settings.Flavours.Quickest import Settings.Flavours.QuickCross -import Settings.Flavours.ThreadSanitizer import Settings.Flavours.Validate import Control.Monad.Except @@ -54,13 +51,11 @@ stagePackages stage = do hadrianFlavours :: [Flavour] hadrianFlavours = [ benchmarkFlavour, defaultFlavour, developmentFlavour Stage1 - , developmentFlavour Stage2, performanceFlavour, profiledFlavour + , developmentFlavour Stage2, performanceFlavour , quickFlavour, quickValidateFlavour, quickDebugFlavour , quickestFlavour - , quickCrossFlavour, benchmarkLlvmFlavour - , performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour - , ghcInGhciFlavour, validateFlavour, slowValidateFlavour - , threadSanitizerFlavour ] + , quickCrossFlavour + , ghcInGhciFlavour, validateFlavour, slowValidateFlavour ] -- | This action looks up a flavour with the name given on the -- command line with @--flavour@, defaulting to 'userDefaultFlavour' @@ -75,11 +70,9 @@ flavour = do let flavours = hadrianFlavours ++ userFlavours (_settingErrs, tweak) = applySettings kvs - return $ - case filter (\fl -> name fl == flavourName) flavours of - [] -> error $ "Unknown build flavour: " ++ flavourName - [f] -> tweak f - _ -> error $ "Multiple build flavours named " ++ flavourName + case parseFlavour flavours flavourTransformers flavourName of + Left err -> fail err + Right f -> return $ tweak f -- TODO: switch to Set Package as the order of packages should not matter? -- Otherwise we have to keep remembering to sort packages from time to time. ===================================== hadrian/src/Settings/Flavours/Llvm.hs deleted ===================================== @@ -1,29 +0,0 @@ -module Settings.Flavours.Llvm ( - benchmarkLlvmFlavour, - performanceLlvmFlavour, - profiledLlvmFlavour, - quickLlvmFlavour, -) where - -import Expression -import Flavour - -import Settings.Flavours.Benchmark -import Settings.Flavours.Performance -import Settings.Flavours.Profiled -import Settings.Flavours.Quick - --- Please update doc/flavours.md when changing this file. -benchmarkLlvmFlavour, performanceLlvmFlavour, profiledLlvmFlavour, quickLlvmFlavour :: Flavour -benchmarkLlvmFlavour = mkLlvmFlavour benchmarkFlavour -performanceLlvmFlavour = mkLlvmFlavour performanceFlavour -profiledLlvmFlavour = mkLlvmFlavour profiledFlavour -quickLlvmFlavour = mkLlvmFlavour quickFlavour - --- | Turn a flavour into an LLVM flavour -mkLlvmFlavour :: Flavour -> Flavour -mkLlvmFlavour flav = flav - { name = name flav ++ "-llvm" - , args = mconcat [ args flav - , builder Ghc ? arg "-fllvm" ] - } ===================================== hadrian/src/Settings/Flavours/Profiled.hs deleted ===================================== @@ -1,22 +0,0 @@ -module Settings.Flavours.Profiled (profiledFlavour) where - -import Expression -import Flavour -import {-# SOURCE #-} Settings.Default - --- Please update doc/flavours.md when changing this file. -profiledFlavour :: Flavour -profiledFlavour = defaultFlavour - { name = "prof" - , args = defaultBuilderArgs <> profiledArgs <> defaultPackageArgs - , ghcProfiled = True - , dynamicGhcPrograms = pure False } - -profiledArgs :: Args -profiledArgs = sourceArgs SourceArgs - { hsDefault = mconcat - [ pure ["-O0", "-H64m"] - ] - , hsLibrary = notStage0 ? arg "-O" - , hsCompiler = mconcat [stage0 ? arg "-O2", notStage0 ? arg "-O"] - , hsGhc = arg "-O" } ===================================== hadrian/src/Settings/Flavours/ThreadSanitizer.hs deleted ===================================== @@ -1,9 +0,0 @@ -module Settings.Flavours.ThreadSanitizer (threadSanitizerFlavour) where - -import Flavour -import Settings.Flavours.Validate - -threadSanitizerFlavour :: Flavour -threadSanitizerFlavour = - enableThreadSanitizer (validateFlavour - { name = "thread-sanitizer" }) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/901bc2208a115e0f8313b3aa9abc76fd05509aaa...6815603f271484766425ff2e37043b78da2d073c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/901bc2208a115e0f8313b3aa9abc76fd05509aaa...6815603f271484766425ff2e37043b78da2d073c 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 Sun Nov 22 19:51:06 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 14:51:06 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 15 commits: Bump time submodule to 1.11.1 Message-ID: <5fbac12a88a98_36a7643e30063531f@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - b57e4805 by John Ericson at 2020-11-22T19:46:39+00:00 Make primop handler indentation more consistent - - - - - c32d5d0a by John Ericson at 2020-11-22T19:47:48+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 2a776711 by John Ericson at 2020-11-22T19:47:53+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - c8f40c5b by Sylvain Henry at 2020-11-22T19:47:53+00:00 Fix toArgRep - - - - - 4bbdd165 by Sylvain Henry at 2020-11-22T19:47:53+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - f8b71eac by John Ericson at 2020-11-22T19:47:53+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 8409220c by John Ericson at 2020-11-22T19:47:53+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 0558b3f6 by John Ericson at 2020-11-22T19:47:53+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 5f4a66cf by Sylvain Henry at 2020-11-22T19:47:53+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f35b37023a72a3665ccccbb3f2746239f38c52a2...5f4a66cf6b84b9fb15f40dfc3292b00b5ac46b00 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f35b37023a72a3665ccccbb3f2746239f38c52a2...5f4a66cf6b84b9fb15f40dfc3292b00b5ac46b00 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 Sun Nov 22 20:01:11 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 15:01:11 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 8 commits: Make fixed-size `Int32#` and `Int64#` Message-ID: <5fbac387510e4_36a7643e3006361f@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 3498b6cc by John Ericson at 2020-11-22T20:00:41+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 77ac38c7 by John Ericson at 2020-11-22T20:00:41+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 88d6d658 by Sylvain Henry at 2020-11-22T20:00:41+00:00 Fix toArgRep - - - - - d1d09bff by Sylvain Henry at 2020-11-22T20:00:41+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 0413b310 by John Ericson at 2020-11-22T20:00:41+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - a70af2d5 by John Ericson at 2020-11-22T20:00:41+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 95b1482c by John Ericson at 2020-11-22T20:00:41+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 61db3fbd by Sylvain Henry at 2020-11-22T20:00:41+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs - libraries/base/GHC/Float/RealFracMethods.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5f4a66cf6b84b9fb15f40dfc3292b00b5ac46b00...61db3fbded229d781aba54cc9fd501eadf447e2d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5f4a66cf6b84b9fb15f40dfc3292b00b5ac46b00...61db3fbded229d781aba54cc9fd501eadf447e2d 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 Sun Nov 22 20:32:36 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 15:32:36 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 8 commits: Make fixed-size `Int32#` and `Int64#` Message-ID: <5fbacae43b82b_36a73fd2f1fdd7f863995c@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 4ad045e8 by John Ericson at 2020-11-22T20:24:25+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - c90bf7d4 by John Ericson at 2020-11-22T20:24:26+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 795695f8 by Sylvain Henry at 2020-11-22T20:24:26+00:00 Fix toArgRep - - - - - e9e8e18e by Sylvain Henry at 2020-11-22T20:24:26+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 0b4b72d4 by John Ericson at 2020-11-22T20:24:26+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 83c69288 by John Ericson at 2020-11-22T20:24:26+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 0dc731be by John Ericson at 2020-11-22T20:24:26+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 982ce063 by Sylvain Henry at 2020-11-22T20:24:26+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs - libraries/base/GHC/Float/RealFracMethods.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61db3fbded229d781aba54cc9fd501eadf447e2d...982ce06332c3a80a7b8d2d4de661f3912fe72a09 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61db3fbded229d781aba54cc9fd501eadf447e2d...982ce06332c3a80a7b8d2d4de661f3912fe72a09 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 Sun Nov 22 21:49:48 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 16:49:48 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/facebook/ghc-8.8-unloading Message-ID: <5fbadcfce9206_36a73fd2f90f5f3064511f@gitlab.mail> Ben Gamari pushed new branch wip/facebook/ghc-8.8-unloading at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/facebook/ghc-8.8-unloading 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 Sun Nov 22 22:16:47 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 17:16:47 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere-new-float-primops] 18 commits: rts: Post ticky entry counts to the eventlog Message-ID: <5fbae34fd452a_36a73fd2f1fdd7f864595@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere-new-float-primops at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - b57e4805 by John Ericson at 2020-11-22T19:46:39+00:00 Make primop handler indentation more consistent - - - - - 4ad045e8 by John Ericson at 2020-11-22T20:24:25+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - c90bf7d4 by John Ericson at 2020-11-22T20:24:26+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 795695f8 by Sylvain Henry at 2020-11-22T20:24:26+00:00 Fix toArgRep - - - - - e9e8e18e by Sylvain Henry at 2020-11-22T20:24:26+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 0b4b72d4 by John Ericson at 2020-11-22T20:24:26+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 83c69288 by John Ericson at 2020-11-22T20:24:26+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 0dc731be by John Ericson at 2020-11-22T20:24:26+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 982ce063 by Sylvain Henry at 2020-11-22T20:24:26+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 939e0624 by John Ericson at 2020-11-22T22:16:40+00:00 WIP: Add missing floats <-> int/word 64 rule and primops - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/CPrim.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/655a4fc373d2ca2d43344a135bbec34a434e42b9...939e062466af51340a37d814142d5ceb1b4659bf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/655a4fc373d2ca2d43344a135bbec34a434e42b9...939e062466af51340a37d814142d5ceb1b4659bf 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 Sun Nov 22 22:50:27 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 17:50:27 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-64-toArgRep Message-ID: <5fbaeb33c58fd_36a71579be4464793b@gitlab.mail> John Ericson pushed new branch wip/fix-64-toArgRep at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-64-toArgRep 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 Mon Nov 23 00:26:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 22 Nov 2020 19:26:09 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] rts/linker: Move shared library loading logic into Elf.c Message-ID: <5fbb01a17e4a_36a73fd2f1d8640065387a@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: 51c8ecce by Ben Gamari at 2020-11-22T19:25:50-05:00 rts/linker: Move shared library loading logic into Elf.c - - - - - 3 changed files: - rts/Linker.c - rts/linker/Elf.c - rts/linker/Elf.h Changes: ===================================== rts/Linker.c ===================================== @@ -64,7 +64,6 @@ # include "linker/Elf.h" # include // regex is already used by dlopen() so this is OK // to use here without requiring an additional lib -# include #elif defined(OBJFORMAT_PEi386) # include "linker/PEi386.h" # include @@ -1961,141 +1960,6 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc, size, kind )); } - -# if defined(OBJFORMAT_ELF) -static int loadNativeObjCb_(struct dl_phdr_info *info, - size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { - ObjectCode* nc = (ObjectCode*) data; - - // This logic mimicks _dl_addr_inside_object from glibc - // For reference: - // int - // internal_function - // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) - // { - // int n = l->l_phnum; - // const ElfW(Addr) reladdr = addr - l->l_addr; - // - // while (--n >= 0) - // if (l->l_phdr[n].p_type == PT_LOAD - // && reladdr - l->l_phdr[n].p_vaddr >= 0 - // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) - // return 1; - // return 0; - // } - - if ((void*) info->dlpi_addr == nc->l_addr) { - int n = info->dlpi_phnum; - while (--n >= 0) { - if (info->dlpi_phdr[n].p_type == PT_LOAD) { - NativeCodeRange* ncr = - stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); - ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); - ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); - - ncr->next = nc->nc_ranges; - nc->nc_ranges = ncr; - } - } - } - return 0; -} - -static void copyErrmsg(char** errmsg_dest, char* errmsg) { - if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; - *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); - strcpy(*errmsg_dest, errmsg); -} - -// need dl_mutex -static void freeNativeCode_ELF (ObjectCode *nc) { - dlclose(nc->dlopen_handle); - - NativeCodeRange *ncr = nc->nc_ranges; - while (ncr) { - NativeCodeRange* last_ncr = ncr; - ncr = ncr->next; - stgFree(last_ncr); - } -} - -static void * loadNativeObj_ELF (pathchar *path, char **errmsg) -{ - ObjectCode* nc; - void *hdl, *retval; - - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); - - retval = NULL; - ACQUIRE_LOCK(&dl_mutex); - - /* Loading the same object multiple times will lead to chaos - * as we will have two ObjectCodes but one underlying dlopen - * handle. Fail if this happens. - */ - if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { - copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); - goto dlopen_fail; - } - - nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, true, NULL, 0); - - foreignExportsLoadingObject(nc); - hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); - foreignExportsFinishedLoadingObject(); - if (hdl == NULL) { - /* dlopen failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlopen_fail; - } - - struct link_map *map; - if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { - /* dlinfo failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlinfo_fail; - } - - nc->l_addr = (void*) map->l_addr; - nc->dlopen_handle = hdl; - hdl = NULL; // pass handle ownership to nc - - dl_iterate_phdr(loadNativeObjCb_, nc); - if (!nc->nc_ranges) { - copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); - goto dl_iterate_phdr_fail; - } - - insertOCSectionIndices(nc); - - nc->next_loaded_object = loaded_objects; - loaded_objects = nc; - - retval = nc->dlopen_handle; - -#if defined(PROFILING) - // collect any new cost centres that were defined in the loaded object. - refreshProfilingCCSs(); -#endif - - goto success; - -dl_iterate_phdr_fail: - // already have dl_mutex - freeNativeCode_ELF(nc); -dlinfo_fail: - if (hdl) dlclose(hdl); -dlopen_fail: -success: - - RELEASE_LOCK(&dl_mutex); - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); - - return retval; -} - -# endif - #define UNUSED(x) (void)(x) void * loadNativeObj (pathchar *path, char **errmsg) ===================================== rts/linker/Elf.c ===================================== @@ -15,15 +15,18 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" +#include "CheckUnload.h" #include "linker/Elf.h" #include "linker/CacheFlush.h" #include "linker/M32Alloc.h" #include "linker/SymbolExtras.h" +#include "ForeignExports.h" #include "sm/OSMem.h" #include "GetEnv.h" #include "linker/util.h" #include "linker/elf_util.h" +#include #include #include #if defined(HAVE_SYS_STAT_H) @@ -1962,6 +1965,143 @@ int ocRunInit_ELF( ObjectCode *oc ) return 1; } +/* + * Shared object loading + */ + +static int loadNativeObjCb_(struct dl_phdr_info *info, + size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { + ObjectCode* nc = (ObjectCode*) data; + + // This logic mimicks _dl_addr_inside_object from glibc + // For reference: + // int + // internal_function + // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) + // { + // int n = l->l_phnum; + // const ElfW(Addr) reladdr = addr - l->l_addr; + // + // while (--n >= 0) + // if (l->l_phdr[n].p_type == PT_LOAD + // && reladdr - l->l_phdr[n].p_vaddr >= 0 + // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) + // return 1; + // return 0; + // } + + if ((void*) info->dlpi_addr == nc->l_addr) { + int n = info->dlpi_phnum; + while (--n >= 0) { + if (info->dlpi_phdr[n].p_type == PT_LOAD) { + NativeCodeRange* ncr = + stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); + ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); + ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); + + ncr->next = nc->nc_ranges; + nc->nc_ranges = ncr; + } + } + } + return 0; +} + +static void copyErrmsg(char** errmsg_dest, char* errmsg) { + if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; + *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); + strcpy(*errmsg_dest, errmsg); +} + +// need dl_mutex +void freeNativeCode_ELF (ObjectCode *nc) { + dlclose(nc->dlopen_handle); + + NativeCodeRange *ncr = nc->nc_ranges; + while (ncr) { + NativeCodeRange* last_ncr = ncr; + ncr = ncr->next; + stgFree(last_ncr); + } +} + +void * loadNativeObj_ELF (pathchar *path, char **errmsg) +{ + ObjectCode* nc; + void *hdl, *retval; + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); + + retval = NULL; + ACQUIRE_LOCK(&dl_mutex); + + /* Loading the same object multiple times will lead to chaos + * as we will have two ObjectCodes but one underlying dlopen + * handle. Fail if this happens. + */ + if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { + copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); + goto dlopen_fail; + } + + nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, true, NULL, 0); + + foreignExportsLoadingObject(nc); + hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); + foreignExportsFinishedLoadingObject(); + if (hdl == NULL) { + /* dlopen failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlopen_fail; + } + + struct link_map *map; + if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { + /* dlinfo failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlinfo_fail; + } + + nc->l_addr = (void*) map->l_addr; + nc->dlopen_handle = hdl; + hdl = NULL; // pass handle ownership to nc + + dl_iterate_phdr(loadNativeObjCb_, nc); + if (!nc->nc_ranges) { + copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); + goto dl_iterate_phdr_fail; + } + + insertOCSectionIndices(nc); + + nc->next_loaded_object = loaded_objects; + loaded_objects = nc; + + retval = nc->dlopen_handle; + +#if defined(PROFILING) + // collect any new cost centres that were defined in the loaded object. + refreshProfilingCCSs(); +#endif + + goto success; + +dl_iterate_phdr_fail: + // already have dl_mutex + freeNativeCode_ELF(nc); +dlinfo_fail: + if (hdl) dlclose(hdl); +dlopen_fail: +success: + + RELEASE_LOCK(&dl_mutex); + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); + + return retval; +} + + /* * PowerPC & X86_64 ELF specifics */ ===================================== rts/linker/Elf.h ===================================== @@ -14,5 +14,7 @@ int ocGetNames_ELF ( ObjectCode* oc ); int ocResolve_ELF ( ObjectCode* oc ); int ocRunInit_ELF ( ObjectCode* oc ); int ocAllocateExtras_ELF ( ObjectCode *oc ); +void freeNativeCode_ELF ( ObjectCode *nc ); +void *loadNativeObj_ELF ( pathchar *path, char **errmsg ); #include "EndPrivate.h" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/51c8ecce055cda5eb30ba496889b2e730041baf7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/51c8ecce055cda5eb30ba496889b2e730041baf7 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 Mon Nov 23 03:48:43 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 22:48:43 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/primop-naming-consistency Message-ID: <5fbb311bb1100_36a71600f92c6606f6@gitlab.mail> John Ericson pushed new branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/primop-naming-consistency 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 Mon Nov 23 03:52:29 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 22:52:29 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 11 commits: Fix toArgRep to support 64-bit reps on all systems Message-ID: <5fbb31fd7cf0f_36a73fd2f208ef80661058@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: b45de34e by Sylvain Henry at 2020-11-22T22:49:08+00:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - 0ddb14aa by John Ericson at 2020-11-22T23:35:09+00:00 Merge branch 'wip/fix-64-toArgRep' into HEAD - - - - - b110ae65 by John Ericson at 2020-11-23T03:47:10+00:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - 0db851a1 by John Ericson at 2020-11-23T03:49:25+00:00 Merge branch 'wip/primop-naming-consistency' into HEAD - - - - - 6d78b1e4 by John Ericson at 2020-11-23T03:50:42+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - fee6ccad by John Ericson at 2020-11-23T03:50:43+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 42d3a399 by Sylvain Henry at 2020-11-23T03:50:43+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - a31eecdc by John Ericson at 2020-11-23T03:50:43+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 2f6e77a2 by John Ericson at 2020-11-23T03:50:43+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 09f595f5 by John Ericson at 2020-11-23T03:50:43+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 08fa3166 by Sylvain Henry at 2020-11-23T03:50:43+00:00 Fix Word64/Int64 constant-folding I've refactored literal narrow/coerce functions to make them more generic. Hence this patch incidentally implements basic support for Int8/16/32 and Word8/16/32 in Core. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs - libraries/base/GHC/Float/RealFracMethods.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/982ce06332c3a80a7b8d2d4de661f3912fe72a09...08fa3166686dd830fcaf91d9324272c519187797 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/982ce06332c3a80a7b8d2d4de661f3912fe72a09...08fa3166686dd830fcaf91d9324272c519187797 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 Mon Nov 23 04:58:01 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 22 Nov 2020 23:58:01 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] Cleanup some primop-related identifers Message-ID: <5fbb41596216a_36a71579be4466815c@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: 58a37f8b by John Ericson at 2020-11-23T04:50:12+00:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - 20 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - testsuite/tests/cmm/opt/T18141.hs - testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/ffi/should_run/PrimFFIInt16.hs - testsuite/tests/ffi/should_run/PrimFFIInt8.hs - testsuite/tests/ffi/should_run/PrimFFIWord16.hs - testsuite/tests/ffi/should_run/PrimFFIWord8.hs - testsuite/tests/primops/should_run/ArithInt16.hs - testsuite/tests/primops/should_run/ArithInt8.hs - testsuite/tests/primops/should_run/ArithWord16.hs - testsuite/tests/primops/should_run/ArithWord8.hs - testsuite/tests/primops/should_run/CmpInt16.hs - testsuite/tests/primops/should_run/CmpInt8.hs - testsuite/tests/primops/should_run/CmpWord16.hs - testsuite/tests/primops/should_run/CmpWord8.hs - testsuite/tests/primops/should_run/ShowPrim.hs - testsuite/tests/primops/should_run/ShowPrim.stdout Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -291,8 +291,8 @@ section "Int8#" primtype Int8# -primop Int8Extend "extendInt8#" GenPrimOp Int8# -> Int# -primop Int8Narrow "narrowInt8#" GenPrimOp Int# -> Int8# +primop Int8ToInt "int8ToInt#" GenPrimOp Int8# -> Int# +primop IntToInt8 "intToInt8#" GenPrimOp Int# -> Int8# primop Int8NegOp "negateInt8#" GenPrimOp Int8# -> Int8# @@ -327,13 +327,13 @@ primop Int8NeOp "neInt8#" Compare Int8# -> Int8# -> Int# ------------------------------------------------------------------------ section "Word8#" - {Operations on 8-bit unsigned integers.} + {Operations on 8-bit unsigned words.} ------------------------------------------------------------------------ primtype Word8# -primop Word8Extend "extendWord8#" GenPrimOp Word8# -> Word# -primop Word8Narrow "narrowWord8#" GenPrimOp Word# -> Word8# +primop Word8ToWord "word8ToWord#" GenPrimOp Word8# -> Word# +primop WordToWord8 "wordToWord8#" GenPrimOp Word# -> Word8# primop Word8NotOp "notWord8#" GenPrimOp Word8# -> Word8# @@ -373,8 +373,8 @@ section "Int16#" primtype Int16# -primop Int16Extend "extendInt16#" GenPrimOp Int16# -> Int# -primop Int16Narrow "narrowInt16#" GenPrimOp Int# -> Int16# +primop Int16ToInt "int16ToInt#" GenPrimOp Int16# -> Int# +primop IntToInt16 "intToInt16#" GenPrimOp Int# -> Int16# primop Int16NegOp "negateInt16#" GenPrimOp Int16# -> Int16# @@ -409,13 +409,13 @@ primop Int16NeOp "neInt16#" Compare Int16# -> Int16# -> Int# ------------------------------------------------------------------------ section "Word16#" - {Operations on 16-bit unsigned integers.} + {Operations on 16-bit unsigned words.} ------------------------------------------------------------------------ primtype Word16# -primop Word16Extend "extendWord16#" GenPrimOp Word16# -> Word# -primop Word16Narrow "narrowWord16#" GenPrimOp Word# -> Word16# +primop Word16ToWord "word16ToWord#" GenPrimOp Word16# -> Word# +primop WordToWord16 "wordToWord16#" GenPrimOp Word# -> Word16# primop Word16NotOp "notWord16#" GenPrimOp Word16# -> Word16# @@ -540,19 +540,19 @@ primop IntQuotRemOp "quotRemInt#" GenPrimOp {Rounds towards zero.} with can_fail = True -primop AndIOp "andI#" GenPrimOp Int# -> Int# -> Int# +primop IntAndOp "andI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "and".} with commutable = True -primop OrIOp "orI#" GenPrimOp Int# -> Int# -> Int# +primop IntOrOp "orI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "or".} with commutable = True -primop XorIOp "xorI#" GenPrimOp Int# -> Int# -> Int# +primop IntXorOp "xorI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "xor".} with commutable = True -primop NotIOp "notI#" GenPrimOp Int# -> Int# +primop IntNotOp "notI#" GenPrimOp Int# -> Int# {Bitwise "not", also known as the binary complement.} primop IntNegOp "negateInt#" GenPrimOp Int# -> Int# @@ -612,13 +612,13 @@ primop IntToDoubleOp "int2Double#" GenPrimOp Int# -> Double# primop WordToFloatOp "word2Float#" GenPrimOp Word# -> Float# primop WordToDoubleOp "word2Double#" GenPrimOp Word# -> Double# -primop ISllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# +primop IntSllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# {Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop ISraOp "uncheckedIShiftRA#" GenPrimOp Int# -> Int# -> Int# +primop IntSraOp "uncheckedIShiftRA#" GenPrimOp Int# -> Int# -> Int# {Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop ISrlOp "uncheckedIShiftRL#" GenPrimOp Int# -> Int# -> Int# +primop IntSrlOp "uncheckedIShiftRL#" GenPrimOp Int# -> Int# -> Int# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} @@ -678,21 +678,21 @@ primop WordQuotRem2Op "quotRemWord2#" GenPrimOp Requires that high word < divisor.} with can_fail = True -primop AndOp "and#" GenPrimOp Word# -> Word# -> Word# +primop WordAndOp "and#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop OrOp "or#" GenPrimOp Word# -> Word# -> Word# +primop WordOrOp "or#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop XorOp "xor#" GenPrimOp Word# -> Word# -> Word# +primop WordXorOp "xor#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop NotOp "not#" GenPrimOp Word# -> Word# +primop WordNotOp "not#" GenPrimOp Word# -> Word# -primop SllOp "uncheckedShiftL#" GenPrimOp Word# -> Int# -> Word# +primop WordSllOp "uncheckedShiftL#" GenPrimOp Word# -> Int# -> Word# {Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop SrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# +primop WordSrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -135,24 +135,24 @@ primOpRules nm = \case retLit zeroi , equalArgs >> retLit zeroi , equalArgs >> retLit zeroi ] - AndIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.&.)) + IntAndOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.&.)) , idempotent , zeroElem zeroi ] - OrIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) + IntOrOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) , idempotent , identityPlatform zeroi ] - XorIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) + IntXorOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) , identityPlatform zeroi , equalArgs >> retLit zeroi ] - NotIOp -> mkPrimOpRule nm 1 [ unaryLit complementOp - , inversePrimOp NotIOp ] + IntNotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp IntNotOp ] IntNegOp -> mkPrimOpRule nm 1 [ unaryLit negOp , inversePrimOp IntNegOp ] - ISllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftL) + IntSllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftL) , rightIdentityPlatform zeroi ] - ISraOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftR) + IntSraOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftR) , rightIdentityPlatform zeroi ] - ISrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt shiftRightLogical + IntSrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt shiftRightLogical , rightIdentityPlatform zeroi ] -- Word operations @@ -183,19 +183,19 @@ primOpRules nm = \case guard (l == onew platform) retLit zerow , equalArgs >> retLit zerow ] - AndOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.&.)) + WordAndOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.&.)) , idempotent , zeroElem zerow ] - OrOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) + WordOrOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) , idempotent , identityPlatform zerow ] - XorOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) + WordXorOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityPlatform zerow , equalArgs >> retLit zerow ] - NotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp - , inversePrimOp NotOp ] - SllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord (const Bits.shiftL) ] - SrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] + WordNotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp WordNotOp ] + WordSllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord (const Bits.shiftL) ] + WordSrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] -- coercions WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform wordToIntLit @@ -206,34 +206,34 @@ primOpRules nm = \case , subsumedByPrimOp Narrow8IntOp , Narrow8IntOp `subsumesPrimOp` Narrow16IntOp , Narrow8IntOp `subsumesPrimOp` Narrow32IntOp - , narrowSubsumesAnd AndIOp Narrow8IntOp 8 ] + , narrowSubsumesAnd IntAndOp Narrow8IntOp 8 ] Narrow16IntOp -> mkPrimOpRule nm 1 [ liftLit narrow16IntLit , subsumedByPrimOp Narrow8IntOp , subsumedByPrimOp Narrow16IntOp , Narrow16IntOp `subsumesPrimOp` Narrow32IntOp - , narrowSubsumesAnd AndIOp Narrow16IntOp 16 ] + , narrowSubsumesAnd IntAndOp Narrow16IntOp 16 ] Narrow32IntOp -> mkPrimOpRule nm 1 [ liftLit narrow32IntLit , subsumedByPrimOp Narrow8IntOp , subsumedByPrimOp Narrow16IntOp , subsumedByPrimOp Narrow32IntOp , removeOp32 - , narrowSubsumesAnd AndIOp Narrow32IntOp 32 ] + , narrowSubsumesAnd IntAndOp Narrow32IntOp 32 ] Narrow8WordOp -> mkPrimOpRule nm 1 [ liftLit narrow8WordLit , subsumedByPrimOp Narrow8WordOp , Narrow8WordOp `subsumesPrimOp` Narrow16WordOp , Narrow8WordOp `subsumesPrimOp` Narrow32WordOp - , narrowSubsumesAnd AndOp Narrow8WordOp 8 ] + , narrowSubsumesAnd WordAndOp Narrow8WordOp 8 ] Narrow16WordOp -> mkPrimOpRule nm 1 [ liftLit narrow16WordLit , subsumedByPrimOp Narrow8WordOp , subsumedByPrimOp Narrow16WordOp , Narrow16WordOp `subsumesPrimOp` Narrow32WordOp - , narrowSubsumesAnd AndOp Narrow16WordOp 16 ] + , narrowSubsumesAnd WordAndOp Narrow16WordOp 16 ] Narrow32WordOp -> mkPrimOpRule nm 1 [ liftLit narrow32WordLit , subsumedByPrimOp Narrow8WordOp , subsumedByPrimOp Narrow16WordOp , subsumedByPrimOp Narrow32WordOp , removeOp32 - , narrowSubsumesAnd AndOp Narrow32WordOp 32 ] + , narrowSubsumesAnd WordAndOp Narrow32WordOp 32 ] OrdOp -> mkPrimOpRule nm 1 [ liftLit charToIntLit , inversePrimOp ChrOp ] ChrOp -> mkPrimOpRule nm 1 [ do [Lit lit] <- getArgs @@ -489,8 +489,8 @@ shiftRule :: LitNumType -- Type of the result, either LitNumInt or LitNumWord -> RuleM CoreExpr -- Shifts take an Int; hence third arg of op is Int -- Used for shift primops --- ISllOp, ISraOp, ISrlOp :: Int# -> Int# -> Int# --- SllOp, SrlOp :: Word# -> Int# -> Word# +-- IntSllOp, IntSraOp, IntSrlOp :: Int# -> Int# -> Int# +-- SllOp, SrlOp :: Word# -> Int# -> Word# shiftRule lit_num_ty shift_op = do { platform <- getPlatform ; [e1, Lit (LitNumber LitNumInt shift_len)] <- getArgs @@ -792,7 +792,7 @@ transform the invalid shift into an "obviously incorrect" value. There are two cases: -- Shifting fixed-width things: the primops ISll, Sll, etc +- Shifting fixed-width things: the primops IntSll, Sll, etc These are handled by shiftRule. We are happy to shift by any amount up to wordSize but no more. @@ -1322,7 +1322,7 @@ builtinRules enableBignumRules [arg, Lit (LitNumber LitNumInt d)] <- getArgs Just n <- return $ exactLog2 d platform <- getPlatform - return $ Var (mkPrimOpId ISraOp) `App` arg `App` mkIntVal platform n + return $ Var (mkPrimOpId IntSraOp) `App` arg `App` mkIntVal platform n ], mkBasicRule modIntName 2 $ msum @@ -1332,7 +1332,7 @@ builtinRules enableBignumRules [arg, Lit (LitNumber LitNumInt d)] <- getArgs Just _ <- return $ exactLog2 d platform <- getPlatform - return $ Var (mkPrimOpId AndIOp) + return $ Var (mkPrimOpId IntAndOp) `App` arg `App` mkIntVal platform (d - 1) ] ] @@ -2306,8 +2306,8 @@ adjustDyadicRight op lit IntAddOp -> Just (\y -> y-lit ) WordSubOp -> Just (\y -> y+lit ) IntSubOp -> Just (\y -> y+lit ) - XorOp -> Just (\y -> y `xor` lit) - XorIOp -> Just (\y -> y `xor` lit) + WordXorOp -> Just (\y -> y `xor` lit) + IntXorOp -> Just (\y -> y `xor` lit) _ -> Nothing adjustDyadicLeft :: Integer -> PrimOp -> Maybe (Integer -> Integer) @@ -2318,8 +2318,8 @@ adjustDyadicLeft lit op IntAddOp -> Just (\y -> y-lit ) WordSubOp -> Just (\y -> lit-y ) IntSubOp -> Just (\y -> lit-y ) - XorOp -> Just (\y -> y `xor` lit) - XorIOp -> Just (\y -> y `xor` lit) + WordXorOp -> Just (\y -> y `xor` lit) + IntXorOp -> Just (\y -> y `xor` lit) _ -> Nothing @@ -2327,8 +2327,8 @@ adjustUnary :: PrimOp -> Maybe (Integer -> Integer) -- Given (op x) return a function 'f' s.t. f (op x) = x adjustUnary op = case op of - NotOp -> Just (\y -> complement y) - NotIOp -> Just (\y -> complement y) + WordNotOp -> Just (\y -> complement y) + IntNotOp -> Just (\y -> complement y) IntNegOp -> Just (\y -> negate y ) _ -> Nothing ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1147,12 +1147,12 @@ emitPrimOp dflags primop = case primop of AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - AndOp -> \args -> opTranslate args (mo_wordAnd platform) - OrOp -> \args -> opTranslate args (mo_wordOr platform) - XorOp -> \args -> opTranslate args (mo_wordXor platform) - NotOp -> \args -> opTranslate args (mo_wordNot platform) - SllOp -> \args -> opTranslate args (mo_wordShl platform) - SrlOp -> \args -> opTranslate args (mo_wordUShr platform) + WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) + WordOrOp -> \args -> opTranslate args (mo_wordOr platform) + WordXorOp -> \args -> opTranslate args (mo_wordXor platform) + WordNotOp -> \args -> opTranslate args (mo_wordNot platform) + WordSllOp -> \args -> opTranslate args (mo_wordShl platform) + WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) @@ -1169,13 +1169,13 @@ emitPrimOp dflags primop = case primop of IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - AndIOp -> \args -> opTranslate args (mo_wordAnd platform) - OrIOp -> \args -> opTranslate args (mo_wordOr platform) - XorIOp -> \args -> opTranslate args (mo_wordXor platform) - NotIOp -> \args -> opTranslate args (mo_wordNot platform) - ISllOp -> \args -> opTranslate args (mo_wordShl platform) - ISraOp -> \args -> opTranslate args (mo_wordSShr platform) - ISrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) + IntOrOp -> \args -> opTranslate args (mo_wordOr platform) + IntXorOp -> \args -> opTranslate args (mo_wordXor platform) + IntNotOp -> \args -> opTranslate args (mo_wordNot platform) + IntSllOp -> \args -> opTranslate args (mo_wordShl platform) + IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) + IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) -- Native word unsigned ops @@ -1195,8 +1195,8 @@ emitPrimOp dflags primop = case primop of -- Int8# signed ops - Int8Extend -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - Int8Narrow -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) + Int8ToInt -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8 -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) Int8AddOp -> \args -> opTranslate args (MO_Add W8) Int8SubOp -> \args -> opTranslate args (MO_Sub W8) @@ -1213,8 +1213,8 @@ emitPrimOp dflags primop = case primop of -- Word8# unsigned ops - Word8Extend -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - Word8Narrow -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) + Word8ToWord -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8 -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) Word8NotOp -> \args -> opTranslate args (MO_Not W8) Word8AddOp -> \args -> opTranslate args (MO_Add W8) Word8SubOp -> \args -> opTranslate args (MO_Sub W8) @@ -1231,8 +1231,8 @@ emitPrimOp dflags primop = case primop of -- Int16# signed ops - Int16Extend -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - Int16Narrow -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) + Int16ToInt -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16 -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) Int16AddOp -> \args -> opTranslate args (MO_Add W16) Int16SubOp -> \args -> opTranslate args (MO_Sub W16) @@ -1249,8 +1249,8 @@ emitPrimOp dflags primop = case primop of -- Word16# unsigned ops - Word16Extend -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - Word16Narrow -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) + Word16ToWord -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16 -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) Word16NotOp -> \args -> opTranslate args (MO_Not W16) Word16AddOp -> \args -> opTranslate args (MO_Add W16) Word16SubOp -> \args -> opTranslate args (MO_Sub W16) ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1517,8 +1517,9 @@ gfoldl_RDR, gunfold_RDR, toConstr_RDR, dataTypeOf_RDR, mkConstr_RDR, eqAddr_RDR , ltAddr_RDR , geAddr_RDR , gtAddr_RDR , leAddr_RDR , eqFloat_RDR , ltFloat_RDR , geFloat_RDR , gtFloat_RDR , leFloat_RDR , eqDouble_RDR, ltDouble_RDR, geDouble_RDR, gtDouble_RDR, leDouble_RDR, - extendWord8_RDR, extendInt8_RDR, - extendWord16_RDR, extendInt16_RDR :: RdrName + word8ToWord_RDR , int8ToInt_RDR , + word16ToWord_RDR, int16ToInt_RDR + :: RdrName gfoldl_RDR = varQual_RDR gENERICS (fsLit "gfoldl") gunfold_RDR = varQual_RDR gENERICS (fsLit "gunfold") toConstr_RDR = varQual_RDR gENERICS (fsLit "toConstr") @@ -1595,11 +1596,11 @@ leDouble_RDR = varQual_RDR gHC_PRIM (fsLit "<=##") gtDouble_RDR = varQual_RDR gHC_PRIM (fsLit ">##" ) geDouble_RDR = varQual_RDR gHC_PRIM (fsLit ">=##") -extendWord8_RDR = varQual_RDR gHC_PRIM (fsLit "extendWord8#") -extendInt8_RDR = varQual_RDR gHC_PRIM (fsLit "extendInt8#") +word8ToWord_RDR = varQual_RDR gHC_PRIM (fsLit "word8ToWord#") +int8ToInt_RDR = varQual_RDR gHC_PRIM (fsLit "int8ToInt#") -extendWord16_RDR = varQual_RDR gHC_PRIM (fsLit "extendWord16#") -extendInt16_RDR = varQual_RDR gHC_PRIM (fsLit "extendInt16#") +word16ToWord_RDR = varQual_RDR gHC_PRIM (fsLit "word16ToWord#") +int16ToInt_RDR = varQual_RDR gHC_PRIM (fsLit "int16ToInt#") {- @@ -2282,16 +2283,16 @@ boxConTbl = , (doublePrimTy, nlHsApp (nlHsVar $ getRdrName doubleDataCon)) , (int8PrimTy, nlHsApp (nlHsVar $ getRdrName intDataCon) - . nlHsApp (nlHsVar extendInt8_RDR)) + . nlHsApp (nlHsVar int8ToInt_RDR)) , (word8PrimTy, nlHsApp (nlHsVar $ getRdrName wordDataCon) - . nlHsApp (nlHsVar extendWord8_RDR)) + . nlHsApp (nlHsVar word8ToWord_RDR)) , (int16PrimTy, nlHsApp (nlHsVar $ getRdrName intDataCon) - . nlHsApp (nlHsVar extendInt16_RDR)) + . nlHsApp (nlHsVar int16ToInt_RDR)) , (word16PrimTy, nlHsApp (nlHsVar $ getRdrName wordDataCon) - . nlHsApp (nlHsVar extendWord16_RDR)) + . nlHsApp (nlHsVar word16ToWord_RDR)) ] @@ -2311,10 +2312,10 @@ postfixModTbl primConvTbl :: [(Type, String)] primConvTbl = - [ (int8PrimTy, "narrowInt8#") - , (word8PrimTy, "narrowWord8#") - , (int16PrimTy, "narrowInt16#") - , (word16PrimTy, "narrowWord16#") + [ (int8PrimTy, "intToInt8#") + , (word8PrimTy, "wordToWord8#") + , (int16PrimTy, "intToInt16#") + , (word16PrimTy, "wordToWord16#") ] litConTbl :: [(Type, LHsExpr GhcPs -> LHsExpr GhcPs)] ===================================== testsuite/tests/cmm/opt/T18141.hs ===================================== @@ -12,6 +12,6 @@ x# `divInt8#` y# ((x# `plusInt8#` one#) `quotInt8#` y#) `subInt8#` one# | otherwise = x# `quotInt8#` y# where - zero# = narrowInt8# 0# - one# = narrowInt8# 1# + zero# = intToInt8# 0# + one# = intToInt8# 1# ===================================== testsuite/tests/codeGen/should_compile/T18614.hs ===================================== @@ -8,4 +8,4 @@ import GHC.Exts main = pure () test :: Word8# -> Word8# -test x = x `plusWord8#` narrowWord8# 1## +test x = x `plusWord8#` wordToWord8# 1## ===================================== testsuite/tests/ffi/should_run/PrimFFIInt16.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_int16" main :: IO () main = do - let a = narrowInt16# 0# - b = narrowInt16# 1# - c = narrowInt16# 2# - d = narrowInt16# 3# - e = narrowInt16# 4# - f = narrowInt16# 5# - g = narrowInt16# 6# - h = narrowInt16# 7# - i = narrowInt16# 8# - j = narrowInt16# 9# - x = I# (extendInt16# (add_all_int16 a b c d e f g h i j)) + let a = intToInt16# 0# + b = intToInt16# 1# + c = intToInt16# 2# + d = intToInt16# 3# + e = intToInt16# 4# + f = intToInt16# 5# + g = intToInt16# 6# + h = intToInt16# 7# + i = intToInt16# 8# + j = intToInt16# 9# + x = I# (int16ToInt# (add_all_int16 a b c d e f g h i j)) print x ===================================== testsuite/tests/ffi/should_run/PrimFFIInt8.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_int8" main :: IO () main = do - let a = narrowInt8# 0# - b = narrowInt8# 1# - c = narrowInt8# 2# - d = narrowInt8# 3# - e = narrowInt8# 4# - f = narrowInt8# 5# - g = narrowInt8# 6# - h = narrowInt8# 7# - i = narrowInt8# 8# - j = narrowInt8# 9# - x = I# (extendInt8# (add_all_int8 a b c d e f g h i j)) + let a = intToInt8# 0# + b = intToInt8# 1# + c = intToInt8# 2# + d = intToInt8# 3# + e = intToInt8# 4# + f = intToInt8# 5# + g = intToInt8# 6# + h = intToInt8# 7# + i = intToInt8# 8# + j = intToInt8# 9# + x = I# (int8ToInt# (add_all_int8 a b c d e f g h i j)) print x ===================================== testsuite/tests/ffi/should_run/PrimFFIWord16.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_word16" main :: IO () main = do - let a = narrowWord16# 0## - b = narrowWord16# 1## - c = narrowWord16# 2## - d = narrowWord16# 3## - e = narrowWord16# 4## - f = narrowWord16# 5## - g = narrowWord16# 6## - h = narrowWord16# 7## - i = narrowWord16# 8## - j = narrowWord16# 9## - x = W# (extendWord16# (add_all_word16 a b c d e f g h i j)) + let a = wordToWord16# 0## + b = wordToWord16# 1## + c = wordToWord16# 2## + d = wordToWord16# 3## + e = wordToWord16# 4## + f = wordToWord16# 5## + g = wordToWord16# 6## + h = wordToWord16# 7## + i = wordToWord16# 8## + j = wordToWord16# 9## + x = W# (word16ToWord# (add_all_word16 a b c d e f g h i j)) print x ===================================== testsuite/tests/ffi/should_run/PrimFFIWord8.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_word8" main :: IO () main = do - let a = narrowWord8# 0## - b = narrowWord8# 1## - c = narrowWord8# 2## - d = narrowWord8# 3## - e = narrowWord8# 4## - f = narrowWord8# 5## - g = narrowWord8# 6## - h = narrowWord8# 7## - i = narrowWord8# 8## - j = narrowWord8# 9## - x = W# (extendWord8# (add_all_word8 a b c d e f g h i j)) + let a = wordToWord8# 0## + b = wordToWord8# 1## + c = wordToWord8# 2## + d = wordToWord8# 3## + e = wordToWord8# 4## + f = wordToWord8# 5## + g = wordToWord8# 6## + h = wordToWord8# 7## + i = wordToWord8# 8## + j = wordToWord8# 9## + x = W# (word8ToWord# (add_all_word8 a b c d e f g h i j)) print x ===================================== testsuite/tests/primops/should_run/ArithInt16.hs ===================================== @@ -146,32 +146,32 @@ addMany (I# a) (I# b) (I# c) (I# d) (I# e) (I# f) (I# g) (I# h) (I# i) (I# j) (I# k) (I# l) (I# m) (I# n) (I# o) (I# p) - = I# (extendInt16# int16) + = I# (int16ToInt# int16) where !int16 = addMany# - (narrowInt16# a) (narrowInt16# b) (narrowInt16# c) (narrowInt16# d) - (narrowInt16# e) (narrowInt16# f) (narrowInt16# g) (narrowInt16# h) - (narrowInt16# i) (narrowInt16# j) (narrowInt16# k) (narrowInt16# l) - (narrowInt16# m) (narrowInt16# n) (narrowInt16# o) (narrowInt16# p) + (intToInt16# a) (intToInt16# b) (intToInt16# c) (intToInt16# d) + (intToInt16# e) (intToInt16# f) (intToInt16# g) (intToInt16# h) + (intToInt16# i) (intToInt16# j) (intToInt16# k) (intToInt16# l) + (intToInt16# m) (intToInt16# n) (intToInt16# o) (intToInt16# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Int16# apply1 :: (Int16# -> Int16#) -> Int -> Int -apply1 opToTest (I# a) = I# (extendInt16# (opToTest (narrowInt16# a))) +apply1 opToTest (I# a) = I# (int16ToInt# (opToTest (intToInt16# a))) {-# NOINLINE apply1 #-} apply2 :: (Int16# -> Int16# -> Int16#) -> Int -> Int -> Int apply2 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) + let (# sa, sb #) = (# intToInt16# a, intToInt16# b #) r = opToTest sa sb - in I# (extendInt16# r) + in I# (int16ToInt# r) {-# NOINLINE apply2 #-} apply3 :: (Int16# -> Int16# -> (# Int16#, Int16# #)) -> Int -> Int -> (Int, Int) apply3 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) + let (# sa, sb #) = (# intToInt16# a, intToInt16# b #) (# ra, rb #) = opToTest sa sb - in (I# (extendInt16# ra), I# (extendInt16# rb)) + in (I# (int16ToInt# ra), I# (int16ToInt# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/ArithInt8.hs ===================================== @@ -150,32 +150,32 @@ addMany (I# a) (I# b) (I# c) (I# d) (I# e) (I# f) (I# g) (I# h) (I# i) (I# j) (I# k) (I# l) (I# m) (I# n) (I# o) (I# p) - = I# (extendInt8# int8) + = I# (int8ToInt# int8) where !int8 = addMany# - (narrowInt8# a) (narrowInt8# b) (narrowInt8# c) (narrowInt8# d) - (narrowInt8# e) (narrowInt8# f) (narrowInt8# g) (narrowInt8# h) - (narrowInt8# i) (narrowInt8# j) (narrowInt8# k) (narrowInt8# l) - (narrowInt8# m) (narrowInt8# n) (narrowInt8# o) (narrowInt8# p) + (intToInt8# a) (intToInt8# b) (intToInt8# c) (intToInt8# d) + (intToInt8# e) (intToInt8# f) (intToInt8# g) (intToInt8# h) + (intToInt8# i) (intToInt8# j) (intToInt8# k) (intToInt8# l) + (intToInt8# m) (intToInt8# n) (intToInt8# o) (intToInt8# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Int8# apply1 :: (Int8# -> Int8#) -> Int -> Int -apply1 opToTest (I# a) = I# (extendInt8# (opToTest (narrowInt8# a))) +apply1 opToTest (I# a) = I# (int8ToInt# (opToTest (intToInt8# a))) {-# NOINLINE apply1 #-} apply2 :: (Int8# -> Int8# -> Int8#) -> Int -> Int -> Int apply2 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt8# a, narrowInt8# b #) + let (# sa, sb #) = (# intToInt8# a, intToInt8# b #) r = opToTest sa sb - in I# (extendInt8# r) + in I# (int8ToInt# r) {-# NOINLINE apply2 #-} apply3 :: (Int8# -> Int8# -> (# Int8#, Int8# #)) -> Int -> Int -> (Int, Int) apply3 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt8# a, narrowInt8# b #) + let (# sa, sb #) = (# intToInt8# a, intToInt8# b #) (# ra, rb #) = opToTest sa sb - in (I# (extendInt8# ra), I# (extendInt8# rb)) + in (I# (int8ToInt# ra), I# (int8ToInt# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/ArithWord16.hs ===================================== @@ -141,34 +141,34 @@ addMany (W# a) (W# b) (W# c) (W# d) (W# e) (W# f) (W# g) (W# h) (W# i) (W# j) (W# k) (W# l) (W# m) (W# n) (W# o) (W# p) - = W# (extendWord16# word16) + = W# (word16ToWord# word16) where !word16 = addMany# - (narrowWord16# a) (narrowWord16# b) (narrowWord16# c) (narrowWord16# d) - (narrowWord16# e) (narrowWord16# f) (narrowWord16# g) (narrowWord16# h) - (narrowWord16# i) (narrowWord16# j) (narrowWord16# k) (narrowWord16# l) - (narrowWord16# m) (narrowWord16# n) (narrowWord16# o) (narrowWord16# p) + (wordToWord16# a) (wordToWord16# b) (wordToWord16# c) (wordToWord16# d) + (wordToWord16# e) (wordToWord16# f) (wordToWord16# g) (wordToWord16# h) + (wordToWord16# i) (wordToWord16# j) (wordToWord16# k) (wordToWord16# l) + (wordToWord16# m) (wordToWord16# n) (wordToWord16# o) (wordToWord16# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Word16# apply1 :: (Word16# -> Word16#) -> Word -> Word -apply1 opToTest (W# a) = W# (extendWord16# (opToTest (narrowWord16# a))) +apply1 opToTest (W# a) = W# (word16ToWord# (opToTest (wordToWord16# a))) {-# NOINLINE apply1 #-} apply2 :: (Word16# -> Word16# -> Word16#) -> Word -> Word -> Word apply2 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord16# a, narrowWord16# b #) + let (# sa, sb #) = (# wordToWord16# a, wordToWord16# b #) r = opToTest sa sb - in W# (extendWord16# r) + in W# (word16ToWord# r) {-# NOINLINE apply2 #-} apply3 :: (Word16# -> Word16# -> (# Word16#, Word16# #)) -> Word -> Word -> (Word, Word) apply3 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord16# a, narrowWord16# b #) + let (# sa, sb #) = (# wordToWord16# a, wordToWord16# b #) (# ra, rb #) = opToTest sa sb - in (W# (extendWord16# ra), W# (extendWord16# rb)) + in (W# (word16ToWord# ra), W# (word16ToWord# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/ArithWord8.hs ===================================== @@ -145,34 +145,34 @@ addMany (W# a) (W# b) (W# c) (W# d) (W# e) (W# f) (W# g) (W# h) (W# i) (W# j) (W# k) (W# l) (W# m) (W# n) (W# o) (W# p) - = W# (extendWord8# word8) + = W# (word8ToWord# word8) where !word8 = addMany# - (narrowWord8# a) (narrowWord8# b) (narrowWord8# c) (narrowWord8# d) - (narrowWord8# e) (narrowWord8# f) (narrowWord8# g) (narrowWord8# h) - (narrowWord8# i) (narrowWord8# j) (narrowWord8# k) (narrowWord8# l) - (narrowWord8# m) (narrowWord8# n) (narrowWord8# o) (narrowWord8# p) + (wordToWord8# a) (wordToWord8# b) (wordToWord8# c) (wordToWord8# d) + (wordToWord8# e) (wordToWord8# f) (wordToWord8# g) (wordToWord8# h) + (wordToWord8# i) (wordToWord8# j) (wordToWord8# k) (wordToWord8# l) + (wordToWord8# m) (wordToWord8# n) (wordToWord8# o) (wordToWord8# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Word8# apply1 :: (Word8# -> Word8#) -> Word -> Word -apply1 opToTest (W# a) = W# (extendWord8# (opToTest (narrowWord8# a))) +apply1 opToTest (W# a) = W# (word8ToWord# (opToTest (wordToWord8# a))) {-# NOINLINE apply1 #-} apply2 :: (Word8# -> Word8# -> Word8#) -> Word -> Word -> Word apply2 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord8# a, narrowWord8# b #) + let (# sa, sb #) = (# wordToWord8# a, wordToWord8# b #) r = opToTest sa sb - in W# (extendWord8# r) + in W# (word8ToWord# r) {-# NOINLINE apply2 #-} apply3 :: (Word8# -> Word8# -> (# Word8#, Word8# #)) -> Word -> Word -> (Word, Word) apply3 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord8# a, narrowWord8# b #) + let (# sa, sb #) = (# wordToWord8# a, wordToWord8# b #) (# ra, rb #) = opToTest sa sb - in (W# (extendWord8# ra), W# (extendWord8# rb)) + in (W# (word8ToWord# ra), W# (word8ToWord# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/CmpInt16.hs ===================================== @@ -16,7 +16,7 @@ data TestInt16 = T16 Int16# deriving (Eq, Ord) mkT16 :: Int -> TestInt16 -mkT16 (I# a) = T16 (narrowInt16# a) +mkT16 (I# a) = T16 (intToInt16# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/CmpInt8.hs ===================================== @@ -16,7 +16,7 @@ data TestInt8 = T8 Int8# deriving (Eq, Ord) mkT8 :: Int -> TestInt8 -mkT8 (I# a) = T8 (narrowInt8# a) +mkT8 (I# a) = T8 (intToInt8# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/CmpWord16.hs ===================================== @@ -16,7 +16,7 @@ data TestWord16 = T16 Word16# deriving (Eq, Ord) mkT16 :: Word -> TestWord16 -mkT16 (W# a) = T16 (narrowWord16# a) +mkT16 (W# a) = T16 (wordToWord16# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/CmpWord8.hs ===================================== @@ -16,7 +16,7 @@ data TestWord8 = T8 Word8# deriving (Eq, Ord) mkT8 :: Word -> TestWord8 -mkT8 (W# a) = T8 (narrowWord8# a) +mkT8 (W# a) = T8 (wordToWord8# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/ShowPrim.hs ===================================== @@ -11,10 +11,10 @@ data Test2 = Test2 Int16# Word16# deriving (Show) test1 :: Test1 -test1 = Test1 (narrowInt8# 1#) (narrowWord8# 2##) +test1 = Test1 (intToInt8# 1#) (wordToWord8# 2##) test2 :: Test2 -test2 = Test2 (narrowInt16# 1#) (narrowWord16# 2##) +test2 = Test2 (intToInt16# 1#) (wordToWord16# 2##) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/ShowPrim.stdout ===================================== @@ -1,2 +1,2 @@ -Test1 (narrowInt8# 1#) (narrowWord8# 2##) -Test2 (narrowInt16# 1#) (narrowWord16# 2##) +Test1 (intToInt8# 1#) (wordToWord8# 2##) +Test2 (intToInt16# 1#) (wordToWord16# 2##) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58a37f8bf3afaee2407ef772af711e27f6da54b0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58a37f8bf3afaee2407ef772af711e27f6da54b0 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 Mon Nov 23 08:51:14 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Mon, 23 Nov 2020 03:51:14 -0500 Subject: [Git][ghc/ghc][wip/con-info] 3 commits: Remove unused function ipe Message-ID: <5fbb780222542_36a73fd2f208ef8068839e@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 6a413e47 by Matthew Pickering at 2020-11-23T08:42:45+00:00 Remove unused function ipe - - - - - c252996f by Matthew Pickering at 2020-11-23T08:43:04+00:00 Add information about -hi mode to documentation - - - - - c5dd1cf1 by Matthew Pickering at 2020-11-23T08:51:04+00:00 Remove bang pattern to fix loop - - - - - 2 changed files: - compiler/GHC/StgToCmm/Monad.hs - docs/users_guide/profiling.rst Changes: ===================================== compiler/GHC/StgToCmm/Monad.hs ===================================== @@ -58,7 +58,7 @@ module GHC.StgToCmm.Monad ( -- more localised access to monad state CgIdInfo(..), getBinds, setBinds, - getUsedInfo, addUsedInfo, + getUsedInfo, -- out of general friendliness, we also export ... CgInfoDownwards(..), CgState(..) -- non-abstract ) where @@ -316,7 +316,7 @@ data CgState cgs_uniqs :: UniqSupply, -- | These are IDs which have an info table - cgs_used_info :: ![CmmInfoTable] + cgs_used_info :: [CmmInfoTable] } data HeapUsage -- See Note [Virtual and real heap pointers] @@ -386,9 +386,6 @@ s1 `addCodeBlocksFrom` s2 cgs_used_info = (cgs_used_info s1) ++ (cgs_used_info s2) } -addUsedInfo :: CmmInfoTable -> CgState -> CgState -addUsedInfo cl cg = cg { cgs_used_info = cl : cgs_used_info cg } - -- The heap high water mark is the larger of virtHp and hwHp. The latter is -- only records the high water marks of forked-off branches, so to find the -- heap high water mark you have to take the max of virtHp and hwHp. Remember, ===================================== docs/users_guide/profiling.rst ===================================== @@ -779,6 +779,11 @@ following RTS options select which break-down to use: Biographical profiling is described in more detail below (:ref:`biography-prof`). +.. rts-flag:: -hi + + Break down the graph by the address of the info table of a closure. This + profiling mode is intended to be used with :ghc-flag:`-finfo-table-map`. + .. rts-flag:: -l :noindex: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54eb5bbe383d3c4c22661fd789185441c9136d22...c5dd1cf18c7c1cc5f90560cf1154daf1f0f86f61 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/54eb5bbe383d3c4c22661fd789185441c9136d22...c5dd1cf18c7c1cc5f90560cf1154daf1f0f86f61 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 Mon Nov 23 08:55:37 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 23 Nov 2020 03:55:37 -0500 Subject: [Git][ghc/ghc][wip/T18857] 2 commits: Add trofis suggestion Message-ID: <5fbb7909499b8_36a73fd2f1fdd7f86890c8@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: f6ea53f7 by Moritz Angermann at 2020-11-23T08:54:50+00:00 Add trofis suggestion - - - - - ce691856 by Moritz Angermann at 2020-11-23T08:55:01+00:00 :see_no_evil: - - - - - 2 changed files: - compiler/GHC/CmmToLlvm/Base.hs - rts/linker/Elf.c Changes: ===================================== compiler/GHC/CmmToLlvm/Base.hs ===================================== @@ -484,7 +484,7 @@ ghcInternalFunctions = do mk "newSpark" w [i8Ptr, i8Ptr] where mk n ret args = do - let n' = llvmDefLabel $ fsLit n + let n' = fsLit n decl = LlvmFunctionDecl n' ExternallyVisible CC_Ccc ret FixedArgs (tysToParams args) Nothing renderLlvm $ ppLlvmFunctionDecl decl @@ -518,7 +518,10 @@ getGlobalPtr llvmLbl = do let mkGlbVar lbl ty = LMGlobalVar lbl (LMPointer ty) Private Nothing Nothing case m_ty of -- Directly reference if we have seen it already - Just ty -> return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global + Just ty -> do + if llvmLbl `elem` (map fsLit ["newSpark", "memmove", "memcpy", "memcmp", "memset"]) + then return $ mkGlbVar (llvmLbl) ty Global + else return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global -- Otherwise use a forward alias of it Nothing -> do saveAlias llvmLbl ===================================== rts/linker/Elf.c ===================================== @@ -781,7 +781,12 @@ ocGetNames_ELF ( ObjectCode* oc ) else if (!oc->imageMapped || size < getPageSize() / 3) { bool executable = kind == SECTIONKIND_CODE_OR_RODATA; m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32; - start = m32_alloc(allocator, size, 8); + // align on 16 bytes. The reason being that llvm will emit see + // paddq statements for x86_64 under optimisation and load from + // RODATA sections. Specifically .rodata.cst16. However we don't + // handle the cst part in any way what so ever, so 16 seems + // better than 8. + start = m32_alloc(allocator, size, 16); if (start == NULL) goto fail; memcpy(start, oc->image + offset, size); alloc = SECTION_M32; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5807df4f99a6d109070b591331ed9f1f90cbd4f7...ce6918560e66e9e76c12ff5b6d3e23de1aaa3014 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5807df4f99a6d109070b591331ed9f1f90cbd4f7...ce6918560e66e9e76c12ff5b6d3e23de1aaa3014 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 Mon Nov 23 09:09:24 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 23 Nov 2020 04:09:24 -0500 Subject: [Git][ghc/ghc][wip/T18857] 32 commits: Add Addr# atomic primops (#17751) Message-ID: <5fbb7c4428291_36a71600f92c69158c@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 4383078b by Ben Gamari at 2020-11-23T09:08:06+00:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - f49dfc83 by Ben Gamari at 2020-11-23T09:08:06+00:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 5dd23c5b by Ben Gamari at 2020-11-23T09:08:56+00:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' fixup ShortText & SymbolExtras - - - - - 2b47ad77 by Moritz Angermann at 2020-11-23T09:08:56+00:00 Add trofis suggestion - - - - - 189f9273 by Moritz Angermann at 2020-11-23T09:08:56+00:00 :see_no_evil: - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce6918560e66e9e76c12ff5b6d3e23de1aaa3014...189f92732b1d2195d99559f3615ddf1c9bbc55c0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce6918560e66e9e76c12ff5b6d3e23de1aaa3014...189f92732b1d2195d99559f3615ddf1c9bbc55c0 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 Mon Nov 23 10:45:53 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 23 Nov 2020 05:45:53 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18894 Message-ID: <5fbb92e16c3e3_36a73fd2f1fdd7f870295a@gitlab.mail> Sebastian Graf pushed new branch wip/T18894 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18894 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 Mon Nov 23 11:11:27 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Mon, 23 Nov 2020 06:11:27 -0500 Subject: [Git][ghc/ghc][wip/con-info] 6 commits: Profiling by info table mode (-hi) Message-ID: <5fbb98dfc134c_36a73fd2caa64b90706010@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: e23d191b by Matthew Pickering at 2020-11-23T10:38:50+00:00 Profiling by info table mode (-hi) - - - - - 82066ddd by Matthew Pickering at 2020-11-23T10:38:51+00:00 IPE? - - - - - b3839dc1 by Matthew Pickering at 2020-11-23T10:40:40+00:00 Data Con info - - - - - 57888e5d by Matthew Pickering at 2020-11-23T10:42:09+00:00 Add whereFrom# primop - - - - - 0edc43a6 by Matthew Pickering at 2020-11-23T10:42:09+00:00 Add test for whereFrom# - - - - - d23b9858 by Matthew Pickering at 2020-11-23T10:42:09+00:00 release notes - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5dd1cf18c7c1cc5f90560cf1154daf1f0f86f61...d23b9858b5306fef2e2f2371f08ca4a7c06e31de -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5dd1cf18c7c1cc5f90560cf1154daf1f0f86f61...d23b9858b5306fef2e2f2371f08ca4a7c06e31de 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 Mon Nov 23 11:13:36 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Mon, 23 Nov 2020 06:13:36 -0500 Subject: [Git][ghc/ghc][wip/con-info] 6 commits: Profiling by info table mode (-hi) Message-ID: <5fbb99606535a_36a71600f92c706769@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: ff1846e0 by Matthew Pickering at 2020-11-23T10:42:39+00:00 Profiling by info table mode (-hi) This profiling mode creates bands by the address of the info table for each closure. This provides a much more fine-grained profiling output than any of the other profiling modes. The `-hi` profiling mode does not require a profiling build. - - - - - 22256273 by Matthew Pickering at 2020-11-23T10:45:36+00:00 Add -finfo-table-map which maps info tables to source positions This new flag embeds a lookup table from the address of an info table to information about that info table. The main interface for consulting the map is the `lookupIPE` C function > InfoProvEnt * lookupIPE(StgInfoTable *info) The `InfoProvEnt` has the following structure: > typedef struct InfoProv_{ > char * table_name; > char * closure_desc; > char * ty_desc; > char * label; > char * module; > char * srcloc; > } InfoProv; > > typedef struct InfoProvEnt_ { > StgInfoTable * info; > InfoProv prov; > struct InfoProvEnt_ *link; > } InfoProvEnt; The source positions are approximated in a similar way to the source positions for DWARF debugging information. They are only approximate but in our experience provide a good enough hint about where the problem might be. It is therefore recommended to use this flag in conjunction with `-g<n>` for more accurate locations. The lookup table is also emitted into the eventlog when it is available as it is intended to be used with the `-hi` profiling mode. Using this flag will significantly increase the size of the resulting object file but only by a factor of 2-3x in our experience. - - - - - ff57d01f by Matthew Pickering at 2020-11-23T11:03:18+00:00 Add option to give each usage of a data constructor its own info table The `-fdistinct-constructor-tables` flag will generate a fresh info table for the usage of any data constructor. This is useful for debugging as now by inspecting the info table, you can determine which usage of a constructor caused that allocation rather than the old situation where the info table always mapped to the definition site of the data constructor which is useless. In conjunction with `-hi` and `-finfo-table-map` this gives a more fine grained understanding of where constructor allocations arise from in a program. - - - - - ad2e6d1e by Matthew Pickering at 2020-11-23T11:06:01+00:00 Add whereFrom and whereFrom# primop The `whereFrom` function provides a Haskell interface for using the information created by `-finfo-table-map`. Given a Haskell value, the info table address will be passed to the `lookupIPE` function in order to attempt to find the source location information for that particular closure. At the moment it's not possible to distinguish the absense of the map and a failed lookup. - - - - - 21fd02c3 by Matthew Pickering at 2020-11-23T11:10:42+00:00 Add test for whereFrom# - - - - - d3d30457 by Matthew Pickering at 2020-11-23T11:10:46+00:00 Add release notes for -hi, -finfo-table-map and -fdistinct-constructor-tables - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d23b9858b5306fef2e2f2371f08ca4a7c06e31de...d3d304578c90a96ccb3d97ac15af05b5e118fdbf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d23b9858b5306fef2e2f2371f08ca4a7c06e31de...d3d304578c90a96ccb3d97ac15af05b5e118fdbf 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 Mon Nov 23 11:18:58 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Mon, 23 Nov 2020 06:18:58 -0500 Subject: [Git][ghc/ghc][wip/con-info] 5 commits: Add -finfo-table-map which maps info tables to source positions Message-ID: <5fbb9aa22a0b6_36a71600f92c7076c4@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 4e2fe44f by Matthew Pickering at 2020-11-23T11:18:16+00:00 Add -finfo-table-map which maps info tables to source positions This new flag embeds a lookup table from the address of an info table to information about that info table. The main interface for consulting the map is the `lookupIPE` C function > InfoProvEnt * lookupIPE(StgInfoTable *info) The `InfoProvEnt` has the following structure: > typedef struct InfoProv_{ > char * table_name; > char * closure_desc; > char * ty_desc; > char * label; > char * module; > char * srcloc; > } InfoProv; > > typedef struct InfoProvEnt_ { > StgInfoTable * info; > InfoProv prov; > struct InfoProvEnt_ *link; > } InfoProvEnt; The source positions are approximated in a similar way to the source positions for DWARF debugging information. They are only approximate but in our experience provide a good enough hint about where the problem might be. It is therefore recommended to use this flag in conjunction with `-g<n>` for more accurate locations. The lookup table is also emitted into the eventlog when it is available as it is intended to be used with the `-hi` profiling mode. Using this flag will significantly increase the size of the resulting object file but only by a factor of 2-3x in our experience. - - - - - 960108eb by Matthew Pickering at 2020-11-23T11:18:42+00:00 Add option to give each usage of a data constructor its own info table The `-fdistinct-constructor-tables` flag will generate a fresh info table for the usage of any data constructor. This is useful for debugging as now by inspecting the info table, you can determine which usage of a constructor caused that allocation rather than the old situation where the info table always mapped to the definition site of the data constructor which is useless. In conjunction with `-hi` and `-finfo-table-map` this gives a more fine grained understanding of where constructor allocations arise from in a program. - - - - - e1270f24 by Matthew Pickering at 2020-11-23T11:18:44+00:00 Add whereFrom and whereFrom# primop The `whereFrom` function provides a Haskell interface for using the information created by `-finfo-table-map`. Given a Haskell value, the info table address will be passed to the `lookupIPE` function in order to attempt to find the source location information for that particular closure. At the moment it's not possible to distinguish the absense of the map and a failed lookup. - - - - - e1fb2d2b by Matthew Pickering at 2020-11-23T11:18:44+00:00 Add test for whereFrom# - - - - - 364ceb53 by Matthew Pickering at 2020-11-23T11:18:44+00:00 Add release notes for -hi, -finfo-table-map and -fdistinct-constructor-tables - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs - compiler/GHC/StgToCmm/Utils.hs - + compiler/GHC/Types/IPE.hs - compiler/GHC/Types/SrcLoc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d3d304578c90a96ccb3d97ac15af05b5e118fdbf...364ceb537a5010bb4bf2c655dbc4f0cf1f00b95b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d3d304578c90a96ccb3d97ac15af05b5e118fdbf...364ceb537a5010bb4bf2c655dbc4f0cf1f00b95b 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 Mon Nov 23 12:57:42 2020 From: gitlab at gitlab.haskell.org (Danya Rogozin) Date: Mon, 23 Nov 2020 07:57:42 -0500 Subject: [Git][ghc/ghc][wip/ghc-11342-char-kind] 26 commits: Export indexError from GHC.Ix (#18579) Message-ID: <5fbbb1c6bb6c_36a73fd2f1fdd7f871137d@gitlab.mail> Danya Rogozin pushed to branch wip/ghc-11342-char-kind at Glasgow Haskell Compiler / GHC Commits: 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 86bba1e4 by Daniel Rogozin at 2020-11-23T15:56:50+03:00 the char kind: type families, functionality, and submodule updates Co-authored-by: Rinat Stryungis <rinat.stryungis at serokell.io> Metric Decrease: T5205 Metric Increase: Naperian T13035 - - - - - 30 changed files: - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Map.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a96ae3c460fa4235b322f7715c93118f668e3db...86bba1e492614d24e0c587fd6392c41de3044180 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a96ae3c460fa4235b322f7715c93118f668e3db...86bba1e492614d24e0c587fd6392c41de3044180 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 Mon Nov 23 14:39:32 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Mon, 23 Nov 2020 09:39:32 -0500 Subject: [Git][ghc/ghc][wip/T18857] CmmToLlvm: Declare signature for memcmp Message-ID: <5fbbc9a442a1d_36a71579be44725055@gitlab.mail> Moritz Angermann pushed to branch wip/T18857 at Glasgow Haskell Compiler / GHC Commits: 170bd49d by Ben Gamari at 2020-11-23T14:38:38+00:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 6 changed files: - compiler/GHC/CmmToLlvm/Base.hs - libraries/ghc-boot/GHC/Data/ShortText.hs - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/elf_reloc_aarch64.c - testsuite/driver/testlib.py Changes: ===================================== compiler/GHC/CmmToLlvm/Base.hs ===================================== @@ -476,13 +476,15 @@ ghcInternalFunctions :: LlvmM () ghcInternalFunctions = do platform <- getPlatform let w = llvmWord platform + cint = LMInt $ widthInBits $ cIntWidth platform + mk "memcmp" cint [i8Ptr, i8Ptr, w] mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w] mk "memmove" i8Ptr [i8Ptr, i8Ptr, w] mk "memset" i8Ptr [i8Ptr, w, w] mk "newSpark" w [i8Ptr, i8Ptr] where mk n ret args = do - let n' = llvmDefLabel $ fsLit n + let n' = fsLit n decl = LlvmFunctionDecl n' ExternallyVisible CC_Ccc ret FixedArgs (tysToParams args) Nothing renderLlvm $ ppLlvmFunctionDecl decl @@ -516,7 +518,10 @@ getGlobalPtr llvmLbl = do let mkGlbVar lbl ty = LMGlobalVar lbl (LMPointer ty) Private Nothing Nothing case m_ty of -- Directly reference if we have seen it already - Just ty -> return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global + Just ty -> do + if llvmLbl `elem` (map fsLit ["newSpark", "memmove", "memcpy", "memcmp", "memset"]) + then return $ mkGlbVar (llvmLbl) ty Global + else return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global -- Otherwise use a forward alias of it Nothing -> do saveAlias llvmLbl ===================================== libraries/ghc-boot/GHC/Data/ShortText.hs ===================================== @@ -1,6 +1,22 @@ -{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-} +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} - +-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore. +-- LLVM based GHC's fail to compile memcmp ffi calls. These end up as memcmp$def in the llvm ir, however we +-- don't have any prototypes and subsequently the llvm toolchain chokes on them. Since 7fdcce6d, we use +-- ShortText for the package database. This however introduces this very module; which through inlining ends +-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in +-- the memcmp call we choke on. +-- +-- The solution thusly is to force late binding via the linker instead of inlining when comping with the +-- bootstrap compiler. This will produce a slower (slightly less optimised) stage1 compiler only. +-- +-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion. +-- +-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler, +-- we can drop this code as well. +#if GHC_STAGE < 1 +{-# OPTIONS_GHC -fignore-interface-pragmas #-} +#endif -- | -- An Unicode string for internal GHC use. Meant to replace String -- in places where being a lazy linked is not very useful and a more ===================================== rts/LinkerInternals.h ===================================== @@ -141,7 +141,7 @@ typedef struct _Segment { int n_sections; } Segment; -#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif ===================================== rts/linker/Elf.c ===================================== @@ -781,7 +781,12 @@ ocGetNames_ELF ( ObjectCode* oc ) else if (!oc->imageMapped || size < getPageSize() / 3) { bool executable = kind == SECTIONKIND_CODE_OR_RODATA; m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32; - start = m32_alloc(allocator, size, 8); + // align on 16 bytes. The reason being that llvm will emit see + // paddq statements for x86_64 under optimisation and load from + // RODATA sections. Specifically .rodata.cst16. However we don't + // handle the cst part in any way what so ever, so 16 seems + // better than 8. + start = m32_alloc(allocator, size, 16); if (start == NULL) goto fail; memcpy(start, oc->image + offset, size); alloc = SECTION_M32; @@ -940,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1867,6 +1872,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1940,6 +1946,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== testsuite/driver/testlib.py ===================================== @@ -2216,6 +2216,13 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + + # filter out nix garbage, that just keeps on showing up as errors on darwin + s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2286,6 +2293,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/170bd49df03989d2e9c976181ea6ac0856cd6853 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/170bd49df03989d2e9c976181ea6ac0856cd6853 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 Mon Nov 23 14:47:40 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Mon, 23 Nov 2020 09:47:40 -0500 Subject: [Git][ghc/ghc][wip/andreask/rts_inlining] RTS: Fix failed inlining of copy_tag. Message-ID: <5fbbcb8c14337_36a71579be447272d5@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/rts_inlining at Glasgow Haskell Compiler / GHC Commits: fc8a7f8f by Andreas Klebinger at 2020-11-23T15:44:09+01:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - 2 changed files: - includes/Rts.h - rts/sm/Evac.c Changes: ===================================== includes/Rts.h ===================================== @@ -37,12 +37,17 @@ extern "C" { #include "HsFFI.h" #include "RtsAPI.h" -// Turn off inlining when debugging - it obfuscates things +// Disencourage gcc from inlining when debugging - it obfuscates things #if defined(DEBUG) # undef STATIC_INLINE # define STATIC_INLINE static #endif +// Fine grained inlining control helpers. +#define ATTR_ALWAYS_INLINE __attribute__((always_inline)) +#define ATTR_NOINLINE __attribute__((noinline)) + + #include "rts/Types.h" #include "rts/Time.h" ===================================== rts/sm/Evac.c ===================================== @@ -58,7 +58,7 @@ #define MAX_THUNK_SELECTOR_DEPTH 16 static void eval_thunk_selector (StgClosure **q, StgSelector *p, bool); -STATIC_INLINE void evacuate_large(StgPtr p); +ATTR_NOINLINE static void evacuate_large(StgPtr p); /* ----------------------------------------------------------------------------- Allocate some space in which to copy an object. @@ -134,8 +134,13 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ -/* size is in words */ -STATIC_INLINE GNUC_ATTR_HOT void +/* size is in words + + We want to *always* inline this as often the size of the closure is static, + which allows unrolling of the copy loop. + + */ +ATTR_ALWAYS_INLINE GNUC_ATTR_HOT static inline void copy_tag(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -194,7 +199,7 @@ copy_tag(StgClosure **p, const StgInfoTable *info, } #if defined(PARALLEL_GC) && !defined(PROFILING) -STATIC_INLINE void +ATTR_ALWAYS_INLINE static inline void copy_tag_nolock(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no, StgWord tag) { @@ -231,7 +236,7 @@ copy_tag_nolock(StgClosure **p, const StgInfoTable *info, * pointer of an object, but reserve some padding after it. This is * used to optimise evacuation of TSOs. */ -static bool +ATTR_ALWAYS_INLINE static inline bool copyPart(StgClosure **p, StgClosure *src, uint32_t size_to_reserve, uint32_t size_to_copy, uint32_t gen_no) { @@ -283,7 +288,7 @@ spin: /* Copy wrappers that don't tag the closure after copying */ -STATIC_INLINE GNUC_ATTR_HOT void +ATTR_ALWAYS_INLINE GNUC_ATTR_HOT static inline void copy(StgClosure **p, const StgInfoTable *info, StgClosure *src, uint32_t size, uint32_t gen_no) { @@ -301,7 +306,7 @@ copy(StgClosure **p, const StgInfoTable *info, that has been evacuated, or unset otherwise. -------------------------------------------------------------------------- */ -static void +ATTR_NOINLINE static void evacuate_large(StgPtr p) { bdescr *bd; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc8a7f8f2aed3420dcbe2c5c25a525634779166f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fc8a7f8f2aed3420dcbe2c5c25a525634779166f 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 Mon Nov 23 14:52:05 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 23 Nov 2020 09:52:05 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18960 Message-ID: <5fbbcc951d585_36a73fd2f90f5f307278a6@gitlab.mail> Sebastian Graf pushed new branch wip/T18960 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18960 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 Mon Nov 23 15:05:08 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Mon, 23 Nov 2020 10:05:08 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 28 commits: Add Addr# atomic primops (#17751) Message-ID: <5fbbcfa49224_36a73fd2caa64b907307db@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 1865c501 by Andreas Klebinger at 2020-11-23T16:01:56+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 ------------------------- - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78d9f2ef6e1838f268dae9a2828c7d5665d5204a...1865c501e540ed6ec3c5f5be6e93d0e185defb83 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78d9f2ef6e1838f268dae9a2828c7d5665d5204a...1865c501e540ed6ec3c5f5be6e93d0e185defb83 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 Mon Nov 23 15:19:06 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Mon, 23 Nov 2020 10:19:06 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 3 commits: Use correct format specifier in rts/linker/Elf.c Message-ID: <5fbbd2eaba7ee_36a73fd2caa64b907333ee@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: 32e2a769 by Andreas Klebinger at 2020-11-23T16:18:49+01:00 Use correct format specifier in rts/linker/Elf.c - - - - - 8feeccc7 by Andreas Klebinger at 2020-11-23T16:18:49+01:00 OSMem.c: Use proper type for mbinds mask argument. StgWord has different widths on 32/64bit. So use the proper type instead. - - - - - 1966559b by Andreas Klebinger at 2020-11-23T16:18:49+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 ------------------------- - - - - - 3 changed files: - .gitlab-ci.yml - rts/linker/Elf.c - rts/posix/OSMem.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | ===================================== rts/linker/Elf.c ===================================== @@ -904,7 +904,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ASSERT(common_used <= common_size); IF_DEBUG(linker, - debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", + debugBelch("COMMON symbol, size %lu name %s allocated at %p\n", symbol->elf_sym->st_size, nm, symbol->addr)); /* Pointless to do addProddableBlock() for this area, ===================================== rts/posix/OSMem.c ===================================== @@ -364,7 +364,7 @@ void osBindMBlocksToNode( { #if HAVE_LIBNUMA int ret; - StgWord mask = 0; + unsigned long mask = 0; mask |= 1 << node; if (RtsFlags.GcFlags.numa) { ret = mbind(addr, (unsigned long)size, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1865c501e540ed6ec3c5f5be6e93d0e185defb83...1966559b15aad7db863dff47f5422aafa7086694 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1865c501e540ed6ec3c5f5be6e93d0e185defb83...1966559b15aad7db863dff47f5422aafa7086694 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 Mon Nov 23 15:33:12 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Mon, 23 Nov 2020 10:33:12 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/fixed-width-lits Message-ID: <5fbbd638a54d7_36a7643e30073797f@gitlab.mail> John Ericson pushed new branch wip/fixed-width-lits at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fixed-width-lits 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 Mon Nov 23 15:35:34 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Mon, 23 Nov 2020 10:35:34 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere-new-float-primops] 13 commits: Fix toArgRep to support 64-bit reps on all systems Message-ID: <5fbbd6c6ec80d_36a71579be447395e8@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere-new-float-primops at Glasgow Haskell Compiler / GHC Commits: b45de34e by Sylvain Henry at 2020-11-22T22:49:08+00:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - 0ddb14aa by John Ericson at 2020-11-22T23:35:09+00:00 Merge branch 'wip/fix-64-toArgRep' into HEAD - - - - - b110ae65 by John Ericson at 2020-11-23T03:47:10+00:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - 0db851a1 by John Ericson at 2020-11-23T03:49:25+00:00 Merge branch 'wip/primop-naming-consistency' into HEAD - - - - - f004001e by Sylvain Henry at 2020-11-23T15:21:42+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 9428b9c9 by John Ericson at 2020-11-23T15:30:14+00:00 Merge branch 'wip/fixed-width-lits' into HEAD - - - - - 1b901384 by John Ericson at 2020-11-23T15:30:18+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - e3041c56 by John Ericson at 2020-11-23T15:30:18+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 0055dfb7 by Sylvain Henry at 2020-11-23T15:30:18+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 844eb6c1 by John Ericson at 2020-11-23T15:30:18+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 46b9e1be by John Ericson at 2020-11-23T15:30:18+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - beba0c1e by John Ericson at 2020-11-23T15:30:18+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 8569aa12 by John Ericson at 2020-11-23T15:35:30+00:00 WIP: Add missing floats <-> int/word 64 rule and primops - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/CPrim.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/939e062466af51340a37d814142d5ceb1b4659bf...8569aa12c9e2b2c014f0096f1e52641aecebb159 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/939e062466af51340a37d814142d5ceb1b4659bf...8569aa12c9e2b2c014f0096f1e52641aecebb159 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 Mon Nov 23 15:35:56 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Mon, 23 Nov 2020 10:35:56 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 8 commits: Make proper fixed-with number literals Message-ID: <5fbbd6dcd4680_36a71600f92c7397c8@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: f004001e by Sylvain Henry at 2020-11-23T15:21:42+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 9428b9c9 by John Ericson at 2020-11-23T15:30:14+00:00 Merge branch 'wip/fixed-width-lits' into HEAD - - - - - 1b901384 by John Ericson at 2020-11-23T15:30:18+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - e3041c56 by John Ericson at 2020-11-23T15:30:18+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 0055dfb7 by Sylvain Henry at 2020-11-23T15:30:18+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 844eb6c1 by John Ericson at 2020-11-23T15:30:18+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 46b9e1be by John Ericson at 2020-11-23T15:30:18+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - beba0c1e by John Ericson at 2020-11-23T15:30:18+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs - libraries/base/GHC/Float/RealFracMethods.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Integer.hs - libraries/base/GHC/StaticPtr.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/08fa3166686dd830fcaf91d9324272c519187797...beba0c1e4a7a6a9547e5d110172dbf1403a5e0ac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/08fa3166686dd830fcaf91d9324272c519187797...beba0c1e4a7a6a9547e5d110172dbf1403a5e0ac 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 Mon Nov 23 15:37:22 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Mon, 23 Nov 2020 10:37:22 -0500 Subject: [Git][ghc/ghc][wip/fixed-width-lits] 2 commits: Cleanup some primop-related identifers Message-ID: <5fbbd73256951_36a71579be4474052e@gitlab.mail> John Ericson pushed to branch wip/fixed-width-lits at Glasgow Haskell Compiler / GHC Commits: 58a37f8b by John Ericson at 2020-11-23T04:50:12+00:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - cfb672c4 by Sylvain Henry at 2020-11-23T15:37:10+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 26 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - testsuite/driver/testlib.py - testsuite/tests/cmm/opt/T18141.hs - testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/ffi/should_run/PrimFFIInt16.hs - testsuite/tests/ffi/should_run/PrimFFIInt8.hs - testsuite/tests/ffi/should_run/PrimFFIWord16.hs - testsuite/tests/ffi/should_run/PrimFFIWord8.hs - testsuite/tests/primops/should_run/ArithInt16.hs - testsuite/tests/primops/should_run/ArithInt8.hs - testsuite/tests/primops/should_run/ArithWord16.hs - testsuite/tests/primops/should_run/ArithWord8.hs - testsuite/tests/primops/should_run/CmpInt16.hs - testsuite/tests/primops/should_run/CmpInt8.hs - testsuite/tests/primops/should_run/CmpWord16.hs - testsuite/tests/primops/should_run/CmpWord8.hs - testsuite/tests/primops/should_run/ShowPrim.hs - testsuite/tests/primops/should_run/ShowPrim.stdout Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -291,8 +291,8 @@ section "Int8#" primtype Int8# -primop Int8Extend "extendInt8#" GenPrimOp Int8# -> Int# -primop Int8Narrow "narrowInt8#" GenPrimOp Int# -> Int8# +primop Int8ToInt "int8ToInt#" GenPrimOp Int8# -> Int# +primop IntToInt8 "intToInt8#" GenPrimOp Int# -> Int8# primop Int8NegOp "negateInt8#" GenPrimOp Int8# -> Int8# @@ -327,13 +327,13 @@ primop Int8NeOp "neInt8#" Compare Int8# -> Int8# -> Int# ------------------------------------------------------------------------ section "Word8#" - {Operations on 8-bit unsigned integers.} + {Operations on 8-bit unsigned words.} ------------------------------------------------------------------------ primtype Word8# -primop Word8Extend "extendWord8#" GenPrimOp Word8# -> Word# -primop Word8Narrow "narrowWord8#" GenPrimOp Word# -> Word8# +primop Word8ToWord "word8ToWord#" GenPrimOp Word8# -> Word# +primop WordToWord8 "wordToWord8#" GenPrimOp Word# -> Word8# primop Word8NotOp "notWord8#" GenPrimOp Word8# -> Word8# @@ -373,8 +373,8 @@ section "Int16#" primtype Int16# -primop Int16Extend "extendInt16#" GenPrimOp Int16# -> Int# -primop Int16Narrow "narrowInt16#" GenPrimOp Int# -> Int16# +primop Int16ToInt "int16ToInt#" GenPrimOp Int16# -> Int# +primop IntToInt16 "intToInt16#" GenPrimOp Int# -> Int16# primop Int16NegOp "negateInt16#" GenPrimOp Int16# -> Int16# @@ -409,13 +409,13 @@ primop Int16NeOp "neInt16#" Compare Int16# -> Int16# -> Int# ------------------------------------------------------------------------ section "Word16#" - {Operations on 16-bit unsigned integers.} + {Operations on 16-bit unsigned words.} ------------------------------------------------------------------------ primtype Word16# -primop Word16Extend "extendWord16#" GenPrimOp Word16# -> Word# -primop Word16Narrow "narrowWord16#" GenPrimOp Word# -> Word16# +primop Word16ToWord "word16ToWord#" GenPrimOp Word16# -> Word# +primop WordToWord16 "wordToWord16#" GenPrimOp Word# -> Word16# primop Word16NotOp "notWord16#" GenPrimOp Word16# -> Word16# @@ -540,19 +540,19 @@ primop IntQuotRemOp "quotRemInt#" GenPrimOp {Rounds towards zero.} with can_fail = True -primop AndIOp "andI#" GenPrimOp Int# -> Int# -> Int# +primop IntAndOp "andI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "and".} with commutable = True -primop OrIOp "orI#" GenPrimOp Int# -> Int# -> Int# +primop IntOrOp "orI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "or".} with commutable = True -primop XorIOp "xorI#" GenPrimOp Int# -> Int# -> Int# +primop IntXorOp "xorI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "xor".} with commutable = True -primop NotIOp "notI#" GenPrimOp Int# -> Int# +primop IntNotOp "notI#" GenPrimOp Int# -> Int# {Bitwise "not", also known as the binary complement.} primop IntNegOp "negateInt#" GenPrimOp Int# -> Int# @@ -612,13 +612,13 @@ primop IntToDoubleOp "int2Double#" GenPrimOp Int# -> Double# primop WordToFloatOp "word2Float#" GenPrimOp Word# -> Float# primop WordToDoubleOp "word2Double#" GenPrimOp Word# -> Double# -primop ISllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# +primop IntSllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# {Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop ISraOp "uncheckedIShiftRA#" GenPrimOp Int# -> Int# -> Int# +primop IntSraOp "uncheckedIShiftRA#" GenPrimOp Int# -> Int# -> Int# {Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop ISrlOp "uncheckedIShiftRL#" GenPrimOp Int# -> Int# -> Int# +primop IntSrlOp "uncheckedIShiftRL#" GenPrimOp Int# -> Int# -> Int# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} @@ -678,21 +678,21 @@ primop WordQuotRem2Op "quotRemWord2#" GenPrimOp Requires that high word < divisor.} with can_fail = True -primop AndOp "and#" GenPrimOp Word# -> Word# -> Word# +primop WordAndOp "and#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop OrOp "or#" GenPrimOp Word# -> Word# -> Word# +primop WordOrOp "or#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop XorOp "xor#" GenPrimOp Word# -> Word# -> Word# +primop WordXorOp "xor#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop NotOp "not#" GenPrimOp Word# -> Word# +primop WordNotOp "not#" GenPrimOp Word# -> Word# -primop SllOp "uncheckedShiftL#" GenPrimOp Word# -> Int# -> Word# +primop WordSllOp "uncheckedShiftL#" GenPrimOp Word# -> Int# -> Word# {Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop SrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# +primop WordSrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} ===================================== compiler/GHC/ByteCode/Asm.hs ===================================== @@ -463,8 +463,14 @@ assembleI platform i = case i of -- LitString requires a zero-terminator when emitted literal (LitNumber nt i) = case nt of LitNumInt -> int (fromIntegral i) - LitNumWord -> int (fromIntegral i) + LitNumInt8 -> int (fromIntegral i) + LitNumInt16 -> int (fromIntegral i) + LitNumInt32 -> int (fromIntegral i) LitNumInt64 -> int64 (fromIntegral i) + LitNumWord -> int (fromIntegral i) + LitNumWord8 -> int (fromIntegral i) + LitNumWord16 -> int (fromIntegral i) + LitNumWord32 -> int (fromIntegral i) LitNumWord64 -> int64 (fromIntegral i) LitNumInteger -> panic "GHC.ByteCode.Asm.literal: LitNumInteger" LitNumNatural -> panic "GHC.ByteCode.Asm.literal: LitNumNatural" ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -76,7 +76,6 @@ import Control.Applicative ( Alternative(..) ) import Control.Monad import Data.Bits as Bits import qualified Data.ByteString as BS -import Data.Int import Data.Ratio import Data.Word import Data.Maybe (fromMaybe) @@ -135,24 +134,24 @@ primOpRules nm = \case retLit zeroi , equalArgs >> retLit zeroi , equalArgs >> retLit zeroi ] - AndIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.&.)) + IntAndOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.&.)) , idempotent , zeroElem zeroi ] - OrIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) + IntOrOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) , idempotent , identityPlatform zeroi ] - XorIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) + IntXorOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) , identityPlatform zeroi , equalArgs >> retLit zeroi ] - NotIOp -> mkPrimOpRule nm 1 [ unaryLit complementOp - , inversePrimOp NotIOp ] + IntNotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp IntNotOp ] IntNegOp -> mkPrimOpRule nm 1 [ unaryLit negOp , inversePrimOp IntNegOp ] - ISllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftL) + IntSllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftL) , rightIdentityPlatform zeroi ] - ISraOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftR) + IntSraOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftR) , rightIdentityPlatform zeroi ] - ISrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt shiftRightLogical + IntSrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt shiftRightLogical , rightIdentityPlatform zeroi ] -- Word operations @@ -183,57 +182,58 @@ primOpRules nm = \case guard (l == onew platform) retLit zerow , equalArgs >> retLit zerow ] - AndOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.&.)) + WordAndOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.&.)) , idempotent , zeroElem zerow ] - OrOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) + WordOrOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) , idempotent , identityPlatform zerow ] - XorOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) + WordXorOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityPlatform zerow , equalArgs >> retLit zerow ] - NotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp - , inversePrimOp NotOp ] - SllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord (const Bits.shiftL) ] - SrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] + WordNotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp WordNotOp ] + WordSllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord (const Bits.shiftL) ] + WordSrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] -- coercions - WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform wordToIntLit + WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumInt) , inversePrimOp IntToWordOp ] - IntToWordOp -> mkPrimOpRule nm 1 [ liftLitPlatform intToWordLit + IntToWordOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumCoerce LitNumWord) , inversePrimOp WordToIntOp ] - Narrow8IntOp -> mkPrimOpRule nm 1 [ liftLit narrow8IntLit + + Narrow8IntOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumNarrow LitNumInt8) , subsumedByPrimOp Narrow8IntOp , Narrow8IntOp `subsumesPrimOp` Narrow16IntOp , Narrow8IntOp `subsumesPrimOp` Narrow32IntOp - , narrowSubsumesAnd AndIOp Narrow8IntOp 8 ] - Narrow16IntOp -> mkPrimOpRule nm 1 [ liftLit narrow16IntLit + , narrowSubsumesAnd IntAndOp Narrow8IntOp 8 ] + Narrow16IntOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumNarrow LitNumInt16) , subsumedByPrimOp Narrow8IntOp , subsumedByPrimOp Narrow16IntOp , Narrow16IntOp `subsumesPrimOp` Narrow32IntOp - , narrowSubsumesAnd AndIOp Narrow16IntOp 16 ] - Narrow32IntOp -> mkPrimOpRule nm 1 [ liftLit narrow32IntLit + , narrowSubsumesAnd IntAndOp Narrow16IntOp 16 ] + Narrow32IntOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumNarrow LitNumInt32) , subsumedByPrimOp Narrow8IntOp , subsumedByPrimOp Narrow16IntOp , subsumedByPrimOp Narrow32IntOp , removeOp32 - , narrowSubsumesAnd AndIOp Narrow32IntOp 32 ] - Narrow8WordOp -> mkPrimOpRule nm 1 [ liftLit narrow8WordLit + , narrowSubsumesAnd IntAndOp Narrow32IntOp 32 ] + Narrow8WordOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumNarrow LitNumWord8) , subsumedByPrimOp Narrow8WordOp , Narrow8WordOp `subsumesPrimOp` Narrow16WordOp , Narrow8WordOp `subsumesPrimOp` Narrow32WordOp - , narrowSubsumesAnd AndOp Narrow8WordOp 8 ] - Narrow16WordOp -> mkPrimOpRule nm 1 [ liftLit narrow16WordLit + , narrowSubsumesAnd WordAndOp Narrow8WordOp 8 ] + Narrow16WordOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumNarrow LitNumWord16) , subsumedByPrimOp Narrow8WordOp , subsumedByPrimOp Narrow16WordOp , Narrow16WordOp `subsumesPrimOp` Narrow32WordOp - , narrowSubsumesAnd AndOp Narrow16WordOp 16 ] - Narrow32WordOp -> mkPrimOpRule nm 1 [ liftLit narrow32WordLit + , narrowSubsumesAnd WordAndOp Narrow16WordOp 16 ] + Narrow32WordOp -> mkPrimOpRule nm 1 [ liftLitPlatform (litNumNarrow LitNumWord32) , subsumedByPrimOp Narrow8WordOp , subsumedByPrimOp Narrow16WordOp , subsumedByPrimOp Narrow32WordOp , removeOp32 - , narrowSubsumesAnd AndOp Narrow32WordOp 32 ] + , narrowSubsumesAnd WordAndOp Narrow32WordOp 32 ] OrdOp -> mkPrimOpRule nm 1 [ liftLit charToIntLit , inversePrimOp ChrOp ] ChrOp -> mkPrimOpRule nm 1 [ do [Lit lit] <- getArgs @@ -489,8 +489,8 @@ shiftRule :: LitNumType -- Type of the result, either LitNumInt or LitNumWord -> RuleM CoreExpr -- Shifts take an Int; hence third arg of op is Int -- Used for shift primops --- ISllOp, ISraOp, ISrlOp :: Int# -> Int# -> Int# --- SllOp, SrlOp :: Word# -> Int# -> Word# +-- IntSllOp, IntSraOp, IntSrlOp :: Int# -> Int# -> Int# +-- SllOp, SrlOp :: Word# -> Int# -> Word# shiftRule lit_num_ty shift_op = do { platform <- getPlatform ; [e1, Lit (LitNumber LitNumInt shift_len)] <- getArgs @@ -542,7 +542,7 @@ doubleOp2 _ _ _ _ = Nothing doubleDecodeOp :: RuleOpts -> Literal -> Maybe CoreExpr doubleDecodeOp env (LitDouble ((decodeFloat . fromRational @Double) -> (m, e))) = Just $ mkCoreUbxTup [iNT64Ty, intPrimTy] - [ Lit (mkLitINT64 (roPlatform env) (toInteger m)) + [ Lit (mkLitINT64 (toInteger m)) , mkIntVal platform (toInteger e) ] where platform = roPlatform env @@ -550,7 +550,7 @@ doubleDecodeOp env (LitDouble ((decodeFloat . fromRational @Double) -> (m, e))) | platformWordSizeInBits platform < 64 = (int64PrimTy, mkLitInt64Wrap) | otherwise - = (intPrimTy , mkLitIntWrap) + = (intPrimTy , mkLitIntWrap platform) doubleDecodeOp _ _ = Nothing @@ -621,28 +621,6 @@ mkRuleFn platform Gt _ (Lit lit) | isMaxBound platform lit = Just $ falseValInt mkRuleFn platform Le _ (Lit lit) | isMaxBound platform lit = Just $ trueValInt platform mkRuleFn _ _ _ _ = Nothing -isMinBound :: Platform -> Literal -> Bool -isMinBound _ (LitChar c) = c == minBound -isMinBound platform (LitNumber nt i) = case nt of - LitNumInt -> i == platformMinInt platform - LitNumInt64 -> i == toInteger (minBound :: Int64) - LitNumWord -> i == 0 - LitNumWord64 -> i == 0 - LitNumNatural -> i == 0 - LitNumInteger -> False -isMinBound _ _ = False - -isMaxBound :: Platform -> Literal -> Bool -isMaxBound _ (LitChar c) = c == maxBound -isMaxBound platform (LitNumber nt i) = case nt of - LitNumInt -> i == platformMaxInt platform - LitNumInt64 -> i == toInteger (maxBound :: Int64) - LitNumWord -> i == platformMaxWord platform - LitNumWord64 -> i == toInteger (maxBound :: Word64) - LitNumNatural -> False - LitNumInteger -> False -isMaxBound _ _ = False - -- | Create an Int literal expression while ensuring the given Integer is in the -- target Int range intResult :: Platform -> Integer -> Maybe CoreExpr @@ -792,7 +770,7 @@ transform the invalid shift into an "obviously incorrect" value. There are two cases: -- Shifting fixed-width things: the primops ISll, Sll, etc +- Shifting fixed-width things: the primops IntSll, Sll, etc These are handled by shiftRule. We are happy to shift by any amount up to wordSize but no more. @@ -1322,7 +1300,7 @@ builtinRules enableBignumRules [arg, Lit (LitNumber LitNumInt d)] <- getArgs Just n <- return $ exactLog2 d platform <- getPlatform - return $ Var (mkPrimOpId ISraOp) `App` arg `App` mkIntVal platform n + return $ Var (mkPrimOpId IntSraOp) `App` arg `App` mkIntVal platform n ], mkBasicRule modIntName 2 $ msum @@ -1332,7 +1310,7 @@ builtinRules enableBignumRules [arg, Lit (LitNumber LitNumInt d)] <- getArgs Just _ <- return $ exactLog2 d platform <- getPlatform - return $ Var (mkPrimOpId AndIOp) + return $ Var (mkPrimOpId IntAndOp) `App` arg `App` mkIntVal platform (d - 1) ] ] @@ -2306,8 +2284,8 @@ adjustDyadicRight op lit IntAddOp -> Just (\y -> y-lit ) WordSubOp -> Just (\y -> y+lit ) IntSubOp -> Just (\y -> y+lit ) - XorOp -> Just (\y -> y `xor` lit) - XorIOp -> Just (\y -> y `xor` lit) + WordXorOp -> Just (\y -> y `xor` lit) + IntXorOp -> Just (\y -> y `xor` lit) _ -> Nothing adjustDyadicLeft :: Integer -> PrimOp -> Maybe (Integer -> Integer) @@ -2318,8 +2296,8 @@ adjustDyadicLeft lit op IntAddOp -> Just (\y -> y-lit ) WordSubOp -> Just (\y -> lit-y ) IntSubOp -> Just (\y -> lit-y ) - XorOp -> Just (\y -> y `xor` lit) - XorIOp -> Just (\y -> y `xor` lit) + WordXorOp -> Just (\y -> y `xor` lit) + IntXorOp -> Just (\y -> y `xor` lit) _ -> Nothing @@ -2327,8 +2305,8 @@ adjustUnary :: PrimOp -> Maybe (Integer -> Integer) -- Given (op x) return a function 'f' s.t. f (op x) = x adjustUnary op = case op of - NotOp -> Just (\y -> complement y) - NotIOp -> Just (\y -> complement y) + WordNotOp -> Just (\y -> complement y) + IntNotOp -> Just (\y -> complement y) IntNegOp -> Just (\y -> negate y ) _ -> Nothing ===================================== compiler/GHC/CoreToByteCode.hs ===================================== @@ -1636,8 +1636,14 @@ pushAtom _ _ (AnnLit lit) = do LitRubbish -> code N LitNumber nt _ -> case nt of LitNumInt -> code N - LitNumWord -> code N + LitNumInt8 -> code N + LitNumInt16 -> code N + LitNumInt32 -> code N LitNumInt64 -> code L + LitNumWord -> code N + LitNumWord8 -> code N + LitNumWord16 -> code N + LitNumWord32 -> code N LitNumWord64 -> code L -- No LitInteger's or LitNatural's should be left by the time this is -- called. CorePrep should have converted them all to a real core ===================================== compiler/GHC/HsToCore/Match/Literal.hs ===================================== @@ -97,8 +97,8 @@ dsLit l = do HsCharPrim _ c -> return (Lit (LitChar c)) HsIntPrim _ i -> return (Lit (mkLitIntWrap platform i)) HsWordPrim _ w -> return (Lit (mkLitWordWrap platform w)) - HsInt64Prim _ i -> return (Lit (mkLitInt64Wrap platform i)) - HsWord64Prim _ w -> return (Lit (mkLitWord64Wrap platform w)) + HsInt64Prim _ i -> return (Lit (mkLitInt64Wrap i)) + HsWord64Prim _ w -> return (Lit (mkLitWord64Wrap w)) HsFloatPrim _ f -> return (Lit (LitFloat (fl_value f))) HsDoublePrim _ d -> return (Lit (LitDouble (fl_value d))) HsChar _ c -> return (mkCharExpr c) @@ -514,8 +514,8 @@ hsLitKey :: Platform -> HsLit GhcTc -> Literal -- HsLit does not. hsLitKey platform (HsIntPrim _ i) = mkLitIntWrap platform i hsLitKey platform (HsWordPrim _ w) = mkLitWordWrap platform w -hsLitKey platform (HsInt64Prim _ i) = mkLitInt64Wrap platform i -hsLitKey platform (HsWord64Prim _ w) = mkLitWord64Wrap platform w +hsLitKey _ (HsInt64Prim _ i) = mkLitInt64Wrap i +hsLitKey _ (HsWord64Prim _ w) = mkLitWord64Wrap w hsLitKey _ (HsCharPrim _ c) = mkLitChar c hsLitKey _ (HsFloatPrim _ f) = mkLitFloat (fl_value f) hsLitKey _ (HsDoublePrim _ d) = mkLitDouble (fl_value d) ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1147,12 +1147,12 @@ emitPrimOp dflags primop = case primop of AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - AndOp -> \args -> opTranslate args (mo_wordAnd platform) - OrOp -> \args -> opTranslate args (mo_wordOr platform) - XorOp -> \args -> opTranslate args (mo_wordXor platform) - NotOp -> \args -> opTranslate args (mo_wordNot platform) - SllOp -> \args -> opTranslate args (mo_wordShl platform) - SrlOp -> \args -> opTranslate args (mo_wordUShr platform) + WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) + WordOrOp -> \args -> opTranslate args (mo_wordOr platform) + WordXorOp -> \args -> opTranslate args (mo_wordXor platform) + WordNotOp -> \args -> opTranslate args (mo_wordNot platform) + WordSllOp -> \args -> opTranslate args (mo_wordShl platform) + WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) @@ -1169,13 +1169,13 @@ emitPrimOp dflags primop = case primop of IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - AndIOp -> \args -> opTranslate args (mo_wordAnd platform) - OrIOp -> \args -> opTranslate args (mo_wordOr platform) - XorIOp -> \args -> opTranslate args (mo_wordXor platform) - NotIOp -> \args -> opTranslate args (mo_wordNot platform) - ISllOp -> \args -> opTranslate args (mo_wordShl platform) - ISraOp -> \args -> opTranslate args (mo_wordSShr platform) - ISrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) + IntOrOp -> \args -> opTranslate args (mo_wordOr platform) + IntXorOp -> \args -> opTranslate args (mo_wordXor platform) + IntNotOp -> \args -> opTranslate args (mo_wordNot platform) + IntSllOp -> \args -> opTranslate args (mo_wordShl platform) + IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) + IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) -- Native word unsigned ops @@ -1195,8 +1195,8 @@ emitPrimOp dflags primop = case primop of -- Int8# signed ops - Int8Extend -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - Int8Narrow -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) + Int8ToInt -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8 -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) Int8AddOp -> \args -> opTranslate args (MO_Add W8) Int8SubOp -> \args -> opTranslate args (MO_Sub W8) @@ -1213,8 +1213,8 @@ emitPrimOp dflags primop = case primop of -- Word8# unsigned ops - Word8Extend -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - Word8Narrow -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) + Word8ToWord -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8 -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) Word8NotOp -> \args -> opTranslate args (MO_Not W8) Word8AddOp -> \args -> opTranslate args (MO_Add W8) Word8SubOp -> \args -> opTranslate args (MO_Sub W8) @@ -1231,8 +1231,8 @@ emitPrimOp dflags primop = case primop of -- Int16# signed ops - Int16Extend -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - Int16Narrow -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) + Int16ToInt -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16 -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) Int16AddOp -> \args -> opTranslate args (MO_Add W16) Int16SubOp -> \args -> opTranslate args (MO_Sub W16) @@ -1249,8 +1249,8 @@ emitPrimOp dflags primop = case primop of -- Word16# unsigned ops - Word16Extend -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - Word16Narrow -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) + Word16ToWord -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16 -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) Word16NotOp -> \args -> opTranslate args (MO_Not W16) Word16AddOp -> \args -> opTranslate args (MO_Add W16) Word16SubOp -> \args -> opTranslate args (MO_Sub W16) ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1517,8 +1517,9 @@ gfoldl_RDR, gunfold_RDR, toConstr_RDR, dataTypeOf_RDR, mkConstr_RDR, eqAddr_RDR , ltAddr_RDR , geAddr_RDR , gtAddr_RDR , leAddr_RDR , eqFloat_RDR , ltFloat_RDR , geFloat_RDR , gtFloat_RDR , leFloat_RDR , eqDouble_RDR, ltDouble_RDR, geDouble_RDR, gtDouble_RDR, leDouble_RDR, - extendWord8_RDR, extendInt8_RDR, - extendWord16_RDR, extendInt16_RDR :: RdrName + word8ToWord_RDR , int8ToInt_RDR , + word16ToWord_RDR, int16ToInt_RDR + :: RdrName gfoldl_RDR = varQual_RDR gENERICS (fsLit "gfoldl") gunfold_RDR = varQual_RDR gENERICS (fsLit "gunfold") toConstr_RDR = varQual_RDR gENERICS (fsLit "toConstr") @@ -1595,11 +1596,11 @@ leDouble_RDR = varQual_RDR gHC_PRIM (fsLit "<=##") gtDouble_RDR = varQual_RDR gHC_PRIM (fsLit ">##" ) geDouble_RDR = varQual_RDR gHC_PRIM (fsLit ">=##") -extendWord8_RDR = varQual_RDR gHC_PRIM (fsLit "extendWord8#") -extendInt8_RDR = varQual_RDR gHC_PRIM (fsLit "extendInt8#") +word8ToWord_RDR = varQual_RDR gHC_PRIM (fsLit "word8ToWord#") +int8ToInt_RDR = varQual_RDR gHC_PRIM (fsLit "int8ToInt#") -extendWord16_RDR = varQual_RDR gHC_PRIM (fsLit "extendWord16#") -extendInt16_RDR = varQual_RDR gHC_PRIM (fsLit "extendInt16#") +word16ToWord_RDR = varQual_RDR gHC_PRIM (fsLit "word16ToWord#") +int16ToInt_RDR = varQual_RDR gHC_PRIM (fsLit "int16ToInt#") {- @@ -2282,16 +2283,16 @@ boxConTbl = , (doublePrimTy, nlHsApp (nlHsVar $ getRdrName doubleDataCon)) , (int8PrimTy, nlHsApp (nlHsVar $ getRdrName intDataCon) - . nlHsApp (nlHsVar extendInt8_RDR)) + . nlHsApp (nlHsVar int8ToInt_RDR)) , (word8PrimTy, nlHsApp (nlHsVar $ getRdrName wordDataCon) - . nlHsApp (nlHsVar extendWord8_RDR)) + . nlHsApp (nlHsVar word8ToWord_RDR)) , (int16PrimTy, nlHsApp (nlHsVar $ getRdrName intDataCon) - . nlHsApp (nlHsVar extendInt16_RDR)) + . nlHsApp (nlHsVar int16ToInt_RDR)) , (word16PrimTy, nlHsApp (nlHsVar $ getRdrName wordDataCon) - . nlHsApp (nlHsVar extendWord16_RDR)) + . nlHsApp (nlHsVar word16ToWord_RDR)) ] @@ -2311,10 +2312,10 @@ postfixModTbl primConvTbl :: [(Type, String)] primConvTbl = - [ (int8PrimTy, "narrowInt8#") - , (word8PrimTy, "narrowWord8#") - , (int16PrimTy, "narrowInt16#") - , (word16PrimTy, "narrowWord16#") + [ (int8PrimTy, "intToInt8#") + , (word8PrimTy, "wordToWord8#") + , (int16PrimTy, "intToInt16#") + , (word16PrimTy, "wordToWord16#") ] litConTbl :: [(Type, LHsExpr GhcPs -> LHsExpr GhcPs)] ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -2,12 +2,15 @@ (c) The University of Glasgow 2006 (c) The GRASP/AQUA Project, Glasgow University, 1998 -\section[Literal]{@Literal@: literals} -} {-# LANGUAGE CPP, DeriveDataTypeable, ScopedTypeVariables #-} +{-# LANGUAGE TypeApplications #-} +{-# LANGUAGE AllowAmbiguousTypes #-} + {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} +-- | Core literals module GHC.Types.Literal ( -- * Main data type @@ -30,6 +33,11 @@ module GHC.Types.Literal , pprLiteral , litNumIsSigned , litNumCheckRange + , litNumWrap + , litNumCoerce + , litNumNarrow + , isMinBound + , isMaxBound -- ** Predicates on Literals and their contents , litIsDupable, litIsTrivial, litIsLifted @@ -39,10 +47,6 @@ module GHC.Types.Literal , litValue, mapLitValue -- ** Coercions - , wordToIntLit, intToWordLit - , narrowLit - , narrow8IntLit, narrow16IntLit, narrow32IntLit - , narrow8WordLit, narrow16WordLit, narrow32WordLit , charToIntLit, intToCharLit , floatToIntLit, intToFloatLit, doubleToIntLit, intToDoubleLit , nullAddrLit, rubbishLit, floatToDoubleLit, doubleToFloatLit @@ -72,7 +76,6 @@ import Data.Int import Data.Word import Data.Char import Data.Data ( Data ) -import Data.Proxy import Numeric ( fromRat ) {- @@ -152,8 +155,14 @@ data LitNumType = LitNumInteger -- ^ @Integer@ (see Note [BigNum literals]) | LitNumNatural -- ^ @Natural@ (see Note [BigNum literals]) | LitNumInt -- ^ @Int#@ - according to target machine + | LitNumInt8 -- ^ @Int8#@ - exactly 8 bits + | LitNumInt16 -- ^ @Int16#@ - exactly 16 bits + | LitNumInt32 -- ^ @Int32#@ - exactly 32 bits | LitNumInt64 -- ^ @Int64#@ - exactly 64 bits | LitNumWord -- ^ @Word#@ - according to target machine + | LitNumWord8 -- ^ @Word8#@ - exactly 8 bits + | LitNumWord16 -- ^ @Word16#@ - exactly 16 bits + | LitNumWord32 -- ^ @Word32#@ - exactly 32 bits | LitNumWord64 -- ^ @Word64#@ - exactly 64 bits deriving (Data,Enum,Eq,Ord) @@ -163,8 +172,14 @@ litNumIsSigned nt = case nt of LitNumInteger -> True LitNumNatural -> False LitNumInt -> True + LitNumInt8 -> True + LitNumInt16 -> True + LitNumInt32 -> True LitNumInt64 -> True LitNumWord -> False + LitNumWord8 -> False + LitNumWord16 -> False + LitNumWord32 -> False LitNumWord64 -> False {- @@ -281,32 +296,65 @@ doesn't yield a warning. Instead we simply squash the value into the *target* Int/Word range. -} --- | Wrap a literal number according to its type -wrapLitNumber :: Platform -> Literal -> Literal -wrapLitNumber platform v@(LitNumber nt i) = case nt of +-- | Make a literal number using wrapping semantics if the value is out of +-- bound. +mkLitNumberWrap :: Platform -> LitNumType -> Integer -> Literal +mkLitNumberWrap platform nt i = case nt of LitNumInt -> case platformWordSize platform of - PW4 -> LitNumber nt (toInteger (fromIntegral i :: Int32)) - PW8 -> LitNumber nt (toInteger (fromIntegral i :: Int64)) + PW4 -> wrap @Int32 + PW8 -> wrap @Int64 LitNumWord -> case platformWordSize platform of - PW4 -> LitNumber nt (toInteger (fromIntegral i :: Word32)) - PW8 -> LitNumber nt (toInteger (fromIntegral i :: Word64)) - LitNumInt64 -> LitNumber nt (toInteger (fromIntegral i :: Int64)) - LitNumWord64 -> LitNumber nt (toInteger (fromIntegral i :: Word64)) - LitNumInteger -> v - LitNumNatural -> v -wrapLitNumber _ x = x + PW4 -> wrap @Word32 + PW8 -> wrap @Word64 + LitNumInt8 -> wrap @Int8 + LitNumInt16 -> wrap @Int16 + LitNumInt32 -> wrap @Int32 + LitNumInt64 -> wrap @Int64 + LitNumWord8 -> wrap @Word8 + LitNumWord16 -> wrap @Word16 + LitNumWord32 -> wrap @Word32 + LitNumWord64 -> wrap @Word64 + LitNumInteger -> LitNumber nt i + LitNumNatural + | i < 0 -> panic "mkLitNumberWrap: trying to create a negative Natural" + | otherwise -> LitNumber nt i + where + wrap :: forall a. (Integral a, Num a) => Literal + wrap = LitNumber nt (toInteger (fromIntegral i :: a)) + +-- | Wrap a literal number according to its type using wrapping semantics. +litNumWrap :: Platform -> Literal -> Literal +litNumWrap platform (LitNumber nt i) = mkLitNumberWrap platform nt i +litNumWrap _ l = pprPanic "litNumWrap" (ppr l) + +-- | Coerce a literal number into another using wrapping semantics. +litNumCoerce :: LitNumType -> Platform -> Literal -> Literal +litNumCoerce pt platform (LitNumber _nt i) = mkLitNumberWrap platform pt i +litNumCoerce _ _ l = pprPanic "litNumWrapCoerce: not a number" (ppr l) + +-- | Narrow a literal number by converting it into another number type and then +-- converting it back to its original type. +litNumNarrow :: LitNumType -> Platform -> Literal -> Literal +litNumNarrow pt platform (LitNumber nt i) + = case mkLitNumberWrap platform pt i of + LitNumber _ j -> mkLitNumberWrap platform nt j + l -> pprPanic "litNumNarrow: got invalid literal" (ppr l) +litNumNarrow _ _ l = pprPanic "litNumNarrow: invalid literal" (ppr l) --- | Create a numeric 'Literal' of the given type -mkLitNumberWrap :: Platform -> LitNumType -> Integer -> Literal -mkLitNumberWrap platform nt i = wrapLitNumber platform (LitNumber nt i) -- | Check that a given number is in the range of a numeric literal litNumCheckRange :: Platform -> LitNumType -> Integer -> Bool litNumCheckRange platform nt i = case nt of LitNumInt -> platformInIntRange platform i LitNumWord -> platformInWordRange platform i - LitNumInt64 -> inInt64Range i - LitNumWord64 -> inWord64Range i + LitNumInt8 -> inBoundedRange @Int8 i + LitNumInt16 -> inBoundedRange @Int16 i + LitNumInt32 -> inBoundedRange @Int32 i + LitNumInt64 -> inBoundedRange @Int64 i + LitNumWord8 -> inBoundedRange @Word8 i + LitNumWord16 -> inBoundedRange @Word16 i + LitNumWord32 -> inBoundedRange @Word32 i + LitNumWord64 -> inBoundedRange @Word64 i LitNumNatural -> i >= 0 LitNumInteger -> True @@ -325,7 +373,7 @@ mkLitInt platform x = ASSERT2( platformInIntRange platform x, integer x ) -- If the argument is out of the (target-dependent) range, it is wrapped. -- See Note [Word/Int underflow/overflow] mkLitIntWrap :: Platform -> Integer -> Literal -mkLitIntWrap platform i = wrapLitNumber platform $ mkLitIntUnchecked i +mkLitIntWrap platform i = mkLitNumberWrap platform LitNumInt i -- | Creates a 'Literal' of type @Int#@ without checking its range. mkLitIntUnchecked :: Integer -> Literal @@ -349,7 +397,7 @@ mkLitWord platform x = ASSERT2( platformInWordRange platform x, integer x ) -- If the argument is out of the (target-dependent) range, it is wrapped. -- See Note [Word/Int underflow/overflow] mkLitWordWrap :: Platform -> Integer -> Literal -mkLitWordWrap platform i = wrapLitNumber platform $ mkLitWordUnchecked i +mkLitWordWrap platform i = mkLitNumberWrap platform LitNumWord i -- | Creates a 'Literal' of type @Word#@ without checking its range. mkLitWordUnchecked :: Integer -> Literal @@ -366,12 +414,12 @@ mkLitWordWrapC platform i = (n, i /= i') -- | Creates a 'Literal' of type @Int64#@ mkLitInt64 :: Integer -> Literal -mkLitInt64 x = ASSERT2( inInt64Range x, integer x ) (mkLitInt64Unchecked x) +mkLitInt64 x = ASSERT2( inBoundedRange @Int64 x, integer x ) (mkLitInt64Unchecked x) -- | Creates a 'Literal' of type @Int64#@. -- If the argument is out of the range, it is wrapped. -mkLitInt64Wrap :: Platform -> Integer -> Literal -mkLitInt64Wrap platform i = wrapLitNumber platform $ mkLitInt64Unchecked i +mkLitInt64Wrap :: Integer -> Literal +mkLitInt64Wrap i = LitNumber LitNumInt64 (toInteger (fromIntegral i :: Int64)) -- | Creates a 'Literal' of type @Int64#@ without checking its range. mkLitInt64Unchecked :: Integer -> Literal @@ -379,12 +427,12 @@ mkLitInt64Unchecked i = LitNumber LitNumInt64 i -- | Creates a 'Literal' of type @Word64#@ mkLitWord64 :: Integer -> Literal -mkLitWord64 x = ASSERT2( inWord64Range x, integer x ) (mkLitWord64Unchecked x) +mkLitWord64 x = ASSERT2( inBoundedRange @Word64 x, integer x ) (mkLitWord64Unchecked x) -- | Creates a 'Literal' of type @Word64#@. -- If the argument is out of the range, it is wrapped. -mkLitWord64Wrap :: Platform -> Integer -> Literal -mkLitWord64Wrap platform i = wrapLitNumber platform $ mkLitWord64Unchecked i +mkLitWord64Wrap :: Integer -> Literal +mkLitWord64Wrap i = LitNumber LitNumWord64 (toInteger (fromIntegral i :: Word64)) -- | Creates a 'Literal' of type @Word64#@ without checking its range. mkLitWord64Unchecked :: Integer -> Literal @@ -418,11 +466,43 @@ mkLitNatural x = ASSERT2( inNaturalRange x, integer x ) inNaturalRange :: Integer -> Bool inNaturalRange x = x >= 0 -inInt64Range, inWord64Range :: Integer -> Bool -inInt64Range x = x >= toInteger (minBound :: Int64) && - x <= toInteger (maxBound :: Int64) -inWord64Range x = x >= toInteger (minBound :: Word64) && - x <= toInteger (maxBound :: Word64) +inBoundedRange :: forall a. (Bounded a, Integral a) => Integer -> Bool +inBoundedRange x = x >= toInteger (minBound :: a) && + x <= toInteger (maxBound :: a) + +isMinBound :: Platform -> Literal -> Bool +isMinBound _ (LitChar c) = c == minBound +isMinBound platform (LitNumber nt i) = case nt of + LitNumInt -> i == platformMinInt platform + LitNumInt8 -> i == toInteger (minBound :: Int8) + LitNumInt16 -> i == toInteger (minBound :: Int16) + LitNumInt32 -> i == toInteger (minBound :: Int32) + LitNumInt64 -> i == toInteger (minBound :: Int64) + LitNumWord -> i == 0 + LitNumWord8 -> i == 0 + LitNumWord16 -> i == 0 + LitNumWord32 -> i == 0 + LitNumWord64 -> i == 0 + LitNumNatural -> i == 0 + LitNumInteger -> False +isMinBound _ _ = False + +isMaxBound :: Platform -> Literal -> Bool +isMaxBound _ (LitChar c) = c == maxBound +isMaxBound platform (LitNumber nt i) = case nt of + LitNumInt -> i == platformMaxInt platform + LitNumInt8 -> i == toInteger (maxBound :: Int8) + LitNumInt16 -> i == toInteger (maxBound :: Int16) + LitNumInt32 -> i == toInteger (maxBound :: Int32) + LitNumInt64 -> i == toInteger (maxBound :: Int64) + LitNumWord -> i == platformMaxWord platform + LitNumWord8 -> i == toInteger (maxBound :: Word8) + LitNumWord16 -> i == toInteger (maxBound :: Word16) + LitNumWord32 -> i == toInteger (maxBound :: Word32) + LitNumWord64 -> i == toInteger (maxBound :: Word64) + LitNumNatural -> False + LitNumInteger -> False +isMaxBound _ _ = False inCharRange :: Char -> Bool inCharRange c = c >= '\0' && c <= chr tARGET_MAX_CHAR @@ -456,7 +536,7 @@ isLitValue_maybe _ = Nothing mapLitValue :: Platform -> (Integer -> Integer) -> Literal -> Literal mapLitValue _ f (LitChar c) = mkLitChar (fchar c) where fchar = chr . fromInteger . f . toInteger . ord -mapLitValue platform f (LitNumber nt i) = wrapLitNumber platform (LitNumber nt (f i)) +mapLitValue platform f (LitNumber nt i) = mkLitNumberWrap platform nt (f i) mapLitValue _ _ l = pprPanic "mapLitValue" (ppr l) {- @@ -464,42 +544,12 @@ mapLitValue _ _ l = pprPanic "mapLitValue" (ppr l) ~~~~~~~~~ -} -narrow8IntLit, narrow16IntLit, narrow32IntLit, - narrow8WordLit, narrow16WordLit, narrow32WordLit, - charToIntLit, intToCharLit, - floatToIntLit, intToFloatLit, doubleToIntLit, intToDoubleLit, +charToIntLit, intToCharLit, + floatToIntLit, intToFloatLit, + doubleToIntLit, intToDoubleLit, floatToDoubleLit, doubleToFloatLit :: Literal -> Literal -wordToIntLit, intToWordLit :: Platform -> Literal -> Literal -wordToIntLit platform (LitNumber LitNumWord w) - -- Map Word range [max_int+1, max_word] - -- to Int range [min_int , -1] - -- Range [0,max_int] has the same representation with both Int and Word - | w > platformMaxInt platform = mkLitInt platform (w - platformMaxWord platform - 1) - | otherwise = mkLitInt platform w -wordToIntLit _ l = pprPanic "wordToIntLit" (ppr l) - -intToWordLit platform (LitNumber LitNumInt i) - -- Map Int range [min_int , -1] - -- to Word range [max_int+1, max_word] - -- Range [0,max_int] has the same representation with both Int and Word - | i < 0 = mkLitWord platform (1 + platformMaxWord platform + i) - | otherwise = mkLitWord platform i -intToWordLit _ l = pprPanic "intToWordLit" (ppr l) - --- | Narrow a literal number (unchecked result range) -narrowLit :: forall a. Integral a => Proxy a -> Literal -> Literal -narrowLit _ (LitNumber nt i) = LitNumber nt (toInteger (fromInteger i :: a)) -narrowLit _ l = pprPanic "narrowLit" (ppr l) - -narrow8IntLit = narrowLit (Proxy :: Proxy Int8) -narrow16IntLit = narrowLit (Proxy :: Proxy Int16) -narrow32IntLit = narrowLit (Proxy :: Proxy Int32) -narrow8WordLit = narrowLit (Proxy :: Proxy Word8) -narrow16WordLit = narrowLit (Proxy :: Proxy Word16) -narrow32WordLit = narrowLit (Proxy :: Proxy Word32) - charToIntLit (LitChar c) = mkLitIntUnchecked (toInteger (ord c)) charToIntLit l = pprPanic "charToIntLit" (ppr l) intToCharLit (LitNumber _ i) = LitChar (chr (fromInteger i)) @@ -572,8 +622,14 @@ litIsTrivial (LitNumber nt _) = case nt of LitNumInteger -> False LitNumNatural -> False LitNumInt -> True + LitNumInt8 -> True + LitNumInt16 -> True + LitNumInt32 -> True LitNumInt64 -> True LitNumWord -> True + LitNumWord8 -> True + LitNumWord16 -> True + LitNumWord32 -> True LitNumWord64 -> True litIsTrivial _ = True @@ -585,8 +641,14 @@ litIsDupable platform x = case x of LitNumInteger -> platformInIntRange platform i LitNumNatural -> platformInWordRange platform i LitNumInt -> True + LitNumInt8 -> True + LitNumInt16 -> True + LitNumInt32 -> True LitNumInt64 -> True LitNumWord -> True + LitNumWord8 -> True + LitNumWord16 -> True + LitNumWord32 -> True LitNumWord64 -> True (LitString _) -> False _ -> True @@ -601,8 +663,14 @@ litIsLifted (LitNumber nt _) = case nt of LitNumInteger -> True LitNumNatural -> True LitNumInt -> False + LitNumInt8 -> False + LitNumInt16 -> False + LitNumInt32 -> False LitNumInt64 -> False LitNumWord -> False + LitNumWord8 -> False + LitNumWord16 -> False + LitNumWord32 -> False LitNumWord64 -> False litIsLifted _ = False @@ -623,8 +691,14 @@ literalType (LitNumber lt _) = case lt of LitNumInteger -> integerTy LitNumNatural -> naturalTy LitNumInt -> intPrimTy + LitNumInt8 -> int8PrimTy + LitNumInt16 -> int16PrimTy + LitNumInt32 -> int32PrimTy LitNumInt64 -> int64PrimTy LitNumWord -> wordPrimTy + LitNumWord8 -> word8PrimTy + LitNumWord16 -> word16PrimTy + LitNumWord32 -> word32PrimTy LitNumWord64 -> word64PrimTy literalType (LitRubbish) = mkForAllTy a Inferred (mkTyVarTy a) where @@ -700,8 +774,14 @@ pprLiteral add_par (LitNumber nt i) LitNumInteger -> pprIntegerVal add_par i LitNumNatural -> pprIntegerVal add_par i LitNumInt -> pprPrimInt i + LitNumInt8 -> pprPrimInt8 i + LitNumInt16 -> pprPrimInt16 i + LitNumInt32 -> pprPrimInt32 i LitNumInt64 -> pprPrimInt64 i LitNumWord -> pprPrimWord i + LitNumWord8 -> pprPrimWord8 i + LitNumWord16 -> pprPrimWord16 i + LitNumWord32 -> pprPrimWord32 i LitNumWord64 -> pprPrimWord64 i pprLiteral add_par (LitLabel l mb fod) = add_par (text "__label" <+> b <+> ppr fod) @@ -743,9 +823,9 @@ LitChar 'a'# LitString "aaa"# LitNullAddr "__NULL" LitInt -1# -LitInt64 -1L# +LitIntN -1#N LitWord 1## -LitWord64 1L## +LitWordN 1##N LitFloat -1.0# LitDouble -1.0## LitInteger -1 (-1) ===================================== compiler/GHC/Utils/Outputable.hs ===================================== @@ -59,10 +59,18 @@ module GHC.Utils.Outputable ( pprInfixVar, pprPrefixVar, pprHsChar, pprHsString, pprHsBytes, - primFloatSuffix, primCharSuffix, primWordSuffix, primDoubleSuffix, - primInt64Suffix, primWord64Suffix, primIntSuffix, - - pprPrimChar, pprPrimInt, pprPrimWord, pprPrimInt64, pprPrimWord64, + primFloatSuffix, primCharSuffix, primDoubleSuffix, + primInt8Suffix, primWord8Suffix, + primInt16Suffix, primWord16Suffix, + primInt32Suffix, primWord32Suffix, + primInt64Suffix, primWord64Suffix, + primIntSuffix, primWordSuffix, + + pprPrimChar, pprPrimInt, pprPrimWord, + pprPrimInt8, pprPrimWord8, + pprPrimInt16, pprPrimWord16, + pprPrimInt32, pprPrimWord32, + pprPrimInt64, pprPrimWord64, pprFastFilePath, pprFilePathString, @@ -1148,22 +1156,44 @@ pprHsBytes bs = let escaped = concatMap escape $ BS.unpack bs -- Postfix modifiers for unboxed literals. -- See Note [Printing of literals in Core] in "GHC.Types.Literal". -primCharSuffix, primFloatSuffix, primIntSuffix :: SDoc -primDoubleSuffix, primWordSuffix, primInt64Suffix, primWord64Suffix :: SDoc +primCharSuffix, primFloatSuffix, primDoubleSuffix, + primIntSuffix, primWordSuffix, + primInt8Suffix, primWord8Suffix, + primInt16Suffix, primWord16Suffix, + primInt32Suffix, primWord32Suffix, + primInt64Suffix, primWord64Suffix + :: SDoc primCharSuffix = char '#' primFloatSuffix = char '#' primIntSuffix = char '#' primDoubleSuffix = text "##" primWordSuffix = text "##" -primInt64Suffix = text "L#" -primWord64Suffix = text "L##" +primInt8Suffix = text "#8" +primWord8Suffix = text "##8" +primInt16Suffix = text "#16" +primWord16Suffix = text "##16" +primInt32Suffix = text "#32" +primWord32Suffix = text "##32" +primInt64Suffix = text "#64" +primWord64Suffix = text "##64" -- | Special combinator for showing unboxed literals. pprPrimChar :: Char -> SDoc -pprPrimInt, pprPrimWord, pprPrimInt64, pprPrimWord64 :: Integer -> SDoc +pprPrimInt, pprPrimWord, + pprPrimInt8, pprPrimWord8, + pprPrimInt16, pprPrimWord16, + pprPrimInt32, pprPrimWord32, + pprPrimInt64, pprPrimWord64 + :: Integer -> SDoc pprPrimChar c = pprHsChar c <> primCharSuffix pprPrimInt i = integer i <> primIntSuffix pprPrimWord w = word w <> primWordSuffix +pprPrimInt8 i = integer i <> primInt8Suffix +pprPrimWord8 w = word w <> primWord8Suffix +pprPrimInt16 i = integer i <> primInt16Suffix +pprPrimWord16 w = word w <> primWord16Suffix +pprPrimInt32 i = integer i <> primInt32Suffix +pprPrimWord32 w = word w <> primWord32Suffix pprPrimInt64 i = integer i <> primInt64Suffix pprPrimWord64 w = word w <> primWord64Suffix ===================================== testsuite/driver/testlib.py ===================================== @@ -2163,7 +2163,7 @@ def normalise_callstacks(s: str) -> str: s = re.sub(r'CallStack \(from -prof\):(\n .*)*\n?', '', s) return s -tyCon_re = re.compile(r'TyCon\s*\d+L?\#\#\s*\d+L?\#\#\s*', flags=re.MULTILINE) +tyCon_re = re.compile(r'TyCon\s*\d+\#\#\d?\d?\s*\d+\#\#\d?\d?\s*', flags=re.MULTILINE) def normalise_type_reps(s: str) -> str: """ Normalise out fingerprints from Typeable TyCon representations """ ===================================== testsuite/tests/cmm/opt/T18141.hs ===================================== @@ -12,6 +12,6 @@ x# `divInt8#` y# ((x# `plusInt8#` one#) `quotInt8#` y#) `subInt8#` one# | otherwise = x# `quotInt8#` y# where - zero# = narrowInt8# 0# - one# = narrowInt8# 1# + zero# = intToInt8# 0# + one# = intToInt8# 1# ===================================== testsuite/tests/codeGen/should_compile/T18614.hs ===================================== @@ -8,4 +8,4 @@ import GHC.Exts main = pure () test :: Word8# -> Word8# -test x = x `plusWord8#` narrowWord8# 1## +test x = x `plusWord8#` wordToWord8# 1## ===================================== testsuite/tests/ffi/should_run/PrimFFIInt16.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_int16" main :: IO () main = do - let a = narrowInt16# 0# - b = narrowInt16# 1# - c = narrowInt16# 2# - d = narrowInt16# 3# - e = narrowInt16# 4# - f = narrowInt16# 5# - g = narrowInt16# 6# - h = narrowInt16# 7# - i = narrowInt16# 8# - j = narrowInt16# 9# - x = I# (extendInt16# (add_all_int16 a b c d e f g h i j)) + let a = intToInt16# 0# + b = intToInt16# 1# + c = intToInt16# 2# + d = intToInt16# 3# + e = intToInt16# 4# + f = intToInt16# 5# + g = intToInt16# 6# + h = intToInt16# 7# + i = intToInt16# 8# + j = intToInt16# 9# + x = I# (int16ToInt# (add_all_int16 a b c d e f g h i j)) print x ===================================== testsuite/tests/ffi/should_run/PrimFFIInt8.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_int8" main :: IO () main = do - let a = narrowInt8# 0# - b = narrowInt8# 1# - c = narrowInt8# 2# - d = narrowInt8# 3# - e = narrowInt8# 4# - f = narrowInt8# 5# - g = narrowInt8# 6# - h = narrowInt8# 7# - i = narrowInt8# 8# - j = narrowInt8# 9# - x = I# (extendInt8# (add_all_int8 a b c d e f g h i j)) + let a = intToInt8# 0# + b = intToInt8# 1# + c = intToInt8# 2# + d = intToInt8# 3# + e = intToInt8# 4# + f = intToInt8# 5# + g = intToInt8# 6# + h = intToInt8# 7# + i = intToInt8# 8# + j = intToInt8# 9# + x = I# (int8ToInt# (add_all_int8 a b c d e f g h i j)) print x ===================================== testsuite/tests/ffi/should_run/PrimFFIWord16.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_word16" main :: IO () main = do - let a = narrowWord16# 0## - b = narrowWord16# 1## - c = narrowWord16# 2## - d = narrowWord16# 3## - e = narrowWord16# 4## - f = narrowWord16# 5## - g = narrowWord16# 6## - h = narrowWord16# 7## - i = narrowWord16# 8## - j = narrowWord16# 9## - x = W# (extendWord16# (add_all_word16 a b c d e f g h i j)) + let a = wordToWord16# 0## + b = wordToWord16# 1## + c = wordToWord16# 2## + d = wordToWord16# 3## + e = wordToWord16# 4## + f = wordToWord16# 5## + g = wordToWord16# 6## + h = wordToWord16# 7## + i = wordToWord16# 8## + j = wordToWord16# 9## + x = W# (word16ToWord# (add_all_word16 a b c d e f g h i j)) print x ===================================== testsuite/tests/ffi/should_run/PrimFFIWord8.hs ===================================== @@ -14,15 +14,15 @@ foreign import ccall "add_all_word8" main :: IO () main = do - let a = narrowWord8# 0## - b = narrowWord8# 1## - c = narrowWord8# 2## - d = narrowWord8# 3## - e = narrowWord8# 4## - f = narrowWord8# 5## - g = narrowWord8# 6## - h = narrowWord8# 7## - i = narrowWord8# 8## - j = narrowWord8# 9## - x = W# (extendWord8# (add_all_word8 a b c d e f g h i j)) + let a = wordToWord8# 0## + b = wordToWord8# 1## + c = wordToWord8# 2## + d = wordToWord8# 3## + e = wordToWord8# 4## + f = wordToWord8# 5## + g = wordToWord8# 6## + h = wordToWord8# 7## + i = wordToWord8# 8## + j = wordToWord8# 9## + x = W# (word8ToWord# (add_all_word8 a b c d e f g h i j)) print x ===================================== testsuite/tests/primops/should_run/ArithInt16.hs ===================================== @@ -146,32 +146,32 @@ addMany (I# a) (I# b) (I# c) (I# d) (I# e) (I# f) (I# g) (I# h) (I# i) (I# j) (I# k) (I# l) (I# m) (I# n) (I# o) (I# p) - = I# (extendInt16# int16) + = I# (int16ToInt# int16) where !int16 = addMany# - (narrowInt16# a) (narrowInt16# b) (narrowInt16# c) (narrowInt16# d) - (narrowInt16# e) (narrowInt16# f) (narrowInt16# g) (narrowInt16# h) - (narrowInt16# i) (narrowInt16# j) (narrowInt16# k) (narrowInt16# l) - (narrowInt16# m) (narrowInt16# n) (narrowInt16# o) (narrowInt16# p) + (intToInt16# a) (intToInt16# b) (intToInt16# c) (intToInt16# d) + (intToInt16# e) (intToInt16# f) (intToInt16# g) (intToInt16# h) + (intToInt16# i) (intToInt16# j) (intToInt16# k) (intToInt16# l) + (intToInt16# m) (intToInt16# n) (intToInt16# o) (intToInt16# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Int16# apply1 :: (Int16# -> Int16#) -> Int -> Int -apply1 opToTest (I# a) = I# (extendInt16# (opToTest (narrowInt16# a))) +apply1 opToTest (I# a) = I# (int16ToInt# (opToTest (intToInt16# a))) {-# NOINLINE apply1 #-} apply2 :: (Int16# -> Int16# -> Int16#) -> Int -> Int -> Int apply2 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) + let (# sa, sb #) = (# intToInt16# a, intToInt16# b #) r = opToTest sa sb - in I# (extendInt16# r) + in I# (int16ToInt# r) {-# NOINLINE apply2 #-} apply3 :: (Int16# -> Int16# -> (# Int16#, Int16# #)) -> Int -> Int -> (Int, Int) apply3 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt16# a, narrowInt16# b #) + let (# sa, sb #) = (# intToInt16# a, intToInt16# b #) (# ra, rb #) = opToTest sa sb - in (I# (extendInt16# ra), I# (extendInt16# rb)) + in (I# (int16ToInt# ra), I# (int16ToInt# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/ArithInt8.hs ===================================== @@ -150,32 +150,32 @@ addMany (I# a) (I# b) (I# c) (I# d) (I# e) (I# f) (I# g) (I# h) (I# i) (I# j) (I# k) (I# l) (I# m) (I# n) (I# o) (I# p) - = I# (extendInt8# int8) + = I# (int8ToInt# int8) where !int8 = addMany# - (narrowInt8# a) (narrowInt8# b) (narrowInt8# c) (narrowInt8# d) - (narrowInt8# e) (narrowInt8# f) (narrowInt8# g) (narrowInt8# h) - (narrowInt8# i) (narrowInt8# j) (narrowInt8# k) (narrowInt8# l) - (narrowInt8# m) (narrowInt8# n) (narrowInt8# o) (narrowInt8# p) + (intToInt8# a) (intToInt8# b) (intToInt8# c) (intToInt8# d) + (intToInt8# e) (intToInt8# f) (intToInt8# g) (intToInt8# h) + (intToInt8# i) (intToInt8# j) (intToInt8# k) (intToInt8# l) + (intToInt8# m) (intToInt8# n) (intToInt8# o) (intToInt8# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Int8# apply1 :: (Int8# -> Int8#) -> Int -> Int -apply1 opToTest (I# a) = I# (extendInt8# (opToTest (narrowInt8# a))) +apply1 opToTest (I# a) = I# (int8ToInt# (opToTest (intToInt8# a))) {-# NOINLINE apply1 #-} apply2 :: (Int8# -> Int8# -> Int8#) -> Int -> Int -> Int apply2 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt8# a, narrowInt8# b #) + let (# sa, sb #) = (# intToInt8# a, intToInt8# b #) r = opToTest sa sb - in I# (extendInt8# r) + in I# (int8ToInt# r) {-# NOINLINE apply2 #-} apply3 :: (Int8# -> Int8# -> (# Int8#, Int8# #)) -> Int -> Int -> (Int, Int) apply3 opToTest (I# a) (I# b) = - let (# sa, sb #) = (# narrowInt8# a, narrowInt8# b #) + let (# sa, sb #) = (# intToInt8# a, intToInt8# b #) (# ra, rb #) = opToTest sa sb - in (I# (extendInt8# ra), I# (extendInt8# rb)) + in (I# (int8ToInt# ra), I# (int8ToInt# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/ArithWord16.hs ===================================== @@ -141,34 +141,34 @@ addMany (W# a) (W# b) (W# c) (W# d) (W# e) (W# f) (W# g) (W# h) (W# i) (W# j) (W# k) (W# l) (W# m) (W# n) (W# o) (W# p) - = W# (extendWord16# word16) + = W# (word16ToWord# word16) where !word16 = addMany# - (narrowWord16# a) (narrowWord16# b) (narrowWord16# c) (narrowWord16# d) - (narrowWord16# e) (narrowWord16# f) (narrowWord16# g) (narrowWord16# h) - (narrowWord16# i) (narrowWord16# j) (narrowWord16# k) (narrowWord16# l) - (narrowWord16# m) (narrowWord16# n) (narrowWord16# o) (narrowWord16# p) + (wordToWord16# a) (wordToWord16# b) (wordToWord16# c) (wordToWord16# d) + (wordToWord16# e) (wordToWord16# f) (wordToWord16# g) (wordToWord16# h) + (wordToWord16# i) (wordToWord16# j) (wordToWord16# k) (wordToWord16# l) + (wordToWord16# m) (wordToWord16# n) (wordToWord16# o) (wordToWord16# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Word16# apply1 :: (Word16# -> Word16#) -> Word -> Word -apply1 opToTest (W# a) = W# (extendWord16# (opToTest (narrowWord16# a))) +apply1 opToTest (W# a) = W# (word16ToWord# (opToTest (wordToWord16# a))) {-# NOINLINE apply1 #-} apply2 :: (Word16# -> Word16# -> Word16#) -> Word -> Word -> Word apply2 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord16# a, narrowWord16# b #) + let (# sa, sb #) = (# wordToWord16# a, wordToWord16# b #) r = opToTest sa sb - in W# (extendWord16# r) + in W# (word16ToWord# r) {-# NOINLINE apply2 #-} apply3 :: (Word16# -> Word16# -> (# Word16#, Word16# #)) -> Word -> Word -> (Word, Word) apply3 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord16# a, narrowWord16# b #) + let (# sa, sb #) = (# wordToWord16# a, wordToWord16# b #) (# ra, rb #) = opToTest sa sb - in (W# (extendWord16# ra), W# (extendWord16# rb)) + in (W# (word16ToWord# ra), W# (word16ToWord# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/ArithWord8.hs ===================================== @@ -145,34 +145,34 @@ addMany (W# a) (W# b) (W# c) (W# d) (W# e) (W# f) (W# g) (W# h) (W# i) (W# j) (W# k) (W# l) (W# m) (W# n) (W# o) (W# p) - = W# (extendWord8# word8) + = W# (word8ToWord# word8) where !word8 = addMany# - (narrowWord8# a) (narrowWord8# b) (narrowWord8# c) (narrowWord8# d) - (narrowWord8# e) (narrowWord8# f) (narrowWord8# g) (narrowWord8# h) - (narrowWord8# i) (narrowWord8# j) (narrowWord8# k) (narrowWord8# l) - (narrowWord8# m) (narrowWord8# n) (narrowWord8# o) (narrowWord8# p) + (wordToWord8# a) (wordToWord8# b) (wordToWord8# c) (wordToWord8# d) + (wordToWord8# e) (wordToWord8# f) (wordToWord8# g) (wordToWord8# h) + (wordToWord8# i) (wordToWord8# j) (wordToWord8# k) (wordToWord8# l) + (wordToWord8# m) (wordToWord8# n) (wordToWord8# o) (wordToWord8# p) {-# NOINLINE addMany #-} -- Convenient and also tests higher order functions on Word8# apply1 :: (Word8# -> Word8#) -> Word -> Word -apply1 opToTest (W# a) = W# (extendWord8# (opToTest (narrowWord8# a))) +apply1 opToTest (W# a) = W# (word8ToWord# (opToTest (wordToWord8# a))) {-# NOINLINE apply1 #-} apply2 :: (Word8# -> Word8# -> Word8#) -> Word -> Word -> Word apply2 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord8# a, narrowWord8# b #) + let (# sa, sb #) = (# wordToWord8# a, wordToWord8# b #) r = opToTest sa sb - in W# (extendWord8# r) + in W# (word8ToWord# r) {-# NOINLINE apply2 #-} apply3 :: (Word8# -> Word8# -> (# Word8#, Word8# #)) -> Word -> Word -> (Word, Word) apply3 opToTest (W# a) (W# b) = - let (# sa, sb #) = (# narrowWord8# a, narrowWord8# b #) + let (# sa, sb #) = (# wordToWord8# a, wordToWord8# b #) (# ra, rb #) = opToTest sa sb - in (W# (extendWord8# ra), W# (extendWord8# rb)) + in (W# (word8ToWord# ra), W# (word8ToWord# rb)) {-# NOINLINE apply3 #-} instance ===================================== testsuite/tests/primops/should_run/CmpInt16.hs ===================================== @@ -16,7 +16,7 @@ data TestInt16 = T16 Int16# deriving (Eq, Ord) mkT16 :: Int -> TestInt16 -mkT16 (I# a) = T16 (narrowInt16# a) +mkT16 (I# a) = T16 (intToInt16# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/CmpInt8.hs ===================================== @@ -16,7 +16,7 @@ data TestInt8 = T8 Int8# deriving (Eq, Ord) mkT8 :: Int -> TestInt8 -mkT8 (I# a) = T8 (narrowInt8# a) +mkT8 (I# a) = T8 (intToInt8# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/CmpWord16.hs ===================================== @@ -16,7 +16,7 @@ data TestWord16 = T16 Word16# deriving (Eq, Ord) mkT16 :: Word -> TestWord16 -mkT16 (W# a) = T16 (narrowWord16# a) +mkT16 (W# a) = T16 (wordToWord16# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/CmpWord8.hs ===================================== @@ -16,7 +16,7 @@ data TestWord8 = T8 Word8# deriving (Eq, Ord) mkT8 :: Word -> TestWord8 -mkT8 (W# a) = T8 (narrowWord8# a) +mkT8 (W# a) = T8 (wordToWord8# a) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/ShowPrim.hs ===================================== @@ -11,10 +11,10 @@ data Test2 = Test2 Int16# Word16# deriving (Show) test1 :: Test1 -test1 = Test1 (narrowInt8# 1#) (narrowWord8# 2##) +test1 = Test1 (intToInt8# 1#) (wordToWord8# 2##) test2 :: Test2 -test2 = Test2 (narrowInt16# 1#) (narrowWord16# 2##) +test2 = Test2 (intToInt16# 1#) (wordToWord16# 2##) main :: IO () main = do ===================================== testsuite/tests/primops/should_run/ShowPrim.stdout ===================================== @@ -1,2 +1,2 @@ -Test1 (narrowInt8# 1#) (narrowWord8# 2##) -Test2 (narrowInt16# 1#) (narrowWord16# 2##) +Test1 (intToInt8# 1#) (wordToWord8# 2##) +Test2 (intToInt16# 1#) (wordToWord16# 2##) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f004001ecd2b87d63a15ace3dd7035cc05ef6787...cfb672c49dc9081982f9284abf6302fd202f4eea -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f004001ecd2b87d63a15ace3dd7035cc05ef6787...cfb672c49dc9081982f9284abf6302fd202f4eea 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 Mon Nov 23 15:38:35 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Mon, 23 Nov 2020 10:38:35 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 9 commits: Cleanup some primop-related identifers Message-ID: <5fbbd77b77ac_36a71579be44741094@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 58a37f8b by John Ericson at 2020-11-23T04:50:12+00:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - cfb672c4 by Sylvain Henry at 2020-11-23T15:37:10+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - b08dae07 by John Ericson at 2020-11-23T15:38:21+00:00 Merge branch 'wip/fix-64-toArgRep' into HEAD - - - - - f69fc06b by John Ericson at 2020-11-23T15:38:22+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 1719e501 by John Ericson at 2020-11-23T15:38:22+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - f3d65cc0 by Sylvain Henry at 2020-11-23T15:38:22+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - fee83bad by John Ericson at 2020-11-23T15:38:22+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - c28f1dd8 by John Ericson at 2020-11-23T15:38:22+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 7e057ab9 by John Ericson at 2020-11-23T15:38:22+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs - libraries/base/GHC/Float/RealFracMethods.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Integer.hs - libraries/base/GHC/StaticPtr.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/beba0c1e4a7a6a9547e5d110172dbf1403a5e0ac...7e057ab98551b7f49e0d336700c3312a74f90610 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/beba0c1e4a7a6a9547e5d110172dbf1403a5e0ac...7e057ab98551b7f49e0d336700c3312a74f90610 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 Mon Nov 23 15:38:48 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Mon, 23 Nov 2020 10:38:48 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere-new-float-primops] 10 commits: Cleanup some primop-related identifers Message-ID: <5fbbd788c00a5_36a7643e3007418b2@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere-new-float-primops at Glasgow Haskell Compiler / GHC Commits: 58a37f8b by John Ericson at 2020-11-23T04:50:12+00:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - cfb672c4 by Sylvain Henry at 2020-11-23T15:37:10+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - b08dae07 by John Ericson at 2020-11-23T15:38:21+00:00 Merge branch 'wip/fix-64-toArgRep' into HEAD - - - - - f69fc06b by John Ericson at 2020-11-23T15:38:22+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 1719e501 by John Ericson at 2020-11-23T15:38:22+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - f3d65cc0 by Sylvain Henry at 2020-11-23T15:38:22+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - fee83bad by John Ericson at 2020-11-23T15:38:22+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - c28f1dd8 by John Ericson at 2020-11-23T15:38:22+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 7e057ab9 by John Ericson at 2020-11-23T15:38:22+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 058ad876 by John Ericson at 2020-11-23T15:38:45+00:00 WIP: Add missing floats <-> int/word 64 rule and primops - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/CPrim.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - includes/stg/Prim.h - libraries/base/GHC/Exts.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/Float/ConversionUtils.hs - libraries/base/GHC/Float/RealFracMethods.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Integer.hs - libraries/base/GHC/StaticPtr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8569aa12c9e2b2c014f0096f1e52641aecebb159...058ad8764037428307839660f5df7e38fc59fa38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8569aa12c9e2b2c014f0096f1e52641aecebb159...058ad8764037428307839660f5df7e38fc59fa38 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 Mon Nov 23 16:37:32 2020 From: gitlab at gitlab.haskell.org (Alan Zimmerman) Date: Mon, 23 Nov 2020 11:37:32 -0500 Subject: [Git][ghc/ghc][wip/az/exactprint] WIP on delta printing. Message-ID: <5fbbe54ccc2fc_36a73fd2f208ef8074968a@gitlab.mail> Alan Zimmerman pushed to branch wip/az/exactprint at Glasgow Haskell Compiler / GHC Commits: 48aec3eb by Alan Zimmerman at 2020-11-23T16:36:36+00:00 WIP on delta printing. Making progress - - - - - 16 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/ThToHs.hs - utils/check-exact/Main.hs - utils/check-exact/Test.hs - + utils/check-exact/cases/LayoutLet2.hs - + utils/check-exact/cases/RenameCase1.hs - utils/check-exact/check-exact.cabal - utils/check-exact/src/ExactPrint.hs - utils/check-exact/src/Utils.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1925,10 +1925,9 @@ data GRHSs p body } | XGRHSs !(XXGRHSs p body) - -- MatchContext dependent, as per 'matchSeparator' -type instance XCGRHSs (GhcPass _) b = ApiAnn' AddApiAnn +type instance XCGRHSs (GhcPass _) _ = NoExtField -type instance XXGRHSs (GhcPass _) b = NoExtCon +type instance XXGRHSs (GhcPass _) _ = NoExtCon -- | Located Guarded Right-Hand Side type LGRHS id body = XRec id (GRHS id body) @@ -1943,11 +1942,11 @@ data GRHS p body = GRHS (XCGRHS p body) body -- Right hand side | XGRHS !(XXGRHS p body) -type instance XCGRHS (GhcPass _) b = ApiAnn' GrhsAnn +type instance XCGRHS (GhcPass _) _ = ApiAnn' GrhsAnn -- Location of matchSeparator -- TODO:AZ does this belong on the GRHS, or GRHSs? -type instance XXGRHS (GhcPass _) b = NoExtCon +type instance XXGRHS (GhcPass _) _ = NoExtCon data GrhsAnn = GrhsAnn { ===================================== compiler/GHC/Hs/Type.hs ===================================== @@ -1120,7 +1120,7 @@ data HsType pass -- For adding new constructors via Trees that Grow | XHsType - (XXType pass) + !(XXType pass) data NewHsTypeX = NHsCoreTy Type -- An escape hatch for tunnelling a *closed* ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -185,10 +185,10 @@ mkSimpleMatch ctxt pats rhs unguardedGRHSs :: Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan - => LocatedA (body (GhcPass p)) -> ApiAnn' AddApiAnn + => LocatedA (body (GhcPass p)) -> ApiAnn' GrhsAnn -> GRHSs (GhcPass p) (LocatedA (body (GhcPass p))) unguardedGRHSs rhs@(L loc _) ann - = GRHSs ann (unguardedRHS noAnn (locA loc) rhs) emptyLocalBinds + = GRHSs noExtField (unguardedRHS ann (locA loc) rhs) emptyLocalBinds unguardedRHS :: Anno (GRHS (GhcPass p) (LocatedA (body (GhcPass p)))) ~ SrcSpan @@ -907,7 +907,7 @@ mkMatch ctxt pats expr binds = noLocA (Match { m_ext = noAnn , m_ctxt = ctxt , m_pats = map paren pats - , m_grhss = GRHSs noAnn (unguardedRHS noAnn noSrcSpan expr) binds }) + , m_grhss = GRHSs noExtField (unguardedRHS noAnn noSrcSpan expr) binds }) where paren :: LPat (GhcPass p) -> LPat (GhcPass p) paren lp@(L l p) ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -504,7 +504,7 @@ dsExpr (HsMultiIf res_ty alts) = mkErrorExpr | otherwise - = do { let grhss = GRHSs noAnn alts emptyLocalBinds + = do { let grhss = GRHSs noExtField alts emptyLocalBinds ; rhss_nablas <- pmcGRHSs IfAlt grhss ; match_result <- dsGRHSs IfAlt grhss res_ty rhss_nablas ; error_expr <- mkErrorExpr ===================================== compiler/GHC/Parser.y ===================================== @@ -2486,10 +2486,10 @@ rhs :: { Located (GRHSs GhcPs (LHsExpr GhcPs)) } : '=' exp wherebinds {% runPV (unECP $2) >>= \ $2 -> do { let loc = (comb3 $1 (reLoc $2) (adaptWhereBinds $3)) ; acs (\cs -> - sL loc (GRHSs (ApiAnn (rs loc) (mj AnnEqual $1) cs) (unguardedRHS (ApiAnn (rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) []) loc $2) + sL loc (GRHSs NoExtField (unguardedRHS (ApiAnn (rs loc) (GrhsAnn Nothing (mj AnnEqual $1)) cs) loc $2) (unLoc $ (adaptWhereBinds $3)))) } } | gdrhs wherebinds { sL (comb2 $1 (adaptWhereBinds $>)) - (GRHSs noAnn (reverse (unLoc $1)) (unLoc $ (adaptWhereBinds $2))) } + (GRHSs noExtField (reverse (unLoc $1)) (unLoc $ (adaptWhereBinds $2))) } gdrhs :: { Located [LGRHS GhcPs (LHsExpr GhcPs)] } : gdrhs gdrh { sLL $1 $> ($2 : unLoc $1) } @@ -2755,7 +2755,7 @@ aexp :: { ECP } $ Match { m_ext = ApiAnn (glR $1) [mj AnnLam $1] cs , m_ctxt = LambdaExpr , m_pats = $2:$3 - , m_grhss = unguardedGRHSs $5 (ApiAnn (glR $4) (mu AnnRarrow $4) []) }])) } + , m_grhss = unguardedGRHSs $5 (ApiAnn (glR $4) (GrhsAnn Nothing (mu AnnRarrow $4)) []) }])) } | 'let' binds 'in' exp { ECP $ unECP $4 >>= \ $4 -> mkHsLetPV (comb2A $1 $>) (unLoc $2) $4 @@ -3181,7 +3181,7 @@ alt :: { forall b. DisambECP b => PV (LMatch GhcPs (LocatedA b)) } alt_rhs :: { forall b. DisambECP b => PV (Located (GRHSs GhcPs (LocatedA b))) } : ralt wherebinds { $1 >>= \alt -> - return $ sLL alt (adaptWhereBinds $>) (GRHSs noAnn (unLoc alt) (unLoc $ adaptWhereBinds $2)) } + return $ sLL alt (adaptWhereBinds $>) (GRHSs noExtField (unLoc alt) (unLoc $ adaptWhereBinds $2)) } ralt :: { forall b. DisambECP b => PV (Located [LGRHS GhcPs (LocatedA b)]) } : '->' exp { unECP $2 >>= \ $2 -> ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -498,6 +498,13 @@ defined. -- AnnKeywordId elements. Note: we may reduce the usage of -- AnnKeywordId, and use locations only, as captured in that -- structure. +-- +-- The spacing between the items under the scope of a given ApiAnn' is +-- derived from the original 'anchor'. But there is no requirement +-- that the items included in the sub-element have a "matching" +-- location in their relative anchors. This allows us to freely move +-- elements around, and stitch together new AST fragments out of old +-- ones, and have them still printed out in a reasonable way. data ApiAnn' ann = ApiAnn { anchor :: RealSrcSpan -- ^ Base location for the start of -- the syntactic element holding the @@ -514,6 +521,9 @@ data ApiAnn' ann type ApiAnn = ApiAnn' [AddApiAnn] type ApiAnnComments = [RealLocated AnnotationComment] +-- +| Relative positions, row then column +-- newtype DeltaPos = DP (Int,Int) deriving (Show,Eq,Ord,Typeable,Data) + data NoApiAnns = NoApiAnns deriving (Data,Eq,Ord) ===================================== compiler/GHC/Rename/Bind.hs ===================================== @@ -1232,7 +1232,7 @@ rnGRHSs :: AnnoBody body rnGRHSs ctxt rnBody (GRHSs _ grhss binds) = rnLocalBindsAndThen binds $ \ binds' _ -> do (grhss', fvGRHSs) <- mapFvRn (rnGRHS ctxt rnBody) grhss - return (GRHSs noAnn grhss' binds', fvGRHSs) + return (GRHSs noExtField grhss' binds', fvGRHSs) rnGRHS :: AnnoBody body => HsMatchContext GhcRn ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -276,7 +276,7 @@ tcGRHSs ctxt (GRHSs _ grhss binds) res_ty mapM (tcCollectingUsage . wrapLocM (tcGRHS ctxt res_ty)) grhss ; let (usages, grhss') = unzip ugrhss ; tcEmitBindingUsage $ supUEs usages - ; return (GRHSs noAnn grhss' binds') } + ; return (GRHSs noExtField grhss' binds') } ------------- tcGRHS :: TcMatchCtxt body -> ExpRhoType -> GRHS GhcRn (LocatedA (body GhcRn)) ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -190,7 +190,7 @@ cvtDec (TH.ValD pat body ds) ; ds' <- cvtLocalDecs (text "a where clause") ds ; returnJustLA $ Hs.ValD noExtField $ PatBind { pat_lhs = pat' - , pat_rhs = GRHSs noAnn body' ds' + , pat_rhs = GRHSs noExtField body' ds' , pat_ext = noAnn , pat_ticks = ([],[]) } } @@ -904,7 +904,7 @@ cvtClause ctxt (Clause ps body wheres) ; let pps = map (parenthesizePat appPrec) ps' ; g' <- cvtGuard body ; ds' <- cvtLocalDecs (text "a where clause") wheres - ; returnLA $ Hs.Match noAnn ctxt pps (GRHSs noAnn g' ds') } + ; returnLA $ Hs.Match noAnn ctxt pps (GRHSs noExtField g' ds') } cvtImplicitParamBind :: String -> TH.Exp -> CvtM (LIPBind GhcPs) cvtImplicitParamBind n e = do @@ -1213,7 +1213,7 @@ cvtMatch ctxt (TH.Match p body decs) _ -> p' ; g' <- cvtGuard body ; decs' <- cvtLocalDecs (text "a where clause") decs - ; returnLA $ Hs.Match noAnn ctxt [lp] (GRHSs noAnn g' decs') } + ; returnLA $ Hs.Match noAnn ctxt [lp] (GRHSs noExtField g' decs') } cvtGuard :: TH.Body -> CvtM [LGRHS GhcPs (LHsExpr GhcPs)] cvtGuard (GuardedB pairs) = mapM cvtpair pairs ===================================== utils/check-exact/Main.hs ===================================== @@ -6,9 +6,9 @@ import GHC hiding (moduleName) import GHC.Driver.Ppr import GHC.Driver.Session import GHC.Hs.Dump -import GHC.Types.SourceText +-- import GHC.Types.SourceText -- import GHC.Hs.Exact hiding (ExactPrint()) -import GHC.Utils.Outputable hiding (space) +-- import GHC.Utils.Outputable hiding (space) import System.Environment( getArgs ) import System.Exit import System.FilePath @@ -21,7 +21,6 @@ import ExactPrint tt :: IO () -- tt = testOneFile "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/lib" tt = testOneFile "/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib" - -- "Test.hs" -- "../../testsuite/tests/printer/Ppr001.hs" -- "../../testsuite/tests/printer/Ppr002.hs" -- "../../testsuite/tests/printer/Ppr003.hs" ===================================== utils/check-exact/Test.hs ===================================== @@ -1,34 +1,189 @@ -{-# LANGUAGE ParallelListComp #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE MagicHash, NoImplicitPrelude, TypeFamilies, UnboxedTuples #-} -module - Main - ( - main - , - foo - ) - where - -import {-# SOURCE #-} qualified Data.List as L -import Data.Map hiding ( Map(..) ) - -main = - putStrLn "hello" - -foo = 1 - - --- | '(' qconsym ')' {% amsr (sLL $1 $> (unLoc $2)) --- [mop $1,mjA AnnVal $2,mcp $3] } -f1 = ( Main.::: ) 0 1 - --- | '(' consym ')' {% amsr (sLL $1 $> (unLoc $2)) --- [mop $1,mjA AnnVal $2,mcp $3] } -f2 = ( ::: ) 0 1 - --- | '`' conid '`' {% amsr (sLL $1 $> (unLoc $2)) --- [mj AnnBackquote $1,mjA AnnVal $2 --- ,mj AnnBackquote $3] } --- data GG = GG Int Int --- gg = 0 ` GG ` 1 +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE ScopedTypeVariables #-} + +-- import Data.List +import Data.Data +import Data.Typeable +-- import GHC.Types.SrcLoc +import GHC.Types.Name.Occurrence +import GHC.Types.Name.Reader +import GHC hiding (moduleName) +import GHC.Driver.Ppr +import GHC.Driver.Session +import GHC.Hs.Dump +-- import GHC.Types.SourceText +-- import GHC.Hs.Exact hiding (ExactPrint()) +-- import GHC.Utils.Outputable hiding (space) +import System.Environment( getArgs ) +import System.Exit +import System.FilePath + +import Types +import Utils +import ExactPrint +-- exactPrint = undefined +-- showPprUnsafe = undefined + +-- --------------------------------------------------------------------- + +tt :: IO () +-- tt = testOneFile "/home/alanz/mysrc/git.haskell.org/ghc/_build/stage1/lib" +tt = testOneFile "/home/alanz/mysrc/git.haskell.org/worktree/exactprint/_build/stage1/lib" + "cases/RenameCase1.hs" changeRenameCase1 + -- "cases/LayoutLet2.hs" changeLayoutLet2 + +-- exact = ppr + +-- --------------------------------------------------------------------- + +usage :: String +usage = unlines + [ "usage: check-ppr (libdir) (file)" + , "" + , "where libdir is the GHC library directory (e.g. the output of" + , "ghc --print-libdir) and file is the file to parse." + ] + +main :: IO() +main = do + args <- getArgs + case args of + [libdir,fileName] -> testOneFile libdir fileName noChange + _ -> putStrLn usage + +testOneFile :: FilePath -> String -> Changer -> IO () +testOneFile libdir fileName changer = do + p <- parseOneFile libdir fileName + -- putStrLn $ "\n\ngot p" + let + origAst = showSDocUnsafe + $ showAstData BlankSrcSpanFile NoBlankApiAnnotations + (pm_parsed_source p) + anns' = pm_annotations p + -- pped = pragmas ++ "\n" ++ (exactPrint $ pm_parsed_source p) + pped = exactPrint (pm_parsed_source p) anns' + -- pragmas = getPragmas anns' + + newFile = dropExtension fileName <.> "ppr" <.> takeExtension fileName + newFileChanged = dropExtension fileName <.> "changed" <.> takeExtension fileName + astFile = fileName <.> "ast" + newAstFile = fileName <.> "ast.new" + + -- pped' <- exactprintWithChange changeRenameCase1 (pm_parsed_source p) anns' + pped' <- exactprintWithChange changer (pm_parsed_source p) anns' + -- putStrLn $ "\n\nabout to writeFile" + writeFile astFile origAst + -- putStrLn $ "\n\nabout to pp" + writeFile newFile pped + writeFile newFileChanged pped' + + -- putStrLn $ "anns':" ++ showPprUnsafe (apiAnnRogueComments anns') + + p' <- parseOneFile libdir newFile + + let newAstStr :: String + newAstStr = showSDocUnsafe + $ showAstData BlankSrcSpanFile NoBlankApiAnnotations + (pm_parsed_source p') + writeFile newAstFile newAstStr + + -- putStrLn $ "\n\nanns':" ++ showPprUnsafe (apiAnnRogueComments anns') + + if origAst == newAstStr + then do + -- putStrLn "ASTs matched" + exitSuccess + else do + putStrLn "AST Match Failed" + -- putStrLn "\n===================================\nOrig\n\n" + -- putStrLn origAst + putStrLn "\n===================================\nNew\n\n" + putStrLn newAstStr + exitFailure + + +parseOneFile :: FilePath -> FilePath -> IO ParsedModule +parseOneFile libdir fileName = do + let modByFile m = + case ml_hs_file $ ms_location m of + Nothing -> False + Just fn -> fn == fileName + runGhc (Just libdir) $ do + dflags <- getSessionDynFlags + let dflags2 = dflags `gopt_set` Opt_KeepRawTokenStream + _ <- setSessionDynFlags dflags2 + addTarget Target { targetId = TargetFile fileName Nothing + , targetAllowObjCode = True + , targetContents = Nothing } + _ <- load LoadAllTargets + graph <- getModuleGraph + let + modSum = case filter modByFile (mgModSummaries graph) of + [x] -> x + xs -> error $ "Can't find module, got:" + ++ show (map (ml_hs_file . ms_location) xs) + parseModule modSum + +-- getPragmas :: ApiAnns -> String +-- getPragmas anns' = pragmaStr +-- where +-- tokComment (L _ (AnnBlockComment s)) = s +-- tokComment (L _ (AnnLineComment s)) = s +-- tokComment _ = "" + +-- comments' = map tokComment $ sortRealLocated $ apiAnnRogueComments anns' +-- pragmas = filter (\c -> isPrefixOf "{-#" c ) comments' +-- pragmaStr = intercalate "\n" pragmas + +-- pp :: (Outputable a) => a -> String +-- pp a = showPpr unsafeGlobalDynFlags a + +-- --------------------------------------------------------------------- + +exactprintWithChange :: Changer -> ParsedSource -> ApiAnns -> IO String +exactprintWithChange f p anns = do + (anns',p') <- f anns p + return $ exactPrint p' anns' + + +type Changer = (ApiAnns -> ParsedSource -> IO (ApiAnns,ParsedSource)) + +noChange :: Changer +noChange ans parsed = return (ans,parsed) + +changeRenameCase1 :: Changer +changeRenameCase1 ans parsed = return (ans,rename "bazLonger" [((3,15),(3,18))] parsed) + +changeLayoutLet2 :: Changer +changeLayoutLet2 ans parsed = return (ans,rename "xxxlonger" [((7,5),(7,8)),((8,24),(8,27))] parsed) + +rename :: (Data a) => String -> [(Pos, Pos)] -> a -> a +rename newNameStr spans' a + = everywhere (mkT replaceRdr) a + where + newName = mkRdrUnqual (mkVarOcc newNameStr) + + cond :: SrcSpan -> Bool + cond ln = ss2range ln `elem` spans' + + replaceRdr :: LocatedN RdrName -> LocatedN RdrName + replaceRdr (L ln _) + | cond (locA ln) = L ln newName + replaceRdr x = x + +-- --------------------------------------------------------------------- +-- From SYB + +-- | Apply transformation on each level of a tree. +-- +-- Just like 'everything', this is stolen from SYB package. +everywhere :: (forall a. Data a => a -> a) -> (forall a. Data a => a -> a) +everywhere f = f . gmapT (everywhere f) + +-- | Create generic transformation. +-- +-- Another function stolen from SYB package. +mkT :: (Typeable a, Typeable b) => (b -> b) -> (a -> a) +mkT f = case cast f of + Just f' -> f' + Nothing -> id ===================================== utils/check-exact/cases/LayoutLet2.hs ===================================== @@ -0,0 +1,9 @@ +module LayoutLet2 where + +-- Simple let expression, rename xxx to something longer or shorter +-- and the let/in layout should adjust accordingly +-- In this case the tokens for xxx + a + b should also shift out + +foo xxx = let a = 1 + b = 2 in xxx + a + b + ===================================== utils/check-exact/cases/RenameCase1.hs ===================================== @@ -0,0 +1,5 @@ +module RenameCase1 where + +foo x = case (baz x) of + 1 -> "a" + _ -> "b" ===================================== utils/check-exact/check-exact.cabal ===================================== @@ -26,7 +26,7 @@ Executable check-exact Build-Depends: base >= 4 && < 5, bytestring, containers, - Cabal >= 3.0 && < 3.4, + Cabal >= 3.0 && < 3.6, directory, filepath, ghc ===================================== utils/check-exact/src/ExactPrint.hs ===================================== @@ -36,8 +36,9 @@ import GHC.Utils.Panic import Control.Monad.Identity import Control.Monad.RWS -import Data.Data ( Data ) +import Data.Data ( Data, toConstr, typeOf, showsTypeRep ) import Data.Foldable +import Data.Typeable import Data.List ( partition, intercalate, sort, sortBy) import Data.Maybe (fromMaybe, isJust, maybeToList) -- import Data.Ord (comparing) @@ -76,13 +77,16 @@ xx = id defaultEPState :: ApiAnns -> EPState defaultEPState as = EPState - { epPos = (1,1) - , epAnns = Map.empty - , epApiAnns = as - , epAnnKds = [] - , epLHS = 0 + { epPos = (1,1) + , epApiAnns = as + , epLHS = 0 + , epAnchorLHS = 0 , epMarkLayout = False - , priorEndPosition = (1,1) + -- , priorEndPosition = (1,1) + , priorEndPositionE = (1,1) + , anchorSpan = badRealSrcSpan + , prevAnchorPos = (1,1) + , origPos = (1,1) , epComments = rogueComments as } @@ -134,14 +138,23 @@ instance Monoid w => Monoid (EPWriter w) where (EPWriter a) `mappend` (EPWriter b) = EPWriter (a <> b) data EPState = EPState - { epPos :: !Pos -- ^ Current output position - , epAnns :: !Anns - , epApiAnns :: !ApiAnns - , epAnnKds :: ![[(KeywordId, DeltaPos)]] -- MP: Could this be moved to the local statE w mith suitable refactoring? + { epPos :: !Pos -- ^ Current output position + , epApiAnns :: !ApiAnns , epMarkLayout :: Bool - , epLHS :: LayoutStartCol - , priorEndPosition :: !Pos -- ^ Position reached when + , epLHS :: LayoutStartCol + , epAnchorLHS :: LayoutStartCol + , priorEndPositionE :: !Pos -- ^ End of Position reached when -- processing the last element + , anchorSpan :: !RealSrcSpan -- ^ in pre-changed AST + -- reference frame, from + -- Annotation + , prevAnchorPos :: !Pos -- ^ Previous start of anchor + -- position. Only advance to + -- start of anchor if this has + -- changed. + , origPos :: !Pos -- ^ Current output position in + -- original annotation, used to + -- calculate DPs , epComments :: ![Comment] } @@ -179,31 +192,73 @@ instance HasEntry (ApiAnn' a) where enterAnn :: (ExactPrint a) => Entry -> a -> Annotated () enterAnn NoEntryVal a = do p <- getPos - debugM $ "enterAnn:NO ANN:p =" ++ show p + debugM $ "enterAnn:NO ANN:(p,a) =" ++ show p ++ " starting" exact a -enterAnn (Entry anchor cs) a = do + debugM $ "enterAnn:NO ANN:p =" ++ show p ++ " done" +enterAnn (Entry anchor' cs) a = do + -- NOTE: in time anchor will note if it has moved, for now we assume + -- both values are the same + let topAnchor = anchor' -- To control spacing to get into this AST element + let curAnchor = anchor' -- As a base for the current AST element + -- -- ----------------------------------------------- + -- -- Advance by any discrepance between origPos and topAnchor + -- op <- getOrigPos + -- p <- getPos + -- let dp = pos2delta op (ss2pos topAnchor) + -- debugM $ "enterAnn:(op,p,topAnchor,dp)=" ++ show (op,p,rs2range topAnchor,dp) + -- advance dp + -- -- We are now cleanly in the current context + -- -- ------------------------------------------- + layout <- gets epMarkLayout + debugM $ "enterAnn:(topAnchor,curAnchor,layout)=" ++ show (rs2range topAnchor,rs2range curAnchor,layout) + p'' <- getPos + op'' <- getOrigPos + let delta = (snd op'') - (snd p'') + debugM $ "enterAnn:(pos,origpos,delta)=" ++ show (p'',op'',delta) + printComments curAnchor + setAnchor curAnchor + setOrigPos (ss2pos curAnchor) -- We assume we are now aligned with the anchor + p' <- getPos addCommentsA cs - printComments anchor + -- printComments curAnchor p <- getPos - debugM $ "enterAnn:(anchor(pos),p)=" ++ show (ss2pos(anchor),p) -- do all the machinery of advancing to the anchor, with a local etc -- modelled on exactpc (which is normally called via withast -- First thing is to calculate the entry DeltaPos. This is based on -- the current position, and the anchor. - -- off <- gets apLayoutStart off <- gets epLHS - priorEndAfterComments <- getPos - let ss = anchor - let edp = adjustDeltaForOffset + let ss = curAnchor + op <- getOrigPos + oldAnchorOffset <- getAnchorOffset +--------------------------- + priorEndAfterCommentsE <- getPriorEndE + pap <- getPrevAnchorPos + debugM $ "enterAnn:(curAnchor,pec,p,p',delta)=" ++ show (ss2pos curAnchor,priorEndAfterCommentsE,p,p',delta) +---------------------------- + -- NOTE: edp only uses the *original* ast spacing, i.e. the gap + -- between the end of the previous leaf span, and the start of the + -- next leaf span + debugM $ "enterAnn:(ss2delta priorEndAfterCommentsE curAnchor)=" ++ show (ss2delta priorEndAfterCommentsE curAnchor) + + let edp' = adjustDeltaForOffset delta -- Use the propagated offset if one is set -- Note that we need to use the new offset if it has -- changed. - off (ss2delta priorEndAfterComments ss) + -- off (ss2delta priorEndAfterCommentsE curAnchor) + oldAnchorOffset (ss2delta priorEndAfterCommentsE curAnchor) + edp = if pap /= (ss2pos curAnchor) -- new leaf node + then edp' else DP (0,0) + debugM $ "enterAnn:(p,ss,edp,edp',op,pap,off,oldAnchorOffset)=" ++ show (p,ss2pos ss,edp,edp',op,pap,off,oldAnchorOffset) + modify (\s -> s { prevAnchorPos = ss2pos curAnchor} ) let st = annNone { annEntryDelta = edp } + withOffset st (advance edp >> exact a) + -- NOTE: any resets happening here should probably move into the + -- 'withOffset" call above. + setAnchorOffset oldAnchorOffset -- --------------------------------------------------------------------- @@ -248,7 +303,7 @@ sr s = RealSrcSpan s Nothing -- Temporary function to simply reproduce the "normal" pretty printer output withPpr :: (Outputable a) => a -> Annotated () -withPpr a = printString False (showPprUnsafe a) +withPpr a = printStringAdvance (showPprUnsafe a) -- --------------------------------------------------------------------- -- Modeled on Outputable @@ -273,6 +328,7 @@ instance (ExactPrint a) => ExactPrint (Located a) where instance (ExactPrint a) => ExactPrint (LocatedA a) where getAnnotationEntry = entryFromLocatedA exact (L la a) = do + debugM $ "LocatedA a:la loc=" ++ show (ss2range $ locA la) markAnnotated a markALocatedA (ann la) @@ -301,13 +357,15 @@ instance ExactPrint HsModule where Just (L ln mn) -> do markApiAnn' an am_main AnnModule -- debugM $ "HsModule name: (ss,ln)=" ++ show (ss2pos ss,ss2pos (realSrcSpan ln)) - printStringAtSs ln (moduleNameString mn) + -- printStringAtSs ln (moduleNameString mn) + markAnnotated (L ln mn) -- forM_ mdeprec markLocated markAnnotated mdeprec markAnnotated mexports + debugM $ "HsModule.AnnWhere coming" markApiAnn' an am_main AnnWhere -- markApiAnn (am_main anns) AnnWhere @@ -319,7 +377,8 @@ instance ExactPrint HsModule where markListWithLayout imports -- setContextLevel (Set.singleton TopLevel) 2 $ markListWithLayout decls - markListWithLayout decls + -- markListWithLayout decls + markAnnotated decls mapM_ markAddApiAnn (al_close $ am_decls $ anns an) -- markOptional GHC.AnnCloseC -- Possible '}' @@ -334,35 +393,62 @@ instance ExactPrint HsModule where -- --------------------------------------------------------------------- printSourceText :: SourceText -> String -> EPP () -printSourceText NoSourceText txt = printString False txt -printSourceText (SourceText txt) _ = printString False txt +printSourceText NoSourceText txt = printStringAdvance txt +printSourceText (SourceText txt) _ = printStringAdvance txt -- --------------------------------------------------------------------- +printStringAtRs :: RealSrcSpan -> String -> EPP () +printStringAtRs ss str = printStringAtKw' ss str + printStringAtSs :: SrcSpan -> String -> EPP () printStringAtSs ss str = printStringAtKw' (realSrcSpan ss) str -- --------------------------------------------------------------------- --- printStringAtKw :: ApiAnn' ann -> AnnKeywordId -> String -> EPP () --- printStringAtKw ApiAnnNotUsed _ str = printString True str --- printStringAtKw (ApiAnn anchor anns _cs) kw str = do --- case find (\(AddApiAnn k _) -> k == kw) anns of --- Nothing -> printString True str --- Just (AddApiAnn _ ss) -> printStringAtKw' ss str - -- AZ:TODO get rid of this printStringAtMkw :: Maybe RealSrcSpan -> String -> EPP () printStringAtMkw (Just r) s = printStringAtKw' r s -printStringAtMkw Nothing s = printStringAtLsDelta [] (DP (0,1)) s +printStringAtMkw Nothing s = printStringAtLsDelta (DP (0,1)) s printStringAtKw' :: RealSrcSpan -> String -> EPP () printStringAtKw' ss str = do + -- This needs to have the same update mechanic as for printStringAdvance printComments ss - dp <- nextDP ss + anchor <- getAnchor + op <- getOrigPos + dp <- nextDPAnchor ss p <- getPos - debugM $ "printStringAtKw': (dp,p) = " ++ show (dp,p) - printStringAtLsDelta [] dp str + debugM $ "printStringAtKw': (dp,p,pe,a,op) = " ++ show (dp,p,ss2posEnd ss,rs2range anchor,op) + setPriorEndE (ss2posEnd ss) + setOrigPos (ss2posEnd ss) + printStringAtLsDelta dp str + +-- | Print a string, advancing origPos by the same amount as the pos +-- advances. Complicated because the string may have newlines in it +printStringAdvance :: String -> EPP () +printStringAdvance str = adaptStateForPrintString (printString str) + +adaptStateForPrintString :: (Monad m, Monoid w) => EP w m () -> EP w m () +adaptStateForPrintString printer = do + op <- getOrigPos + p1 <- getPos + printer + p2 <- getPos + let dp = pos2delta p1 p2 + -- colOffset <- getLayoutOffset + colOffset <- getAnchorOffset + let op2 = undelta op dp colOffset + debugM $ "adaptStateForPrintString:(op,p1,p2,dp,op2)=" ++ show (op,p1,p2,dp,op2) + setPriorEndNoLayout op2 + setOrigPos op2 + +adaptPos dp = do + op <- getOrigPos + -- colOffset <- getLayoutOffset + colOffset <- getAnchorOffset + let op2 = undelta op dp colOffset + setOrigPos op2 -- --------------------------------------------------------------------- @@ -418,13 +504,6 @@ markLocatedAALS (ApiAnn _ a _) f kw (Just str) = go (f a) markArrow :: ApiAnn' TrailingAnn -> (HsArrow GhcPs) -> EPP () markArrow ApiAnnNotUsed _ = pure () markArrow an mult = markKwT (anns an) - -- = case mult of - -- HsLinearArrow -> markApiAnn an AnnLolly - -- HsUnrestrictedArrow -> markApiAnn an AnnRarrow - -- HsExplicitMult p -> do - -- printString False "#" - -- markAnnotated p - -- markApiAnn an AnnRarrow -- --------------------------------------------------------------------- @@ -514,13 +593,7 @@ markKw (AddApiAnn kw ss) = markKw' kw ss -- | This should be the main driver of the process, managing comments markKw' :: AnnKeywordId -> RealSrcSpan -> EPP () -markKw' kw ss = do - p' <- getPos - printComments ss - dp <- nextDP ss - p <- getPos - debugM $ "markKw: (dp,p,p') = " ++ show (dp,p,p') - printStringAtLsDelta [] dp (keywordToString (G kw)) +markKw' kw ss = printStringAtKw' ss (keywordToString (G kw)) -- --------------------------------------------------------------------- @@ -594,6 +667,15 @@ nextDP ss = do p <- getPos return $ pos2delta p (ss2pos ss) +nextDPAnchor :: RealSrcSpan -> EPP DeltaPos +nextDPAnchor ss = do + anchor <- getAnchor + op <- getOrigPos + let dp = pos2delta op (ss2pos ss) + -- return $ pos2delta (ss2pos anchor) (ss2pos ss) + debugM $ "nextDPAnchor:(dp,op,ss,anchor)=" ++ show (dp,op,rs2range ss,rs2range anchor) + return dp + -- --------------------------------------------------------------------- markListWithLayout :: ExactPrint (LocatedA ast) => [LocatedA ast] -> EPP () @@ -948,7 +1030,7 @@ instance ExactPrint FastString where getAnnotationEntry = const NoEntryVal -- TODO: https://ghc.haskell.org/trac/ghc/ticket/10313 applies. - exact fs = printString False (show (unpackFS fs)) + exact fs = printStringAdvance (show (unpackFS fs)) -- --------------------------------------------------------------------- @@ -1048,7 +1130,7 @@ instance ExactPrint DocDecl where (DocCommentNamed _s ds) -> unpackHDS ds (DocGroup _i ds) -> unpackHDS ds in - printString False str + printStringAdvance str -- --------------------------------------------------------------------- @@ -1426,7 +1508,7 @@ exactMatch (Match an mctxt pats grhss) = do markApiAnn an AnnLam mapM_ markAnnotated pats GHC.CaseAlt -> do - mapM_ markAnnotated pats + markAnnotated pats _ -> withPpr mctxt markAnnotated grhss @@ -1434,22 +1516,17 @@ exactMatch (Match an mctxt pats grhss) = do -- --------------------------------------------------------------------- instance ExactPrint (GRHSs GhcPs (LocatedA (HsExpr GhcPs))) where - getAnnotationEntry (GRHSs an _ _) = fromAnn an + getAnnotationEntry (GRHSs _ _ _) = NoEntryVal exact (GRHSs an grhss binds) = do - debugM $ "GRHSs: before matchSeparator" - markLocatedAA an id -- Mark the matchSeparator for these GRHSs - debugM $ "GRHSs: after matchSeparator" markAnnotated grhss markAnnotated binds + instance ExactPrint (GRHSs GhcPs (LocatedA (HsCmd GhcPs))) where - getAnnotationEntry (GRHSs an _ _) = fromAnn an + getAnnotationEntry (GRHSs _ _ _) = NoEntryVal exact (GRHSs an grhss binds) = do - debugM $ "GRHSs: before matchSeparator" - markLocatedAA an id -- Mark the matchSeparator for these GRHSs - debugM $ "GRHSs: after matchSeparator" markAnnotated grhss markAnnotated binds @@ -1499,7 +1576,7 @@ instance ExactPrint (IPBind GhcPs) where instance ExactPrint HsIPName where getAnnotationEntry = const NoEntryVal - exact (HsIPName fs) = printString False ("?" ++ (unpackFS fs)) + exact (HsIPName fs) = printStringAdvance ("?" ++ (unpackFS fs)) -- --------------------------------------------------------------------- @@ -1507,7 +1584,7 @@ instance ExactPrint (HsValBindsLR GhcPs GhcPs) where getAnnotationEntry _ = NoEntryVal exact (ValBinds sortkey binds sigs) = do - -- printString False "ValBinds" + -- printStringAdvance "ValBinds" applyListAnnotations (prepareListAnnotationA (bagToList binds) ++ prepareListAnnotationA sigs @@ -1780,7 +1857,9 @@ instance ExactPrint (GRHS GhcPs (LocatedA (HsExpr GhcPs))) where exact (GRHS an guards expr) = do markAnnKwM an ga_vbar AnnVbar markAnnotated guards + debugM $ "GRHS before matchSeparator" markLocatedAA an ga_sep -- Mark the matchSeparator for these GRHSs + debugM $ "GRHS after matchSeparator" markAnnotated expr -- markLocatedAA an ga_sep @@ -1848,7 +1927,7 @@ instance ExactPrint (HsExpr GhcPs) where -- exact x@(HsRecFld{}) = withPpr x -- exact x@(HsOverLabel ann _ _) = withPpr x exact (HsIPVar _ (HsIPName n)) - = printString False ("?" ++ unpackFS n) + = printStringAdvance ("?" ++ unpackFS n) exact x@(HsOverLit ann ol) = do let str = case ol_val ol of @@ -1857,7 +1936,7 @@ instance ExactPrint (HsExpr GhcPs) where HsIsString src _ -> src -- markExternalSourceText l str "" case str of - SourceText s -> printString False s + SourceText s -> printStringAdvance s NoSourceText -> withPpr x exact (HsLit ann lit) = withPpr lit @@ -1897,9 +1976,9 @@ instance ExactPrint (HsExpr GhcPs) where exact x@(HsPar an e) = do markOpeningParen an markAnnotated e - -- debugM $ "HsPar closing paren" + debugM $ "HsPar closing paren" markClosingParen an - -- debugM $ "HsPar done" + debugM $ "HsPar done" -- exact (SectionL an expr op) = do exact (SectionR an op expr) = do @@ -1929,7 +2008,7 @@ instance ExactPrint (HsExpr GhcPs) where markAnnKw an hsCaseAnnOf AnnOf markApiAnn' an hsCaseAnnsRest AnnOpenC markApiAnnAll an hsCaseAnnsRest AnnSemi - markAnnotated alts + setLayout $ markAnnotated alts markApiAnn' an hsCaseAnnsRest AnnCloseC -- exact x@(HsCase ApiAnnNotUsed _ _) = withPpr x @@ -1950,9 +2029,12 @@ instance ExactPrint (HsExpr GhcPs) where exact (HsLet an binds e) = do markApiAnn an AnnLet markApiAnn an AnnOpenC -- '{' - markAnnotated binds + debugM $ "HSlet:binds coming" + setLayout $ markAnnotated binds + debugM $ "HSlet:binds done" markApiAnn an AnnCloseC -- '}' markApiAnn an AnnIn + debugM $ "HSlet:expr coming" markAnnotated e exact (HsDo an do_or_list_comp stmts) = do @@ -2142,7 +2224,7 @@ instance ExactPrint (HsSplice GhcPs) where -- = ppr_splice empty n e empty exact (HsQuasiQuote _ _ q _ss fs) = do - printString False + printStringAdvance -- Note: Lexer.x does not provide unicode alternative. 2017-02-26 ("[" ++ (showPprUnsafe q) ++ "|" ++ (unpackFS fs) ++ "|]") @@ -2222,7 +2304,7 @@ instance ExactPrint (HsTupArg GhcPs) where exact (Present _ e) = markAnnotated e exact (Missing ApiAnnNotUsed) = return () - exact (Missing _) = printString False "," + exact (Missing _) = printStringAdvance "," -- --------------------------------------------------------------------- @@ -2402,12 +2484,12 @@ instance ExactPrint (HsCmd GhcPs) where instance (ExactPrint (LocatedA body)) => ExactPrint (StmtLR GhcPs GhcPs (LocatedA body)) where -- instance ExactPrint (StmtLR GhcPs GhcPs (LocatedA (HsCmd GhcPs))) where - getAnnotationEntry (LastStmt _ _ _ _) = NoEntryVal + getAnnotationEntry (LastStmt _ _ _ _) = NoEntryVal getAnnotationEntry (BindStmt an _ _) = fromAnn an - getAnnotationEntry (ApplicativeStmt an _ _) = NoEntryVal - getAnnotationEntry (BodyStmt an _ _ _) = NoEntryVal + getAnnotationEntry (ApplicativeStmt _ _ _) = NoEntryVal + getAnnotationEntry (BodyStmt _ _ _ _) = NoEntryVal getAnnotationEntry (LetStmt an _) = fromAnn an - getAnnotationEntry (ParStmt an _ _ _) = NoEntryVal + getAnnotationEntry (ParStmt _ _ _ _) = NoEntryVal getAnnotationEntry (TransStmt an _ _ _ _ _ _ _ _) = fromAnn an getAnnotationEntry (RecStmt an _ _ _ _ _ _) = fromAnn an @@ -2515,7 +2597,7 @@ instance (ExactPrint (LocatedA body)) -- markTrailingSemi -- exact x = error $ "exact CmdLStmt for:" ++ showAst x - exact x = error $ "exact CmdLStmt for:" + -- exact x = error $ "exact CmdLStmt for:" -- --------------------------------------------------------------------- @@ -2690,7 +2772,7 @@ instance ExactPrint (TyClDecl GhcPs) where -- = error "extension hit for TyClDecl" -- markAST _ (GHC.XTyClDecl _) -- = error "extension hit for TyClDecl" - exact x = error $ "exact TyClDecl for:" ++ showAst x + -- exact x = error $ "exact TyClDecl for:" ++ showAst x -- --------------------------------------------------------------------- @@ -2719,7 +2801,7 @@ instance ExactPrint (FamilyDecl GhcPs) where markApiAnn an AnnWhere markApiAnn an AnnOpenC case mb_eqns of - Nothing -> printString False ".." + Nothing -> printStringAdvance ".." Just eqns -> markAnnotated eqns markApiAnn an AnnCloseC _ -> return () @@ -2887,7 +2969,7 @@ instance ExactPrint (HsType GhcPs) where getAnnotationEntry (HsWildCardTy _) = NoEntryVal - exact (HsForAllTy { hst_xforall = an + exact (HsForAllTy { hst_xforall = _an , hst_tele = tele, hst_body = ty }) = do markAnnotated tele markAnnotated ty @@ -2900,9 +2982,9 @@ instance ExactPrint (HsType GhcPs) where when (promoted == IsPromoted) $ markApiAnn an AnnSimpleQuote markAnnotated name - exact x@(HsAppTy _ t1 t2) = markAnnotated t1 >> markAnnotated t2 - exact x@(HsAppKindTy an _ _) = withPpr x - exact x@(HsFunTy an mult ty1 ty2) = do + exact (HsAppTy _ t1 t2) = markAnnotated t1 >> markAnnotated t2 + exact x@(HsAppKindTy _an _ _) = withPpr x + exact (HsFunTy an mult ty1 ty2) = do markAnnotated ty1 markArrow an mult markAnnotated ty2 @@ -2918,7 +3000,7 @@ instance ExactPrint (HsType GhcPs) where markOpeningParen an markAnnotated tys markClosingParen an - exact (HsOpTy an t1 lo t2) = do + exact (HsOpTy _an t1 lo t2) = do markAnnotated t1 markAnnotated lo markAnnotated t2 @@ -2926,14 +3008,14 @@ instance ExactPrint (HsType GhcPs) where markOpeningParen an markAnnotated ty markClosingParen an - exact x@(HsIParamTy an n t) = do + exact (HsIParamTy an n t) = do markAnnotated n markApiAnn an AnnDcolon markAnnotated t - exact (HsStarTy an isUnicode) + exact (HsStarTy _an isUnicode) = if isUnicode - then printString False "\x2605" -- Unicode star - else printString False "*" + then printStringAdvance "\x2605" -- Unicode star + else printStringAdvance "*" exact (HsKindSig an ty k) = do exact ty markApiAnn an AnnDcolon @@ -2969,7 +3051,7 @@ instance ExactPrint (HsType GhcPs) where case lit of (HsNumTy src v) -> printSourceText src (show v) (HsStrTy src v) -> printSourceText src (show v) - exact (HsWildCardTy _) = printString False "_" + exact (HsWildCardTy _) = printStringAdvance "_" exact x = error $ "missing match for HsType:" ++ showAst x -- --------------------------------------------------------------------- @@ -3076,8 +3158,10 @@ instance ExactPrint (HsSigType GhcPs) where instance ExactPrint (LocatedN RdrName) where getAnnotationEntry (L sann _) = fromAnn sann - exact (L (SrcSpanAnn ApiAnnNotUsed _) n) = do - printString False (showPprUnsafe n) + exact (L (SrcSpanAnn ApiAnnNotUsed l) n) = do + p <- getPos + debugM $ "LocatedN RdrName:NOANN: (p,l,str)=" ++ show (p,ss2range l, showPprUnsafe n) + printStringAtSs l (showPprUnsafe n) exact (L (SrcSpanAnn (ApiAnn _anchor ann _cs) ll) n) = do case ann of NameAnn a o l c t -> do @@ -3100,7 +3184,7 @@ instance ExactPrint (LocatedN RdrName) where markAnnotated (L (SrcSpanAnn name ll) n) markTrailing t NameAnnTrailing t -> do - printString False (showPprUnsafe n) + printStringAdvance (showPprUnsafe n) markTrailing t markName :: NameAdornment @@ -3133,12 +3217,12 @@ exact_condecls an cs | gadt_syntax -- In GADT syntax -- = hang (text "where") 2 (vcat (map ppr cs)) = do - -- printString False "exact_condecls:gadt" + -- printStringAdvance "exact_condecls:gadt" mapM_ markAnnotated cs | otherwise -- In H98 syntax -- = equals <+> sep (punctuate (text " |") (map ppr cs)) = do - -- printString False "exact_condecls:not gadt" + -- printStringAdvance "exact_condecls:not gadt" markApiAnn an AnnEqual mapM_ markAnnotated cs where @@ -3210,8 +3294,8 @@ instance ExactPrint (ConDecl GhcPs) where when (isJust mcxt) $ markApiAnn an AnnDarrow -- mapM_ markAnnotated args case args of - (PrefixConGADT args) -> mapM_ markAnnotated args - (RecConGADT fields) -> markAnnotated fields + (PrefixConGADT args') -> mapM_ markAnnotated args' + (RecConGADT fields) -> markAnnotated fields -- mapM_ markAnnotated (unLoc fields) markAnnotated res_ty -- markAST _ (GHC.ConDeclGADT _ lns (GHC.L l forall) qvars mbCxt args typ _) = do @@ -3315,7 +3399,7 @@ instance ExactPrint (LocatedP CType) where getAnnotationEntry = entryFromLocatedA exact (L (SrcSpanAnn ApiAnnNotUsed _) ct) = withPpr ct - exact (L (SrcSpanAnn an ll) + exact (L (SrcSpanAnn an _ll) (CType stp mh (stct,ct))) = do markAnnOpenP an stp "{-# CTYPE" case mh of @@ -3345,7 +3429,7 @@ instance ExactPrint (SourceText, RuleName) where getAnnotationEntry = const NoEntryVal exact (st, rn) - = printString False (toSourceTextWithSuffix st (unpackFS rn) "") + = printStringAdvance (toSourceTextWithSuffix st (unpackFS rn) "") -- ===================================================================== @@ -3408,7 +3492,7 @@ instance ExactPrint (LocatedL [LocatedA (StmtLR GhcPs GhcPs (LocatedA (HsExpr Gh markAnnList an $ do -- markLocatedMAA an al_open case snocView stmts of - Just (initStmts, ls@(L _ (LastStmt _ body _ _))) -> do + Just (initStmts, ls@(L _ (LastStmt _ _body _ _))) -> do debugM $ "LocatedL [ExprLStmt: snocView" markAnnotated ls markAnnotated initStmts @@ -3459,7 +3543,7 @@ instance ExactPrint (IE GhcPs) where markApiAnn an AnnDotdot markApiAnn an AnnCloseP - exact (IEThingWith an thing wc withs flds) = do + exact (IEThingWith an thing wc withs _flds) = do markAnnotated thing markApiAnn an AnnOpenP case wc of @@ -3525,12 +3609,14 @@ instance ExactPrint (Pat GhcPs) where getAnnotationEntry (ViewPat an _ _) = fromAnn an getAnnotationEntry (SplicePat _ _) = NoEntryVal getAnnotationEntry (LitPat _ _) = NoEntryVal - getAnnotationEntry (NPat _ _ _ _) = NoEntryVal + getAnnotationEntry (NPat an _ _ _) = fromAnn an getAnnotationEntry (NPlusKPat an _ _ _ _ _) = fromAnn an getAnnotationEntry (SigPat an _ _) = fromAnn an - - exact (WildPat _) = printString False "_" + exact (WildPat _) = do + anchor <- getAnchor + debugM $ "WildPat:anchor=" ++ show anchor + printStringAtRs anchor "_" exact (VarPat _ n) = do -- The parser inserts a placeholder value for a record pun rhs. This must be -- filtered. @@ -3558,7 +3644,7 @@ instance ExactPrint (Pat GhcPs) where Boxed -> markApiAnn an AnnCloseP Unboxed -> markApiAnn an AnnClosePH - exact (SumPat an pat alt arity) = do + exact (SumPat an pat _alt _arity) = do markLocatedAAL an sumPatParens AnnOpenPH markAnnKwAll an sumPatVbarsBefore AnnVbar markAnnotated pat @@ -3578,7 +3664,7 @@ instance ExactPrint (Pat GhcPs) where markApiAnn an AnnRarrow markAnnotated pat exact (SplicePat _ splice) = markAnnotated splice - exact (LitPat _ lit) = printString False (hsLit2String lit) + exact (LitPat _ lit) = printStringAdvance (hsLit2String lit) exact (NPat an ol mn _) = do when (isJust mn) $ markApiAnn an AnnMinus markAnnotated ol @@ -3699,7 +3785,7 @@ instance ExactPrint (HsOverLit GhcPs) where HsIsString src _ -> src in case str of - SourceText s -> printString False s + SourceText s -> printStringAdvance s NoSourceText -> return () -- --------------------------------------------------------------------- @@ -3756,165 +3842,36 @@ entryFromLocatedA (L la _) = fromAnn la -- ===================================================================== -- Utility stuff --- annNone :: Annotation --- annNone = Ann (DP (0,0)) [] [] [] Nothing Nothing - --- -- --------------------------------------------------------------------- --- -- | Calculates the distance from the start of a string to the end of --- -- a string. --- dpFromString :: String -> DeltaPos --- dpFromString xs = dpFromString' xs 0 0 --- where --- dpFromString' "" line col = DP (line, col) --- dpFromString' ('\n': cs) line _ = dpFromString' cs (line + 1) 0 --- dpFromString' (_:cs) line col = dpFromString' cs line (col + 1) - --- --------------------------------------------------------------------- --- --------------------------------------------------------------------- - --- --------------------------------------------------------------------- - --- | Put the provided context elements into the existing set with fresh level --- counts --- setAcs :: Set.Set AstContext -> AstContextSet -> AstContextSet --- setAcs ctxt acs = setAcsWithLevel ctxt 3 acs - --- -- | Put the provided context elements into the existing set with given level --- -- counts --- -- setAcsWithLevel :: Set.Set AstContext -> Int -> AstContextSet -> AstContextSet --- -- setAcsWithLevel ctxt level (ACS a) = ACS a' --- -- where --- -- upd s (k,v) = Map.insert k v s --- -- a' = foldl' upd a $ zip (Set.toList ctxt) (repeat level) --- setAcsWithLevel :: (Ord a) => Set.Set a -> Int -> ACS' a -> ACS' a --- setAcsWithLevel ctxt level (ACS a) = ACS a' --- where --- upd s (k,v) = Map.insert k v s --- a' = foldl' upd a $ zip (Set.toList ctxt) (repeat level) - --- --------------------------------------------------------------------- --- | Remove the provided context element from the existing set --- unsetAcs :: AstContext -> AstContextSet -> AstContextSet --- unsetAcs :: (Ord a) => a -> ACS' a -> ACS' a --- unsetAcs ctxt (ACS a) = ACS $ Map.delete ctxt a - --- --------------------------------------------------------------------- - --- | Are any of the contexts currently active? --- inAcs :: Set.Set AstContext -> AstContextSet -> Bool --- inAcs :: (Ord a) => Set.Set a -> ACS' a -> Bool --- inAcs ctxt (ACS a) = not $ Set.null $ Set.intersection ctxt (Set.fromList $ Map.keys a) - --- -- | propagate the ACS down a level, dropping all values which hit zero --- -- pushAcs :: AstContextSet -> AstContextSet --- pushAcs :: ACS' a -> ACS' a --- pushAcs (ACS a) = ACS $ Map.mapMaybe f a --- where --- f n --- | n <= 1 = Nothing --- | otherwise = Just (n - 1) - --- |Sometimes we have to pass the context down unchanged. Bump each count up by --- one so that it is unchanged after a @pushAcs@ call. --- bumpAcs :: AstContextSet -> AstContextSet --- bumpAcs :: ACS' a -> ACS' a --- bumpAcs (ACS a) = ACS $ Map.mapMaybe f a --- where --- f n = Just (n + 1) - - --- --------------------------------------------------------------------- --- --------------------------------------------------------------------- - --- printStringAtMaybeAnn :: (Monad m, Monoid w) => KeywordId -> Maybe String -> EP w m () --- printStringAtMaybeAnn an mstr = printStringAtMaybeAnnThen an mstr (return ()) - --- -- printStringAtMaybeAnnAll :: (Monad m, Monoid w) => KeywordId -> Maybe String -> EP w m () --- -- printStringAtMaybeAnnAll an mstr = go --- -- where --- -- go = printStringAtMaybeAnnThen an mstr go - --- printStringAtMaybeAnnThen :: (Monad m, Monoid w) --- => KeywordId -> Maybe String -> EP w m () -> EP w m () --- printStringAtMaybeAnnThen an mstr next = do --- let str = fromMaybe (keywordToString an) mstr --- annFinal <- getAnnFinal an --- case (annFinal, an) of --- -- Could be unicode syntax --- -- TODO: This is a bit fishy, refactor --- (Nothing, G kw') -> do --- let kw = unicodeAnn kw' --- let str' = fromMaybe (keywordToString (G kw)) mstr --- res <- getAnnFinal (G kw) --- return () `debug` ("printStringAtMaybeAnn:missed:Unicode:(an,res)" ++ show (an,res)) --- unless (null res) $ do --- forM_ --- res --- (\(comments, ma) -> printStringAtLsDelta comments ma str') --- next --- (Just (comments, ma),_) -> printStringAtLsDelta comments ma str >> next --- (Nothing, _) -> return () `debug` ("printStringAtMaybeAnn:missed:(an)" ++ show an) --- -- Note: do not call next, nothing to chain --- -- ++AZ++: Enabling the following line causes a very weird error associated with AnnPackageName. I suspect it is because it is forcing the evaluation of a non-existent an or str --- -- `debug` ("printStringAtMaybeAnn:(an,ma,str)=" ++ show (an,ma,str)) - -- --------------------------------------------------------------------- -- |This should be the final point where things are mode concrete, --- before output. Hence the point where comments can be inserted -printStringAtLsDelta :: (Monad m, Monoid w) => [(Comment, DeltaPos)] -> DeltaPos -> String -> EP w m () -printStringAtLsDelta cs cl s = do +-- before output. +printStringAtLsDelta :: (Monad m, Monoid w) => DeltaPos -> String -> EP w m () +printStringAtLsDelta cl s = do p <- getPos - colOffset <- getLayoutOffset + -- colOffset <- getLayoutOffset + colOffset <- getAnchorOffset if isGoodDeltaWithOffset cl colOffset then do - mapM_ (uncurry printQueuedComment) cs printStringAt (undelta p cl colOffset) s `debug` ("printStringAtLsDelta:(pos,s):" ++ show (undelta p cl colOffset,s)) else return () `debug` ("printStringAtLsDelta:bad delta for (mc,s):" ++ show (cl,s)) -- --------------------------------------------------------------------- --- -- |destructive get, hence use an annotation once only --- getAnnFinal :: (Monad m, Monoid w) --- => KeywordId -> EP w m (Maybe ([(Comment, DeltaPos)], DeltaPos)) --- getAnnFinal kw = do --- kd <- gets epAnnKds --- case kd of --- [] -> return Nothing -- Should never be triggered --- (k:kds) -> do --- let (res, kd') = destructiveGetFirst kw ([],k) --- modify (\s -> s { epAnnKds = kd' : kds }) --- return res - --- -- | Get and remove the first item in the (k,v) list for which the k matches. --- -- Return the value, together with any comments skipped over to get there. --- destructiveGetFirst :: KeywordId --- -> ([(KeywordId, v)],[(KeywordId,v)]) --- -> (Maybe ([(Comment, v)], v),[(KeywordId,v)]) --- destructiveGetFirst _key (acc,[]) = (Nothing, acc) --- destructiveGetFirst key (acc, (k,v):kvs ) --- | k == key = (Just (skippedComments, v), others ++ kvs) --- | otherwise = destructiveGetFirst key (acc ++ [(k,v)], kvs) --- where --- (skippedComments, others) = foldr comments ([], []) acc --- comments (AnnComment comment' , dp ) (cs, kws) = ((comment', dp) : cs, kws) --- comments kw (cs, kws) = (cs, kw : kws) - - - isGoodDeltaWithOffset :: DeltaPos -> LayoutStartCol -> Bool isGoodDeltaWithOffset dp colOffset = isGoodDelta (DP (undelta (0,0) dp colOffset)) printQueuedComment :: (Monad m, Monoid w) => Comment -> DeltaPos -> EP w m () printQueuedComment Comment{commentContents} dp = do p <- getPos - colOffset <- getLayoutOffset + -- colOffset <- getLayoutOffset + colOffset <- getAnchorOffset let (dr,dc) = undelta (0,0) dp colOffset debugM $ "printQueuedComment: (p,dp,colOffset,undelta)=" ++ show (p,dp,colOffset,undelta p dp colOffset) -- do not lose comments against the left margin when (isGoodDelta (DP (dr,max 0 dc))) $ - printCommentAt (undelta p dp colOffset) commentContents + adaptStateForPrintString (printCommentAt (undelta p dp colOffset) commentContents) -- --------------------------------------------------------------------- @@ -3934,33 +3891,73 @@ withOffset :: (Monad m, Monoid w) => Annotation -> (EP w m a -> EP w m a) withOffset a = local (\s -> s { epAnn = a, epContext = pushAcs (epContext s) }) - --- --------------------------------------------------------------------- --- --- Necessary as there are destructive gets of Kds across scopes --- withKds :: (Monad m, Monoid w) => [(KeywordId, DeltaPos)] -> EP w m a -> EP w m a --- withKds kd action = do --- modify (\s -> s { epAnnKds = kd : epAnnKds s }) --- r <- action --- modify (\s -> s { epAnnKds = tail (epAnnKds s) }) --- return r - ------------------------------------------------------------------------ setLayout :: (Monad m, Monoid w) => EP w m () -> EP w m () setLayout k = do oldLHS <- gets epLHS + debugM $ "setLayout: oldLHS=" ++ show oldLHS modify (\a -> a { epMarkLayout = True } ) - let reset = modify (\a -> a { epMarkLayout = False - , epLHS = oldLHS } ) + let reset = do + debugM $ "setLayout:reset: oldLHS=" ++ show oldLHS + modify (\a -> a { epMarkLayout = False + , epLHS = oldLHS } ) k <* reset +-- TODO:AZ: we are storing the epLHS here. and also in +-- printString. One of them is redundant +setLayoutStartIfNeeded :: (Monad m, Monoid w) => Int -> EP w m () +setLayoutStartIfNeeded p = do + markLayout <- gets epMarkLayout + when markLayout $ do + lp <- getPos + let lc = snd lp + debugM $ "setLayoutStartIfNeeded: markLayout==True,(p,lc)=" ++ show (p,lc) + modify (\s -> s { epMarkLayout = False + , epLHS = LayoutStartCol lc}) + getPos :: (Monad m, Monoid w) => EP w m Pos getPos = gets epPos setPos :: (Monad m, Monoid w) => Pos -> EP w m () setPos l = modify (\s -> s {epPos = l}) +getPriorEndE :: (Monad m, Monoid w) => EP w m Pos +getPriorEndE = gets priorEndPositionE + +getAnchor :: (Monad m, Monoid w) => EP w m RealSrcSpan +getAnchor = gets anchorSpan + +getPrevAnchorPos :: (Monad m, Monoid w) => EP w m Pos +getPrevAnchorPos = gets prevAnchorPos + +getOrigPos :: (Monad m, Monoid w) => EP w m Pos +getOrigPos = gets origPos + +setPriorEndE :: (Monad m, Monoid w) => Pos -> EP w m () +setPriorEndE pe = do + setLayoutStartIfNeeded (snd pe) + setPriorEndNoLayout pe + +setPriorEndNoLayout :: (Monad m, Monoid w) => Pos -> EP w m () +setPriorEndNoLayout pe = do + modify (\s -> s { priorEndPositionE = pe }) + +setAnchor :: (Monad m, Monoid w) => RealSrcSpan -> EP w m () +setAnchor rss = do + debugM $ "setAnchor:" ++ show (rs2range rss) + modify (\s -> s { anchorSpan = rss }) + +setPrevAnchorPos :: (Monad m, Monoid w) => Pos -> EP w m () +setPrevAnchorPos p = do + debugM $ "setPrevAnchorPos:" ++ show p + modify (\s -> s { prevAnchorPos = p }) + +setOrigPos :: (Monad m, Monoid w) => Pos -> EP w m () +setOrigPos p = do + debugM $ "setOrigPos:" ++ show p + modify (\s -> s { origPos = p }) + getUnallocatedComments :: (Monad m, Monoid w) => EP w m [Comment] getUnallocatedComments = gets epComments @@ -3971,6 +3968,14 @@ putUnallocatedComments cs = modify (\s -> s { epComments = cs } ) getLayoutOffset :: (Monad m, Monoid w) => EP w m LayoutStartCol getLayoutOffset = gets epLHS +getAnchorOffset :: (Monad m, Monoid w) => EP w m LayoutStartCol +getAnchorOffset = gets epAnchorLHS + +setAnchorOffset :: (Monad m, Monoid w) => LayoutStartCol -> EP w m () +setAnchorOffset c = do + debugM $ "setAnchorOffset:" ++ show c + modify (\s -> s { epAnchorLHS = c }) + getEofPos :: (Monad m, Monoid w) => EP w m RealSrcSpan getEofPos = do as <- gets epApiAnns @@ -4011,14 +4016,15 @@ getEofPos = do -- return (a, s', EPWriter w') advance :: (Monad m, Monoid w) => DeltaPos -> EP w m () -advance cl = do +advance dp = do p <- getPos - colOffset <- getLayoutOffset - debugM $ "advance:(p,colOffset,ws)=" ++ show (p,colOffset,undelta p cl colOffset) - printWhitespace (undelta p cl colOffset) - --- getAndRemoveAnnotation :: (Monad m, Monoid w, Data a) => GHC.Located a -> EP w m (Maybe Annotation) --- getAndRemoveAnnotation a = gets (getAnnotationEP a . epAnns) + -- colOffset <- getLayoutOffset + colOffset <- getAnchorOffset + debugM $ "advance:(p,dp,colOffset,ws)=" ++ show (p,dp,colOffset,undelta p dp colOffset) + printWhitespace (undelta p dp colOffset) + p' <- getPos + let anchorOffset = LayoutStartCol (snd p') + setAnchorOffset anchorOffset -- --------------------------------------------------------------------- @@ -4027,27 +4033,29 @@ advance cl = do -- colOffset <- gets epLHS -- return (adjustDeltaForOffset colOffset dp) -adjustDeltaForOffset :: LayoutStartCol -> DeltaPos -> DeltaPos -adjustDeltaForOffset _colOffset dp@(DP (0,_)) = dp -- same line -adjustDeltaForOffset (LayoutStartCol colOffset) (DP (l,c)) = DP (l,c - colOffset) +adjustDeltaForOffset :: Int -> LayoutStartCol -> DeltaPos -> DeltaPos +adjustDeltaForOffset _ _colOffset dp@(DP (0,_)) = dp -- same line +-- adjustDeltaForOffset _ (LayoutStartCol colOffset) (DP (l,c)) = DP (l,c - colOffset) +adjustDeltaForOffset d (LayoutStartCol colOffset) (DP (l,c)) = DP (l,c - colOffset - d) +-- adjustDeltaForOffset anchorCol (LayoutStartCol colOffset) (DP (l,c)) = DP (l,c - anchorCol) +-- adjustDeltaForOffset d (LayoutStartCol colOffset) (DP (l,c)) = DP (l,colOffset) +-- adjustDeltaForOffset d (LayoutStartCol colOffset) (DP (l,c)) = DP (l,colOffset + d) +-- adjustDeltaForOffset _ (LayoutStartCol colOffset) (DP (l,c)) = DP (l,0) + -- --------------------------------------------------------------------- -- Printing functions - - - -printString :: (Monad m, Monoid w) => Bool -> String -> EP w m () -printString layout str = do +printString :: (Monad m, Monoid w) => String -> EP w m () +printString str = do EPState{epPos = (_,c), epMarkLayout} <- get PrintOptions{epTokenPrint, epWhitespacePrint} <- ask - when (epMarkLayout && layout) $ - modify (\s -> s { epLHS = LayoutStartCol c, epMarkLayout = False } ) -- Advance position, taking care of any newlines in the string let strDP@(DP (cr,_cc)) = dpFromString str p <- getPos - colOffset <- getLayoutOffset + -- colOffset <- getLayoutOffset + colOffset <- getAnchorOffset if cr == 0 then setPos (undelta p strDP colOffset) else setPos (undelta p strDP 1) @@ -4058,7 +4066,7 @@ printString layout str = do -- Debug end -- - if not layout && c == 0 + if c == 0 then lift (epWhitespacePrint str) >>= \s -> tell EPWriter { output = s} else lift (epTokenPrint str) >>= \s -> tell EPWriter { output = s} @@ -4066,13 +4074,13 @@ printString layout str = do newLine :: (Monad m, Monoid w) => EP w m () newLine = do (l,_) <- getPos - printString False "\n" + printString "\n" setPos (l+1,1) padUntil :: (Monad m, Monoid w) => Pos -> EP w m () padUntil (l,c) = do (l1,c1) <- getPos - if | l1 == l && c1 <= c -> printString False $ replicate (c - c1) ' ' + if | l1 == l && c1 <= c -> printString $ replicate (c - c1) ' ' | l1 < l -> newLine >> padUntil (l,c) | otherwise -> return () @@ -4082,7 +4090,7 @@ printWhitespace = padUntil printCommentAt :: (Monad m, Monoid w) => Pos -> String -> EP w m () printCommentAt p str = do debugM $ "printCommentAt: (pos,str)" ++ show (p,str) - printWhitespace p >> printString False str + printWhitespace p >> printString str printStringAt :: (Monad m, Monoid w) => Pos -> String -> EP w m () -printStringAt p str = printWhitespace p >> printString False str +printStringAt p str = printWhitespace p >> printString str ===================================== utils/check-exact/src/Utils.hs ===================================== @@ -37,6 +37,7 @@ import GHC.Types.Name import GHC.Types.Name.Reader import GHC.Types.SrcLoc import GHC.Driver.Ppr +import GHC.Data.FastString -- import GHC.Types.Var -- import GHC.Types.Name.Occurrence @@ -164,6 +165,22 @@ ss2pos ss = (srcSpanStartLine ss,srcSpanStartCol ss) ss2posEnd :: RealSrcSpan -> Pos ss2posEnd ss = (srcSpanEndLine ss,srcSpanEndCol ss) +ss2range :: SrcSpan -> (Pos,Pos) +ss2range ss = (ss2pos $ rs ss, ss2posEnd $ rs ss) + +rs2range :: RealSrcSpan -> (Pos,Pos) +rs2range ss = (ss2pos ss, ss2posEnd ss) + +rs :: SrcSpan -> RealSrcSpan +rs (RealSrcSpan s _) = s +rs _ = badRealSrcSpan + +badRealSrcSpan :: RealSrcSpan +badRealSrcSpan = mkRealSrcSpan bad bad + where + bad = mkRealSrcLoc (fsLit "ghc-exactprint-nospan") 0 0 + + -- srcSpanEndColumn :: SrcSpan -> Int -- srcSpanEndColumn (RealSrcSpan s) = srcSpanEndCol s -- srcSpanEndColumn _ = 0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48aec3ebc01d9c50148d614d75abc71e695fb3fa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/48aec3ebc01d9c50148d614d75abc71e695fb3fa 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 Mon Nov 23 18:58:24 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 13:58:24 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/m32-fixes Message-ID: <5fbc0650781d8_36a73fd2f90f5f307620f0@gitlab.mail> Ben Gamari pushed new branch wip/m32-fixes at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/m32-fixes 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 Mon Nov 23 19:13:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 14:13:25 -0500 Subject: [Git][ghc/ghc][wip/m32-fixes] 3 commits: rts: Post ticky entry counts to the eventlog Message-ID: <5fbc09d588be5_36a7643e30076365@gitlab.mail> Ben Gamari pushed to branch wip/m32-fixes at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 46d84a1c by Ben Gamari at 2020-11-23T14:13:18-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - 19 changed files: - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - docs/users_guide/debugging.rst - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/profiling.rst - includes/rts/EventLogFormat.h - includes/rts/Flags.h - rts/Proftimer.c - rts/Proftimer.h - rts/RtsFlags.c - rts/RtsStartup.c - rts/Ticky.c - rts/Ticky.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/linker/M32Alloc.c - rts/sm/GC.c Changes: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -138,7 +138,13 @@ outputC dflags filenm cmm_stream packages = hPutStr h ("/* GHC_PACKAGES " ++ unwords pkg_names ++ "\n*/\n") hPutStr h "#include \"Stg.h\"\n" let platform = targetPlatform dflags - writeC = printForC dflags h . cmmToC platform + writeC cmm = do + let doc = cmmToC platform cmm + dumpIfSet_dyn dflags Opt_D_dump_c_backend + "C backend output" + FormatC + doc + printForC dflags h doc Stream.consume cmm_stream writeC {- ===================================== compiler/GHC/Driver/Flags.hs ===================================== @@ -49,6 +49,7 @@ data DumpFlag | Opt_D_dump_asm_conflicts | Opt_D_dump_asm_stats | Opt_D_dump_asm_expanded + | Opt_D_dump_c_backend | Opt_D_dump_llvm | Opt_D_dump_core_stats | Opt_D_dump_deriv ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -2539,6 +2539,8 @@ dynamic_flags_deps = [ (setDumpFlag Opt_D_dump_asm_expanded) , make_ord_flag defGhcFlag "ddump-llvm" (NoArg $ setObjBackend LLVM >> setDumpFlag' Opt_D_dump_llvm) + , make_ord_flag defGhcFlag "ddump-c-backend" + (NoArg $ setDumpFlag' Opt_D_dump_c_backend) , make_ord_flag defGhcFlag "ddump-deriv" (setDumpFlag Opt_D_dump_deriv) , make_ord_flag defGhcFlag "ddump-ds" ===================================== docs/users_guide/debugging.rst ===================================== @@ -552,6 +552,15 @@ LLVM code generator LLVM code from the :ref:`LLVM code generator ` +C code generator +~~~~~~~~~~~~~~~~ + +.. ghc-flag:: -ddump-c-backend + :shortdesc: Dump C code produced by the C (unregisterised) backend. + :type: dynamic + + :shortdesc: Dump C code produced by the C (unregisterised) backend. + Native code generator ~~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/eventlog-formats.rst ===================================== @@ -755,3 +755,34 @@ intended to provide insight into fragmentation of the non-moving heap. :field Word32: number of live blocks. Describes the occupancy of the *blk_sz* sub-heap. + +Ticky counters +~~~~~~~~~~~~~~ + +Programs compiled with :ghc-flag:`-ticky` and :ghc-flag:`-eventlog` and invoked +with ``+RTS -lT`` will emit periodic samples of the ticky entry counters to the +eventlog. + +.. event-type:: TICKY_COUNTER_DEF + + :tag: 210 + :length: variable + :field Word64: counter ID + :field Word16: arity/field count + :field String: argument kinds. This is the same as the synonymous field in the + textual ticky summary. + :field String: counter name + + Defines a ticky counter. + +.. event-type:: TICKY_COUNTER_SAMPLE + + :tag: 211 + :length: fixed + :field Word64: counter ID + :field Word64: number of times closures of this type has been entered. + :field Word64: number of allocations (words) + :field Word64: number of times this has been allocated (words). Only + produced for modules compiled with :ghc-flag:`-ticky-allocd`. + + Records the counter statistics at a moment in time. ===================================== docs/users_guide/expected-undocumented-flags.txt ===================================== @@ -118,5 +118,3 @@ -syslib -this-component-id -ticky-LNE --ticky-allocd --ticky-dyn-thunk ===================================== docs/users_guide/profiling.rst ===================================== @@ -1681,11 +1681,27 @@ Using “ticky-ticky” profiling (for implementors) single: ticky-ticky profiling .. ghc-flag:: -ticky - :shortdesc: :ref:`Turn on ticky-ticky profiling ` + :shortdesc: Turn on :ref:`ticky-ticky profiling ` :type: dynamic :category: - Enable ticky-ticky profiling. + Enable ticky-ticky profiling. By default this only tracks the allocations + *by* each closure type. See :ghc-flag:`-ticky-allocd` to keep track of + allocations *of* each closure type as well. + +.. ghc-flag:: -ticky-allocd + :shortdesc: Track the number of times each closure type is allocated. + :type: dynamic + :category: + + Keep track of how much each closure type is allocated. + +.. ghc-flag:: -ticky-dyn-thunk + :shortdesc: Track allocations of dynamic thunks + :type: dynamic + :category: + + Track allocations of dynamic thunks. Because ticky-ticky profiling requires a certain familiarity with GHC internals, we have moved the documentation to the GHC developers wiki. ===================================== includes/rts/EventLogFormat.h ===================================== @@ -154,12 +154,15 @@ #define EVENT_CONC_UPD_REM_SET_FLUSH 206 #define EVENT_NONMOVING_HEAP_CENSUS 207 +#define EVENT_TICKY_COUNTER_DEF 210 +#define EVENT_TICKY_COUNTER_SAMPLE 211 + /* * The highest event code +1 that ghc itself emits. Note that some event * ranges higher than this are reserved but not currently emitted by ghc. * This must match the size of the EventDesc[] array in EventLog.c */ -#define NUM_GHC_EVENT_TAGS 208 +#define NUM_GHC_EVENT_TAGS 212 #if 0 /* DEPRECATED EVENTS: */ /* we don't actually need to record the thread, it's implicit */ ===================================== includes/rts/Flags.h ===================================== @@ -176,6 +176,7 @@ typedef struct _TRACE_FLAGS { bool nonmoving_gc; /* trace nonmoving GC events */ bool sparks_sampled; /* trace spark events by a sampled method */ bool sparks_full; /* trace spark events 100% accurately */ + bool ticky; /* trace ticky-ticky samples */ bool user; /* trace user events (emitted from Haskell code) */ char *trace_output; /* output filename for eventlog */ } TRACE_FLAGS; ===================================== rts/Proftimer.c ===================================== @@ -20,6 +20,12 @@ static bool do_prof_ticks = false; // enable profiling ticks static bool do_heap_prof_ticks = false; // enable heap profiling ticks +// Sampling of Ticky-Ticky profiler to eventlog +#if defined(TICKY_TICKY) && defined(TRACING) +static int ticks_to_ticky_sample = 0; +bool performTickySample = false; +#endif + // Number of ticks until next heap census static int ticks_to_heap_profile; @@ -83,6 +89,16 @@ handleProfTick(void) } #endif +#if defined(TICKY_TICKY) && defined(TRACING) + if (RtsFlags.TraceFlags.ticky) { + ticks_to_ticky_sample--; + if (ticks_to_ticky_sample <= 0) { + ticks_to_ticky_sample = RtsFlags.ProfFlags.heapProfileIntervalTicks; + performTickySample = true; + } + } +#endif + if (RELAXED_LOAD(&do_heap_prof_ticks)) { ticks_to_heap_profile--; if (ticks_to_heap_profile <= 0) { ===================================== rts/Proftimer.h ===================================== @@ -17,5 +17,6 @@ void stopHeapProfTimer ( void ); void startHeapProfTimer ( void ); extern bool performHeapProfile; +extern bool performTickySample; #include "EndPrivate.h" ===================================== rts/RtsFlags.c ===================================== @@ -235,6 +235,7 @@ void initRtsFlagsDefaults(void) RtsFlags.TraceFlags.sparks_sampled= false; RtsFlags.TraceFlags.sparks_full = false; RtsFlags.TraceFlags.user = false; + RtsFlags.TraceFlags.ticky = false; RtsFlags.TraceFlags.trace_output = NULL; #endif @@ -403,6 +404,9 @@ usage_text[] = { " p par spark events (sampled)", " f par spark events (full detail)", " u user events (emitted from Haskell code)", +#if defined(TICKY_TICKY) +" T ticky-ticky counter samples", +#endif " a all event classes above", # if defined(DEBUG) " t add time stamps (only useful with -v)", @@ -1855,6 +1859,11 @@ static void normaliseRtsOpts (void) "the compacting collector."); errorUsage(); } + + if (RtsFlags.TraceFlags.ticky && RtsFlags.TickyFlags.showTickyStats) { + barf("The ticky-ticky eventlog output cannot be used in conjunction with\n" + "+RTS -r."); + } } static void errorUsage (void) @@ -2297,6 +2306,15 @@ static void read_trace_flags(const char *arg) RtsFlags.TraceFlags.user = enabled; enabled = true; break; + case 'T': +#if defined(TICKY_TICKY) + RtsFlags.TraceFlags.ticky = enabled; + enabled = true; + break; +#else + errorBelch("Program not compiled with ticky-ticky support"); + break; +#endif default: errorBelch("unknown trace option: %c",*c); break; ===================================== rts/RtsStartup.c ===================================== @@ -487,6 +487,17 @@ hs_exit_(bool wait_foreign) */ exitTimer(true); + /* + * Dump the ticky counter definitions + * We do this at the end of execution since tickers are registered in the + * course of program execution. + */ +#if defined(TICKY_TICKY) && defined(TRACING) + if (RtsFlags.TraceFlags.ticky) { + emitTickyCounterDefs(); + } +#endif + // set the terminal settings back to what they were #if !defined(mingw32_HOST_OS) resetTerminalSettings(); ===================================== rts/Ticky.c ===================================== @@ -10,6 +10,8 @@ #include "PosixSource.h" #include "Rts.h" +#include "eventlog/EventLog.h" + /* Catch-all top-level counter struct. Allocations from CAFs will go * here. */ @@ -46,6 +48,10 @@ static void printRegisteredCounterInfo (FILE *); /* fwd decl */ void PrintTickyInfo(void) { + if (RtsFlags.TraceFlags.ticky) { + barf("Ticky eventlog output can't be used with +RTS -r"); + } + unsigned long i; unsigned long tot_thk_enters = ENT_STATIC_THK_MANY_ctr + ENT_DYN_THK_MANY_ctr @@ -374,4 +380,19 @@ printRegisteredCounterInfo (FILE *tf) } } + +void emitTickyCounterDefs() +{ +#if defined(TRACING) + postTickyCounterDefs(ticky_entry_ctrs); +#endif +} + +void emitTickyCounterSamples() +{ +#if defined(TRACING) + postTickyCounterSamples(ticky_entry_ctrs); +#endif +} + #endif /* TICKY_TICKY */ ===================================== rts/Ticky.h ===================================== @@ -8,4 +8,11 @@ #pragma once -RTS_PRIVATE void PrintTickyInfo(void); +#include "BeginPrivate.h" + +void PrintTickyInfo(void); + +void emitTickyCounterSamples(void); +void emitTickyCounterDefs(void); + +#include "EndPrivate.h" ===================================== rts/eventlog/EventLog.c ===================================== @@ -119,7 +119,9 @@ char *EventDesc[] = { [EVENT_CONC_SWEEP_BEGIN] = "Begin concurrent sweep", [EVENT_CONC_SWEEP_END] = "End concurrent sweep", [EVENT_CONC_UPD_REM_SET_FLUSH] = "Update remembered set flushed", - [EVENT_NONMOVING_HEAP_CENSUS] = "Nonmoving heap census" + [EVENT_NONMOVING_HEAP_CENSUS] = "Nonmoving heap census", + [EVENT_TICKY_COUNTER_DEF] = "Ticky-ticky entry counter definition", + [EVENT_TICKY_COUNTER_SAMPLE] = "Ticky-ticky entry counter sample", }; // Event type. @@ -487,6 +489,14 @@ init_event_types(void) eventTypes[t].size = 13; break; + case EVENT_TICKY_COUNTER_DEF: // (counter_id, arity, arg_kinds, name) + eventTypes[t].size = EVENT_SIZE_DYNAMIC; + break; + + case EVENT_TICKY_COUNTER_SAMPLE: // (counter_id, entry_count, allocs, allocd) + eventTypes[t].size = 8*4; + break; + default: continue; /* ignore deprecated events */ } @@ -1472,6 +1482,53 @@ void postProfBegin(void) } #endif /* PROFILING */ +#if defined(TICKY_TICKY) +static void postTickyCounterDef(EventsBuf *eb, StgEntCounter *p) +{ + StgWord len = 8 + 2 + strlen(p->arg_kinds)+1 + strlen(p->str)+1; + ensureRoomForVariableEvent(eb, len); + postEventHeader(eb, EVENT_TICKY_COUNTER_DEF); + postPayloadSize(eb, len); + postWord64(eb, (uint64_t) p); + postWord16(eb, (uint16_t) p->arity); + postString(eb, p->arg_kinds); + postString(eb, p->str); +} + +void postTickyCounterDefs(StgEntCounter *counters) +{ + ACQUIRE_LOCK(&eventBufMutex); + for (StgEntCounter *p = counters; p != NULL; p = p->link) { + postTickyCounterDef(&eventBuf, p); + } + RELEASE_LOCK(&eventBufMutex); +} + +static void postTickyCounterSample(EventsBuf *eb, StgEntCounter *p) +{ + if ( p->entry_count == 0 + && p->allocs == 0 + && p->allocd == 0) + return; + + ensureRoomForEvent(eb, EVENT_TICKY_COUNTER_SAMPLE); + postEventHeader(eb, EVENT_TICKY_COUNTER_SAMPLE); + postWord64(eb, (uint64_t) p); + postWord64(eb, p->entry_count); + postWord64(eb, p->allocs); + postWord64(eb, p->allocd); +} + +void postTickyCounterSamples(StgEntCounter *counters) +{ + ACQUIRE_LOCK(&eventBufMutex); + for (StgEntCounter *p = counters; p != NULL; p = p->link) { + postTickyCounterSample(&eventBuf, p); + } + RELEASE_LOCK(&eventBufMutex); +} +#endif /* TICKY_TICKY */ + void printAndClearEventBuf (EventsBuf *ebuf) { closeBlockMarker(ebuf); ===================================== rts/eventlog/EventLog.h ===================================== @@ -173,6 +173,11 @@ void postConcMarkEnd(StgWord32 marked_obj_count); void postNonmovingHeapCensus(int log_blk_size, const struct NonmovingAllocCensus *census); +#if defined(TICKY_TICKY) +void postTickyCounterDefs(StgEntCounter *p); +void postTickyCounterSamples(StgEntCounter *p); +#endif /* TICKY_TICKY */ + #else /* !TRACING */ INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, ===================================== rts/linker/M32Alloc.c ===================================== @@ -81,6 +81,7 @@ The allocator manages two kinds of allocations: * small allocations, which are allocated into a set of "nursery" pages (recorded in m32_allocator_t.pages; the size of the set is <= M32_MAX_PAGES) + * large allocations are those larger than a page and are mapped directly Each page (or the first page of a large allocation) begins with a m32_page_t @@ -126,7 +127,9 @@ code accordingly). To avoid unnecessary mapping/unmapping we maintain a global list of free pages (which can grow up to M32_MAX_FREE_PAGE_POOL_SIZE long). Pages on this list have the usual m32_page_t header and are linked together with -m32_page_t.free_page.next. +m32_page_t.free_page.next. When run out of free pages we allocate a chunk of +M32_MAP_PAGES to both avoid fragmenting our address space and amortize the +runtime cost of the mapping. The allocator is *not* thread-safe. @@ -139,7 +142,12 @@ The allocator is *not* thread-safe. * M32 ALLOCATOR (see Note [M32 Allocator] ***************************************************************************/ +/* How many open pages each allocator will keep around? */ #define M32_MAX_PAGES 32 +/* How many pages should we map at once when re-filling the free page pool? */ +#define M32_MAP_PAGES 32 +/* Upper bound on the number of pages to keep in the free page pool */ +#define M32_MAX_FREE_PAGE_POOL_SIZE 64 /** * Page header @@ -204,7 +212,6 @@ struct m32_allocator_t { * * We keep a small pool of free pages around to avoid fragmentation. */ -#define M32_MAX_FREE_PAGE_POOL_SIZE 16 struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO @@ -250,18 +257,29 @@ m32_release_page(struct m32_page_t *page) static struct m32_page_t * m32_alloc_page(void) { - if (m32_free_page_pool_size > 0) { - struct m32_page_t *page = m32_free_page_pool; - m32_free_page_pool = page->free_page.next; - m32_free_page_pool_size --; - return page; - } else { - struct m32_page_t *page = mmapForLinker(getPageSize(), PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + if (m32_free_page_pool_size == 0) { + /* + * Free page pool is empty; refill it with a new batch of M32_MAP_PAGES + * pages. + */ + struct m32_page_t *chunk = mmapForLinker(getPageSize() * M32_MAP_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); if (page > (struct m32_page_t *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } - return page; + + for (int i=0; i < M32_MAP_PAGES; i++) { + struct m32_page_t *page = chunk[i]; + page->free_page.next = &page[i+1]; + } + chunk[M32_MAP_PAGES-1]->free_page.next = m32_free_page_pool; + m32_free_page_pool = &chunk[0]; + m32_free_page_pool_size += M32_MAP_PAGES; } + + struct m32_page_t *page = m32_free_page_pool; + m32_free_page_pool = page->free_page.next; + m32_free_page_pool_size --; + return page; } /** @@ -276,19 +294,6 @@ m32_allocator_new(bool executable) stgMallocBytes(sizeof(m32_allocator), "m32_new_allocator"); memset(alloc, 0, sizeof(struct m32_allocator_t)); alloc->executable = executable; - - // Preallocate the initial M32_MAX_PAGES to ensure that they don't - // fragment the memory. - size_t pgsz = getPageSize(); - char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); - if (bigchunk == NULL) - barf("m32_allocator_init: Failed to map"); - - int i; - for (i=0; ipages[i] = (struct m32_page_t *) (bigchunk + i*pgsz); - alloc->pages[i]->current_size = sizeof(struct m32_page_t); - } return alloc; } @@ -350,7 +355,9 @@ m32_allocator_push_filled_list(struct m32_page_t **head, struct m32_page_t *page void m32_allocator_flush(m32_allocator *alloc) { for (int i=0; ipages[i]->current_size == sizeof(struct m32_page_t)) { + if (alloc->pages[i] == NULL) { + continue; + } else if (alloc->pages[i]->current_size == sizeof(struct m32_page_t)) { // the page is empty, free it m32_release_page(alloc->pages[i]); } else { ===================================== rts/sm/GC.c ===================================== @@ -38,6 +38,7 @@ #include "Sanity.h" #include "BlockAlloc.h" #include "ProfHeap.h" +#include "Proftimer.h" #include "Weak.h" #include "Prelude.h" #include "RtsSignals.h" @@ -52,6 +53,7 @@ #include "CNF.h" #include "RtsFlags.h" #include "NonMoving.h" +#include "Ticky.h" #include // for memset() #include @@ -903,6 +905,16 @@ GarbageCollect (uint32_t collect_gen, ACQUIRE_SM_LOCK; } +#if defined(TICKY_TICKY) + // Post ticky counter sample. + // We do this at the end of execution since tickers are registered in the + // course of program execution. + if (performTickySample) { + emitTickyCounterSamples(); + performTickySample = false; + } +#endif + // send exceptions to any threads which were about to die RELEASE_SM_LOCK; resurrectThreads(resurrected_threads); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5e90343aae50d1ccf9949299b7f4de6ac471d379...46d84a1cc0f080430d36df5d5b3475a8de36fef1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5e90343aae50d1ccf9949299b7f4de6ac471d379...46d84a1cc0f080430d36df5d5b3475a8de36fef1 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 Mon Nov 23 20:23:22 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 15:23:22 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/win32-m32 Message-ID: <5fbc1a3aa2fc_36a71600f92c7734d9@gitlab.mail> Ben Gamari pushed new branch wip/win32-m32 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/win32-m32 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 Mon Nov 23 20:36:06 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 15:36:06 -0500 Subject: [Git][ghc/ghc][wip/win32-m32] rts/linker: Use m32 to allocate symbol extras in PEi386 Message-ID: <5fbc1d362e1be_36a71579be4477494@gitlab.mail> Ben Gamari pushed to branch wip/win32-m32 at Glasgow Haskell Compiler / GHC Commits: cc437472 by Ben Gamari at 2020-11-23T15:35:59-05:00 rts/linker: Use m32 to allocate symbol extras in PEi386 - - - - - 2 changed files: - rts/LinkerInternals.h - rts/linker/PEi386.c Changes: ===================================== rts/LinkerInternals.h ===================================== @@ -149,7 +149,7 @@ typedef struct _Segment { * We use the m32 allocator for symbol extras on Windows and other mmap-using * platforms. */ -#if RTS_LINKER_USE_MMAP +#if RTS_LINKER_USE_MMAP || defined(mingw32_HOST_ARCH) #define NEED_M32 1 #endif ===================================== rts/linker/PEi386.c ===================================== @@ -1788,42 +1788,28 @@ ocGetNames_PEi386 ( ObjectCode* oc ) bool ocAllocateExtras_PEi386 ( ObjectCode* oc ) { - /* If the ObjectCode was unloaded we don't need a trampoline, it's likely - an import library so we're discarding it earlier. */ - if (!oc->info) - return false; + /* If the ObjectCode was unloaded we don't need a trampoline, it's likely + an import library so we're discarding it earlier. */ + if (!oc->info) + return false; - const int mask = default_alignment - 1; - size_t origin = oc->info->trampoline; - oc->symbol_extras - = (SymbolExtra*)((uintptr_t)(oc->info->image + origin + mask) & ~mask); - oc->first_symbol_extra = 0; - COFF_HEADER_INFO *info = oc->info->ch_info; - oc->n_symbol_extras = info->numberOfSymbols; + // These are allocated on-demand from m32 by makeSymbolExtra_PEi386 + oc->first_symbol_extra = 0; + oc->n_symbol_extras = 0; + oc->symbol_extras = NULL; - return true; + return true; } static size_t makeSymbolExtra_PEi386( ObjectCode* oc, uint64_t index, size_t s, char* symbol ) { - unsigned int curr_thunk; - SymbolExtra *extra; - curr_thunk = oc->first_symbol_extra + index; - if (index >= oc->n_symbol_extras) { - IF_DEBUG(linker, debugBelch("makeSymbolExtra first:%d, num:%lu, member:%" PATH_FMT ", index:%llu\n", curr_thunk, oc->n_symbol_extras, oc->archiveMemberName, index)); - barf("Can't allocate thunk for `%s' in `%" PATH_FMT "' with member `%" PATH_FMT "'", symbol, oc->fileName, oc->archiveMemberName); - } - - extra = oc->symbol_extras + curr_thunk; + SymbolExtra *extra = m32_alloc(oc->rx_m32, sizeof(SymbolExtra), 8); - if (!extra->addr) - { - // jmp *-14(%rip) - static uint8_t jmp[] = { 0xFF, 0x25, 0xF2, 0xFF, 0xFF, 0xFF }; - extra->addr = (uint64_t)s; - memcpy(extra->jumpIsland, jmp, 6); - } + // jmp *-14(%rip) + static uint8_t jmp[] = { 0xFF, 0x25, 0xF2, 0xFF, 0xFF, 0xFF }; + extra->addr = (uint64_t)s; + memcpy(extra->jumpIsland, jmp, 6); return (size_t)extra->jumpIsland; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc437472912dc7bce72db01964e6ca021cf0325c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cc437472912dc7bce72db01964e6ca021cf0325c 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 Mon Nov 23 21:23:18 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 23 Nov 2020 16:23:18 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: Bump time submodule to 1.11.1 Message-ID: <5fbc284680960_36a71600f92c779992@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - b08971de by Ben Gamari at 2020-11-23T16:23:07-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 6367c403 by Ben Gamari at 2020-11-23T16:23:08-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 4a399e83 by Ben Gamari at 2020-11-23T16:23:08-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 357bedc3 by Ben Gamari at 2020-11-23T16:23:08-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToLlvm/Base.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/Cabal - libraries/base/Debug/Trace.hs - libraries/directory - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/hpc - libraries/time - libraries/unix - rts/Capability.c - rts/Capability.h - rts/LinkerInternals.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h - rts/linker/Elf.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1f30757d5a951a342ec6170e84795b8ed3efa5f...357bedc3672faf699a72954f0f2b000262dae033 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d1f30757d5a951a342ec6170e84795b8ed3efa5f...357bedc3672faf699a72954f0f2b000262dae033 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 Mon Nov 23 21:51:24 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 16:51:24 -0500 Subject: [Git][ghc/ghc][wip/win32-m32] 6 commits: rts/m32: Refactor handling of allocator seeding Message-ID: <5fbc2edc10aa6_36a73fd2f208ef807808bc@gitlab.mail> Ben Gamari pushed to branch wip/win32-m32 at Glasgow Haskell Compiler / GHC Commits: 52cf9952 by Ben Gamari at 2020-11-23T16:48:28-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - d987f98d by Ben Gamari at 2020-11-23T16:51:17-05:00 rts: Introduce mmapAnonForLinker Previously most of the uses of mmapForLinker were mapping anonymous memory, resulting in a great deal of unnecessary repetition. Factor this out into a new helper. Also fixes a few places where error checking was missing or suboptimal. - - - - - bea04642 by Ben Gamari at 2020-11-23T16:51:17-05:00 rts/linker: Introduce munmapForLinker Consolidates munmap calls to ensure consistent error handling. - - - - - 2f8724d8 by Ben Gamari at 2020-11-23T16:51:17-05:00 rts/Linker: Introduce Windows implementations for mmapForLinker, et al. - - - - - 9bb5d9b1 by Ben Gamari at 2020-11-23T16:51:17-05:00 rts/m32: Introduce NEEDS_M32 macro Instead of relying on RTS_LINKER_USE_MMAP - - - - - 4cd87229 by Ben Gamari at 2020-11-23T16:51:17-05:00 rts/linker: Use m32 to allocate symbol extras in PEi386 - - - - - 10 changed files: - rts/Linker.c - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/M32Alloc.c - rts/linker/M32Alloc.h - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/SymbolExtras.c - rts/linker/elf_got.c Changes: ===================================== rts/Linker.c ===================================== @@ -1026,7 +1026,38 @@ resolveSymbolAddr (pathchar* buffer, int size, #endif /* OBJFORMAT_PEi386 */ } -#if RTS_LINKER_USE_MMAP +#if defined(mingw32_HOST_OS) + +// +// Returns NULL on failure. +// +void * +mmapAnonForLinker (size_t bytes) +{ + return VirtualAlloc(NULL, bytes, MEM_COMMIT | MEM_RESERVE, PAGE_READWRITE); +} + +void +munmapForLinker (void *addr, size_t bytes, const char *caller) +{ + if (VirtualFree(addr, 0, MEM_RELEASE) == 0) { + sysErrorBelch("munmapForLinker: %s: Failed to unmap %zd bytes at %p", + caller, bytes, addr); + } +} + +void +mmapForLinkerMarkExecutable(void *start, size_t len) +{ + DWORD old; + if (VirtualProtect(start, len, PAGE_EXECUTE_READ, &old) == 0) { + sysErrorBelch("mmapForLinkerMarkExecutable: failed to protect %zd bytes at %p", + len, start); + ASSERT(false); + } +} + +#elif RTS_LINKER_USE_MMAP // // Returns NULL on failure. // @@ -1085,7 +1116,7 @@ mmap_again: fixed = MAP_FIXED; goto mmap_again; #else - errorBelch("loadObj: failed to mmap() memory below 2Gb; " + errorBelch("mmapForLinker: failed to mmap() memory below 2Gb; " "asked for %lu bytes at %p. " "Try specifying an address with +RTS -xm -RTS", size, map_addr); @@ -1145,6 +1176,24 @@ mmap_again: return result; } +/* + * Map read/write pages in low memory. Returns NULL on failure. + */ +void * +mmapAnonForLinker (size_t bytes) +{ + return mmapForLinker (bytes, PROT_READ|PROT_WRITE, MAP_ANONYMOUS, -1, 0); +} + +void munmapForLinker (void *addr, size_t bytes, const char *caller) +{ + int r = munmap(addr,size); + if (r == -1) { + // Should we abort here? + sysErrorBelch("munmap: %s", caller); + } +} + /* Note [Memory protection in the linker] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * For many years the linker would simply map all of its memory @@ -1230,7 +1279,7 @@ freePreloadObjectFile (ObjectCode *oc) #else if (RTS_LINKER_USE_MMAP && oc->imageMapped) { - munmap(oc->image, oc->fileSize); + munmapForLinker(oc->image, oc->fileSize, "freePreloadObjectFile"); } else { stgFree(oc->image); @@ -1278,13 +1327,15 @@ void freeObjectCode (ObjectCode *oc) switch(oc->sections[i].alloc){ #if RTS_LINKER_USE_MMAP case SECTION_MMAP: - munmap(oc->sections[i].mapped_start, - oc->sections[i].mapped_size); + munmapForLinker( + oc->sections[i].mapped_start, + oc->sections[i].mapped_size, + "freeObjectCode"); break; +#endif case SECTION_M32: // Freed by m32_allocator_free break; -#endif case SECTION_MALLOC: IF_DEBUG(zero_on_gc, memset(oc->sections[i].start, @@ -1327,7 +1378,7 @@ void freeObjectCode (ObjectCode *oc) ocDeinit_ELF(oc); #endif -#if RTS_LINKER_USE_MMAP == 1 +#if defined(NEED_M32) m32_allocator_free(oc->rx_m32); m32_allocator_free(oc->rw_m32); #endif @@ -1405,7 +1456,7 @@ mkOc( ObjectType type, pathchar *path, char *image, int imageSize, oc->mark = object_code_mark_bit; oc->dependencies = allocHashSet(); -#if RTS_LINKER_USE_MMAP +#if defined(NEED_M32) oc->rw_m32 = m32_allocator_new(false); oc->rx_m32 = m32_allocator_new(true); #endif @@ -1742,7 +1793,7 @@ int ocTryLoad (ObjectCode* oc) { // We have finished loading and relocating; flush the m32 allocators to // setup page protections. -#if RTS_LINKER_USE_MMAP +#if defined(NEED_M32) m32_allocator_flush(oc->rx_m32); m32_allocator_flush(oc->rw_m32); #endif @@ -2168,7 +2219,7 @@ void freeSegments (ObjectCode *oc) continue; } else { #if RTS_LINKER_USE_MMAP - CHECKM(0 == munmap(s->start, s->size), "freeSegments: failed to unmap memory"); + munmapForLinker(s->start, s->size, "freeSegments"); #else stgFree(s->start); #endif ===================================== rts/LinkerInternals.h ===================================== @@ -145,6 +145,14 @@ typedef struct _Segment { #define NEED_SYMBOL_EXTRAS 1 #endif +/* + * We use the m32 allocator for symbol extras on Windows and other mmap-using + * platforms. + */ +#if RTS_LINKER_USE_MMAP || defined(mingw32_HOST_ARCH) +#define NEED_M32 1 +#endif + /* Jump Islands are sniplets of machine code required for relative * address relocations on the PowerPC, x86_64 and ARM. */ @@ -276,7 +284,7 @@ typedef struct _ObjectCode { require extra information.*/ StrHashTable *extraInfos; -#if RTS_LINKER_USE_MMAP == 1 +#if defined(NEED_M32) /* The m32 allocators used for allocating small sections and symbol extras * during loading. We have two: one for (writeable) data and one for * (read-only/executable) code. */ @@ -334,8 +342,10 @@ void exitLinker( void ); void freeObjectCode (ObjectCode *oc); SymbolAddr* loadSymbol(SymbolName *lbl, RtsSymbolInfo *pinfo); +void *mmapAnonForLinker (size_t bytes); void *mmapForLinker (size_t bytes, uint32_t prot, uint32_t flags, int fd, int offset); void mmapForLinkerMarkExecutable (void *start, size_t len); +void munmapForLinker (void *addr, size_t bytes, const char *caller); void addProddableBlock ( ObjectCode* oc, void* start, int size ); void checkProddableBlock (ObjectCode *oc, void *addr, size_t size ); ===================================== rts/linker/Elf.c ===================================== @@ -709,7 +709,11 @@ ocGetNames_ELF ( ObjectCode* oc ) * address might be out of range for sections that are mmaped. */ alloc = SECTION_MMAP; - start = mmapForLinker(size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + start = mmapAnonForLinker(size); + if (start == NULL) { + barf("failed to mmap memory for bss. " + "errno = %d", i, errno); + } mapped_start = start; mapped_offset = 0; mapped_size = roundUpToPage(size); @@ -751,9 +755,9 @@ ocGetNames_ELF ( ObjectCode* oc ) unsigned nstubs = numberOfStubsForSection(oc, i); unsigned stub_space = STUB_SIZE * nstubs; - void * mem = mmapForLinker(size+stub_space, PROT_READ | PROT_WRITE, MAP_ANON, -1, 0); + void * mem = mmapAnonForLinker(size+stub_space); - if( mem == MAP_FAILED ) { + if( mem == NULL ) { barf("failed to mmap allocated memory to load section %d. " "errno = %d", i, errno); } @@ -855,11 +859,10 @@ ocGetNames_ELF ( ObjectCode* oc ) } void * common_mem = NULL; if(common_size > 0) { - common_mem = mmapForLinker(common_size, - PROT_READ | PROT_WRITE, - MAP_ANON | MAP_PRIVATE, - -1, 0); - ASSERT(common_mem != NULL); + common_mem = mmapAnonForLinker(common_size); + if (common_mem == NULL) { + barf("ocGetNames_ELF: Failed to allocate memory for SHN_COMMONs"); + } } //TODO: we ignore local symbols anyway right? So we can use the ===================================== rts/linker/LoadArchive.c ===================================== @@ -489,7 +489,7 @@ static HsInt loadArchive_ (pathchar *path) #if defined(darwin_HOST_OS) || defined(ios_HOST_OS) if (RTS_LINKER_USE_MMAP) - image = mmapForLinker(memberSize, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + image = mmapAnonForLinker(memberSize); else { /* See loadObj() */ misalignment = machoGetMisalignment(f); @@ -549,7 +549,7 @@ while reading filename from `%" PATH_FMT "'", path); } DEBUG_LOG("Found GNU-variant file index\n"); #if RTS_LINKER_USE_MMAP - gnuFileIndex = mmapForLinker(memberSize + 1, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + gnuFileIndex = mmapAnonForLinker(memberSize + 1); #else gnuFileIndex = stgMallocBytes(memberSize + 1, "loadArchive(image)"); #endif @@ -613,7 +613,7 @@ fail: stgFree(fileName); if (gnuFileIndex != NULL) { #if RTS_LINKER_USE_MMAP - munmap(gnuFileIndex, gnuFileIndexSize + 1); + munmapForLinker(gnuFileIndex, gnuFileIndexSize + 1, "loadArchive_"); #else stgFree(gnuFileIndex); #endif ===================================== rts/linker/M32Alloc.c ===================================== @@ -42,7 +42,7 @@ still check the call for syntax and correct function parameter types. */ -#if RTS_LINKER_USE_MMAP == 1 +#if defined(NEED_M32) /* @@ -81,6 +81,7 @@ The allocator manages two kinds of allocations: * small allocations, which are allocated into a set of "nursery" pages (recorded in m32_allocator_t.pages; the size of the set is <= M32_MAX_PAGES) + * large allocations are those larger than a page and are mapped directly Each page (or the first page of a large allocation) begins with a m32_page_t @@ -126,7 +127,9 @@ code accordingly). To avoid unnecessary mapping/unmapping we maintain a global list of free pages (which can grow up to M32_MAX_FREE_PAGE_POOL_SIZE long). Pages on this list have the usual m32_page_t header and are linked together with -m32_page_t.free_page.next. +m32_page_t.free_page.next. When run out of free pages we allocate a chunk of +M32_MAP_PAGES to both avoid fragmenting our address space and amortize the +runtime cost of the mapping. The allocator is *not* thread-safe. @@ -139,7 +142,12 @@ The allocator is *not* thread-safe. * M32 ALLOCATOR (see Note [M32 Allocator] ***************************************************************************/ +/* How many open pages each allocator will keep around? */ #define M32_MAX_PAGES 32 +/* How many pages should we map at once when re-filling the free page pool? */ +#define M32_MAP_PAGES 32 +/* Upper bound on the number of pages to keep in the free page pool */ +#define M32_MAX_FREE_PAGE_POOL_SIZE 64 /** * Page header @@ -204,30 +212,10 @@ struct m32_allocator_t { * * We keep a small pool of free pages around to avoid fragmentation. */ -#define M32_MAX_FREE_PAGE_POOL_SIZE 16 struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO -/** - * Wrapper for `unmap` that handles error cases. - * This is the real implementation. There is another dummy implementation below. - * See the note titled "Compile Time Trickery" at the top of this file. - */ -static void -munmapForLinker (void * addr, size_t size) -{ - IF_DEBUG(linker, - debugBelch("m32_alloc: Unmapping %zu bytes at %p\n", - size, addr)); - - int r = munmap(addr,size); - if (r == -1) { - // Should we abort here? - sysErrorBelch("munmap"); - } -} - /** * Free a page or, if possible, place it in the free page pool. */ @@ -239,7 +227,7 @@ m32_release_page(struct m32_page_t *page) m32_free_page_pool = page; m32_free_page_pool_size ++; } else { - munmapForLinker((void *) page, getPageSize()); + munmapForLinker((void *) page, getPageSize(), "m32_release_page"); } } @@ -250,18 +238,33 @@ m32_release_page(struct m32_page_t *page) static struct m32_page_t * m32_alloc_page(void) { - if (m32_free_page_pool_size > 0) { - struct m32_page_t *page = m32_free_page_pool; - m32_free_page_pool = page->free_page.next; - m32_free_page_pool_size --; - return page; - } else { - struct m32_page_t *page = mmapForLinker(getPageSize(), PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); - if (page > (struct m32_page_t *) 0xffffffff) { + if (m32_free_page_pool_size == 0) { + /* + * Free page pool is empty; refill it with a new batch of M32_MAP_PAGES + * pages. + */ + const size_t pgsz = getPageSize(); + char *chunk = mmapAnonForLinker(pgsz * M32_MAP_PAGES); + if (chunk > (char *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } - return page; + +#define GET_PAGE(i) ((struct m32_page_t *) (chunk + (i) * pgsz)) + for (int i=0; i < M32_MAP_PAGES; i++) { + struct m32_page_t *page = GET_PAGE(i); + page->free_page.next = GET_PAGE(i+1); + } + + GET_PAGE(M32_MAP_PAGES-1)->free_page.next = m32_free_page_pool; + m32_free_page_pool = (struct m32_page_t *) chunk; + m32_free_page_pool_size += M32_MAP_PAGES; +#undef GET_PAGE } + + struct m32_page_t *page = m32_free_page_pool; + m32_free_page_pool = page->free_page.next; + m32_free_page_pool_size --; + return page; } /** @@ -276,19 +279,6 @@ m32_allocator_new(bool executable) stgMallocBytes(sizeof(m32_allocator), "m32_new_allocator"); memset(alloc, 0, sizeof(struct m32_allocator_t)); alloc->executable = executable; - - // Preallocate the initial M32_MAX_PAGES to ensure that they don't - // fragment the memory. - size_t pgsz = getPageSize(); - char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); - if (bigchunk == NULL) - barf("m32_allocator_init: Failed to map"); - - int i; - for (i=0; ipages[i] = (struct m32_page_t *) (bigchunk + i*pgsz); - alloc->pages[i]->current_size = sizeof(struct m32_page_t); - } return alloc; } @@ -300,7 +290,7 @@ m32_allocator_unmap_list(struct m32_page_t *head) { while (head != NULL) { struct m32_page_t *next = m32_filled_page_get_next(head); - munmapForLinker((void *) head, head->filled_page.size); + munmapForLinker((void *) head, head->filled_page.size, "m32_allocator_unmap_list"); head = next; } } @@ -318,7 +308,7 @@ void m32_allocator_free(m32_allocator *alloc) const size_t pgsz = getPageSize(); for (int i=0; i < M32_MAX_PAGES; i++) { if (alloc->pages[i]) { - munmapForLinker(alloc->pages[i], pgsz); + munmapForLinker(alloc->pages[i], pgsz, "m32_allocator_free"); } } @@ -350,7 +340,9 @@ m32_allocator_push_filled_list(struct m32_page_t **head, struct m32_page_t *page void m32_allocator_flush(m32_allocator *alloc) { for (int i=0; ipages[i]->current_size == sizeof(struct m32_page_t)) { + if (alloc->pages[i] == NULL) { + continue; + } else if (alloc->pages[i]->current_size == sizeof(struct m32_page_t)) { // the page is empty, free it m32_release_page(alloc->pages[i]); } else { @@ -396,7 +388,14 @@ m32_alloc(struct m32_allocator_t *alloc, size_t size, size_t alignment) if (m32_is_large_object(size,alignment)) { // large object size_t alsize = ROUND_UP(sizeof(struct m32_page_t), alignment); - struct m32_page_t *page = mmapForLinker(alsize+size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); + struct m32_page_t *page = mmapAnonForLinker(alsize+size); + if (page == NULL) { + sysErrorBelch("m32_alloc: Failed to map pages for %zd bytes", size); + return NULL; + } else if (page > (struct m32_page_t *) 0xffffffff) { + debugBelch("m32_alloc: warning: Allocation of %zd bytes resulted in pages above 4GB (%p)", + size, page); + } page->filled_page.size = alsize + size; m32_allocator_push_filled_list(&alloc->unprotected_list, (struct m32_page_t *) page); return (char*) page + alsize; @@ -449,7 +448,7 @@ m32_alloc(struct m32_allocator_t *alloc, size_t size, size_t alignment) return (char*)page + ROUND_UP(sizeof(struct m32_page_t),alignment); } -#elif RTS_LINKER_USE_MMAP == 0 +#else // The following implementations of these functions should never be called. If // they are, there is a bug at the call site. @@ -480,8 +479,4 @@ m32_alloc(m32_allocator *alloc STG_UNUSED, barf("%s: RTS_LINKER_USE_MMAP is %d", __func__, RTS_LINKER_USE_MMAP); } -#else - -#error RTS_LINKER_USE_MMAP should be either `0` or `1`. - #endif ===================================== rts/linker/M32Alloc.h ===================================== @@ -8,19 +8,17 @@ #pragma once -#if RTS_LINKER_USE_MMAP == 1 -#include -#include - -#if defined(HAVE_UNISTD_H) -#include -#endif - +/* + * We use the m32 allocator for symbol extras on Windows and other mmap-using + * platforms. + */ +#if RTS_LINKER_USE_MMAP || defined(mingw32_HOST_OS) +#define NEED_M32 1 #endif #include "BeginPrivate.h" -#if RTS_LINKER_USE_MMAP +#if defined(NEED_M32) #define M32_NO_RETURN /* Nothing */ #else #define M32_NO_RETURN GNUC3_ATTRIBUTE(__noreturn__) ===================================== rts/linker/MachO.c ===================================== @@ -508,11 +508,8 @@ makeGot(ObjectCode * oc) { if(got_slots > 0) { oc->info->got_size = got_slots * sizeof(void*); - oc->info->got_start = mmapForLinker(oc->info->got_size, - PROT_READ | PROT_WRITE, - MAP_ANON | MAP_PRIVATE, - -1, 0); - if( oc->info->got_start == MAP_FAILED ) { + oc->info->got_start = mmapAnonForLinker(oc->info->got_size); + if( oc->info->got_start == NULL ) { barf("MAP_FAILED. errno=%d", errno ); return EXIT_FAILURE; } @@ -529,7 +526,7 @@ makeGot(ObjectCode * oc) { void freeGot(ObjectCode * oc) { - munmap(oc->info->got_start, oc->info->got_size); + munmapForLinker(oc->info->got_start, oc->info->got_size, "freeGot"); oc->info->got_start = NULL; oc->info->got_size = 0; } @@ -1114,7 +1111,7 @@ ocBuildSegments_MachO(ObjectCode *oc) return 1; } - mem = mmapForLinker(size_compound, PROT_READ | PROT_WRITE, MAP_ANON, -1, 0); + mem = mmapAnonForLinker(size_compound); if (NULL == mem) return 0; IF_DEBUG(linker, debugBelch("ocBuildSegments: allocating %d segments\n", n_activeSegments)); ===================================== rts/linker/PEi386.c ===================================== @@ -1788,42 +1788,28 @@ ocGetNames_PEi386 ( ObjectCode* oc ) bool ocAllocateExtras_PEi386 ( ObjectCode* oc ) { - /* If the ObjectCode was unloaded we don't need a trampoline, it's likely - an import library so we're discarding it earlier. */ - if (!oc->info) - return false; + /* If the ObjectCode was unloaded we don't need a trampoline, it's likely + an import library so we're discarding it earlier. */ + if (!oc->info) + return false; - const int mask = default_alignment - 1; - size_t origin = oc->info->trampoline; - oc->symbol_extras - = (SymbolExtra*)((uintptr_t)(oc->info->image + origin + mask) & ~mask); - oc->first_symbol_extra = 0; - COFF_HEADER_INFO *info = oc->info->ch_info; - oc->n_symbol_extras = info->numberOfSymbols; + // These are allocated on-demand from m32 by makeSymbolExtra_PEi386 + oc->first_symbol_extra = 0; + oc->n_symbol_extras = 0; + oc->symbol_extras = NULL; - return true; + return true; } static size_t -makeSymbolExtra_PEi386( ObjectCode* oc, uint64_t index, size_t s, char* symbol ) +makeSymbolExtra_PEi386( ObjectCode* oc, uint64_t index STG_UNUSED, size_t s, char* symbol STG_UNUSED ) { - unsigned int curr_thunk; - SymbolExtra *extra; - curr_thunk = oc->first_symbol_extra + index; - if (index >= oc->n_symbol_extras) { - IF_DEBUG(linker, debugBelch("makeSymbolExtra first:%d, num:%lu, member:%" PATH_FMT ", index:%llu\n", curr_thunk, oc->n_symbol_extras, oc->archiveMemberName, index)); - barf("Can't allocate thunk for `%s' in `%" PATH_FMT "' with member `%" PATH_FMT "'", symbol, oc->fileName, oc->archiveMemberName); - } - - extra = oc->symbol_extras + curr_thunk; + SymbolExtra *extra = m32_alloc(oc->rx_m32, sizeof(SymbolExtra), 8); - if (!extra->addr) - { - // jmp *-14(%rip) - static uint8_t jmp[] = { 0xFF, 0x25, 0xF2, 0xFF, 0xFF, 0xFF }; - extra->addr = (uint64_t)s; - memcpy(extra->jumpIsland, jmp, 6); - } + // jmp *-14(%rip) + static uint8_t jmp[] = { 0xFF, 0x25, 0xF2, 0xFF, 0xFF, 0xFF }; + extra->addr = (uint64_t)s; + memcpy(extra->jumpIsland, jmp, 6); return (size_t)extra->jumpIsland; } ===================================== rts/linker/SymbolExtras.c ===================================== @@ -81,11 +81,11 @@ int ocAllocateExtras(ObjectCode* oc, int count, int first, int bssSize) // symbol_extras is aligned to a page boundary so it can be mprotect'd. bssSize = roundUpToPage(bssSize); size_t allocated_size = n + bssSize + extras_size; - void *new = mmapForLinker(allocated_size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + void *new = mmapAnonForLinker(allocated_size); if (new) { memcpy(new, oc->image, oc->fileSize); if (oc->imageMapped) { - munmap(oc->image, n); + munmapForLinker(oc->image, n, "ocAllocateExtras"); } oc->image = new; oc->imageMapped = true; ===================================== rts/linker/elf_got.c ===================================== @@ -48,11 +48,8 @@ makeGot(ObjectCode * oc) { } if(got_slots > 0) { oc->info->got_size = got_slots * sizeof(void *); - void * mem = mmapForLinker(oc->info->got_size, - PROT_READ | PROT_WRITE, - MAP_ANON | MAP_PRIVATE, - -1, 0); - if (mem == MAP_FAILED) { + void * mem = mmapAnonForLinker(oc->info->got_size); + if (mem == NULL) { errorBelch("MAP_FAILED. errno=%d", errno); return EXIT_FAILURE; } @@ -147,7 +144,7 @@ verifyGot(ObjectCode * oc) { void freeGot(ObjectCode * oc) { -// munmap(oc->info->got_start, oc->info->got_size); +// munmapForLinker(oc->info->got_start, oc->info->got_size, "freeGot); oc->info->got_start = 0x0; oc->info->got_size = 0; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cc437472912dc7bce72db01964e6ca021cf0325c...4cd87229f71c639f2f8b1217c22c92b8bcb18d7a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cc437472912dc7bce72db01964e6ca021cf0325c...4cd87229f71c639f2f8b1217c22c92b8bcb18d7a 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 Mon Nov 23 21:51:31 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 16:51:31 -0500 Subject: [Git][ghc/ghc][wip/m32-fixes] rts/m32: Refactor handling of allocator seeding Message-ID: <5fbc2ee369044_36a73fd2f208ef807810eb@gitlab.mail> Ben Gamari pushed to branch wip/m32-fixes at Glasgow Haskell Compiler / GHC Commits: 52cf9952 by Ben Gamari at 2020-11-23T16:48:28-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - 1 changed file: - rts/linker/M32Alloc.c Changes: ===================================== rts/linker/M32Alloc.c ===================================== @@ -81,6 +81,7 @@ The allocator manages two kinds of allocations: * small allocations, which are allocated into a set of "nursery" pages (recorded in m32_allocator_t.pages; the size of the set is <= M32_MAX_PAGES) + * large allocations are those larger than a page and are mapped directly Each page (or the first page of a large allocation) begins with a m32_page_t @@ -126,7 +127,9 @@ code accordingly). To avoid unnecessary mapping/unmapping we maintain a global list of free pages (which can grow up to M32_MAX_FREE_PAGE_POOL_SIZE long). Pages on this list have the usual m32_page_t header and are linked together with -m32_page_t.free_page.next. +m32_page_t.free_page.next. When run out of free pages we allocate a chunk of +M32_MAP_PAGES to both avoid fragmenting our address space and amortize the +runtime cost of the mapping. The allocator is *not* thread-safe. @@ -139,7 +142,12 @@ The allocator is *not* thread-safe. * M32 ALLOCATOR (see Note [M32 Allocator] ***************************************************************************/ +/* How many open pages each allocator will keep around? */ #define M32_MAX_PAGES 32 +/* How many pages should we map at once when re-filling the free page pool? */ +#define M32_MAP_PAGES 32 +/* Upper bound on the number of pages to keep in the free page pool */ +#define M32_MAX_FREE_PAGE_POOL_SIZE 64 /** * Page header @@ -204,7 +212,6 @@ struct m32_allocator_t { * * We keep a small pool of free pages around to avoid fragmentation. */ -#define M32_MAX_FREE_PAGE_POOL_SIZE 16 struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO @@ -250,18 +257,33 @@ m32_release_page(struct m32_page_t *page) static struct m32_page_t * m32_alloc_page(void) { - if (m32_free_page_pool_size > 0) { - struct m32_page_t *page = m32_free_page_pool; - m32_free_page_pool = page->free_page.next; - m32_free_page_pool_size --; - return page; - } else { - struct m32_page_t *page = mmapForLinker(getPageSize(), PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); - if (page > (struct m32_page_t *) 0xffffffff) { + if (m32_free_page_pool_size == 0) { + /* + * Free page pool is empty; refill it with a new batch of M32_MAP_PAGES + * pages. + */ + const size_t pgsz = getPageSize(); + char *chunk = mmapForLinker(pgsz * M32_MAP_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + if (chunk > (char *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } - return page; + +#define GET_PAGE(i) ((struct m32_page_t *) (chunk + (i) * pgsz)) + for (int i=0; i < M32_MAP_PAGES; i++) { + struct m32_page_t *page = GET_PAGE(i); + page->free_page.next = GET_PAGE(i+1); + } + + GET_PAGE(M32_MAP_PAGES-1)->free_page.next = m32_free_page_pool; + m32_free_page_pool = (struct m32_page_t *) chunk; + m32_free_page_pool_size += M32_MAP_PAGES; +#undef GET_PAGE } + + struct m32_page_t *page = m32_free_page_pool; + m32_free_page_pool = page->free_page.next; + m32_free_page_pool_size --; + return page; } /** @@ -276,19 +298,6 @@ m32_allocator_new(bool executable) stgMallocBytes(sizeof(m32_allocator), "m32_new_allocator"); memset(alloc, 0, sizeof(struct m32_allocator_t)); alloc->executable = executable; - - // Preallocate the initial M32_MAX_PAGES to ensure that they don't - // fragment the memory. - size_t pgsz = getPageSize(); - char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); - if (bigchunk == NULL) - barf("m32_allocator_init: Failed to map"); - - int i; - for (i=0; ipages[i] = (struct m32_page_t *) (bigchunk + i*pgsz); - alloc->pages[i]->current_size = sizeof(struct m32_page_t); - } return alloc; } @@ -350,7 +359,9 @@ m32_allocator_push_filled_list(struct m32_page_t **head, struct m32_page_t *page void m32_allocator_flush(m32_allocator *alloc) { for (int i=0; ipages[i]->current_size == sizeof(struct m32_page_t)) { + if (alloc->pages[i] == NULL) { + continue; + } else if (alloc->pages[i]->current_size == sizeof(struct m32_page_t)) { // the page is empty, free it m32_release_page(alloc->pages[i]); } else { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/52cf9952776b551a4dbed418c1276df73e7427a2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/52cf9952776b551a4dbed418c1276df73e7427a2 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 Mon Nov 23 22:54:50 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 17:54:50 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/check-likelihood Message-ID: <5fbc3dba48c13_36a715ae31b0787471@gitlab.mail> Ben Gamari pushed new branch wip/check-likelihood at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/check-likelihood 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 Mon Nov 23 23:00:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 18:00:56 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/no-assert Message-ID: <5fbc3f286739c_36a73fd2f208ef807911f6@gitlab.mail> Ben Gamari pushed new branch wip/no-assert at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/no-assert 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 Mon Nov 23 23:03:31 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Mon, 23 Nov 2020 18:03:31 -0500 Subject: [Git][ghc/ghc][wip/T18894] Fix a bug regarding recursive lazy_fvs Message-ID: <5fbc3fc3c15c8_36a715ae31b07929d8@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: 87c15c1a by Sebastian Graf at 2020-11-24T00:03:18+01:00 Fix a bug regarding recursive lazy_fvs - - - - - 2 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -65,32 +65,41 @@ data DmdAnalOpts = DmdAnalOpts -- -- Note: use `seqBinds` on the result to avoid leaks due to lazyness (cf Note -- [Stamp out space leaks in demand analysis]) -dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> CoreProgram -> CoreProgram -dmdAnalProgram opts fam_envs binds = binds_plus_dmds +dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> [CoreRule] -> CoreProgram -> CoreProgram +dmdAnalProgram opts fam_envs rules binds = binds_plus_dmds where env = emptyAnalEnv opts fam_envs + rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules binds_plus_dmds = snd $ go env nopDmdType binds go _ dmd_ty [] = (dmd_ty, []) go env dmd_ty (b:bs) = case b of NonRec id rhs - | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel Nothing env topSubDmd id rhs + | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel NonRecursive env topSubDmd id rhs , (dmd_ty', bs') <- go env' (add_exported_use env' dmd_ty id') bs , (dmd_ty'', id_dmd) <- findBndrDmd env' False (dmd_ty' `addLazyFVs` lazy_fvs) id' - , let id'' = id' `setIdDemandInfo` if isInterestingTopLevelFn id' then id_dmd else topDmd + , let id'' = annotate_id_dmd id' id_dmd -> (dmd_ty'', NonRec id'' rhs' : bs') Rec pairs | (env', lazy_fvs, pairs') <- dmdFix TopLevel env topSubDmd pairs , let ids' = map fst pairs' , (dmd_ty', bs') <- go env' (add_exported_uses env' dmd_ty ids') bs , (dmd_ty'', id_dmds) <- findBndrsDmds env' (dmd_ty' `addLazyFVs` lazy_fvs) ids' - , let ids'' = zipWith (\id' id_dmd -> id' `setIdDemandInfo` if isInterestingTopLevelFn id' then id_dmd else topDmd) ids' id_dmds + , let ids'' = zipWith annotate_id_dmd ids' id_dmds , let pairs'' = zipWith (\id'' (_, rhs') -> (id'', rhs')) ids'' pairs' -> (dmd_ty'', Rec pairs'' : bs') + annotate_id_dmd id dmd + | isInterestingTopLevelFn id, not (id `elemVarSet` rule_fvs) + -- See Note [Absence analysis for stable unfoldings and RULES] + = id `setIdDemandInfo` dmd + | otherwise + = id `setIdDemandInfo` topDmd + add_exported_uses env = foldl' (add_exported_use env) add_exported_use env dmd_ty id - | isExportedId id = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) + | isExportedId id || not (isInterestingTopLevelFn id) + = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) | otherwise = dmd_ty {- Note [Stamp out space leaks in demand analysis] @@ -326,7 +335,7 @@ dmdAnal' env dmd (Let (NonRec id rhs) body) dmdAnal' env dmd (Let (NonRec id rhs) body) = (body_ty2, Let (NonRec id2 rhs') body') where - (env1, lazy_fv, id1, rhs') = dmdAnalRhsLetDown NotTopLevel Nothing env dmd id rhs + (env1, lazy_fv, id1, rhs') = dmdAnalRhsLetDown NotTopLevel NonRecursive env dmd id rhs (body_ty, body') = dmdAnal env1 dmd body (body_ty1, id2) = annotateBndr env body_ty id1 body_ty2 = addLazyFVs body_ty1 lazy_fv -- see Note [Lazy and unleashable free variables] @@ -348,8 +357,8 @@ dmdAnal' env dmd (Let (Rec pairs) body) = let (env', lazy_fv, pairs') = dmdFix NotTopLevel env dmd pairs (body_ty, body') = dmdAnal env' dmd body - body_ty1 = deleteFVs body_ty (map fst pairs) - body_ty2 = addLazyFVs body_ty1 lazy_fv -- see Note [Lazy and unleashable free variables] + body_ty1 = addLazyFVs body_ty lazy_fv -- see Note [Lazy and unleashable free variables] + body_ty2 = deleteFVs body_ty1 (map fst pairs) -- TODO: We could annotate idDemandInfo here in body_ty2 `seq` (body_ty2, Let (Rec pairs') body') @@ -565,7 +574,8 @@ strict in |y|. -- (e.g. called), but aren't interested in whether they were called strictly -- or not. Other top-level bindings are boring. isInterestingTopLevelFn :: Id -> Bool -isInterestingTopLevelFn id = typeArity (idType id) `lengthExceeds` 0 +isInterestingTopLevelFn id = + typeArity (idType id) `lengthExceeds` 0 dmdTransform :: AnalEnv -- ^ The strictness environment -> Id -- ^ The function @@ -630,7 +640,7 @@ dmdTransform env var dmd -- This is the LetDown rule in the paper “Higher-Order Cardinality Analysis”. dmdAnalRhsLetDown :: TopLevelFlag - -> Maybe [Id] -- Just bs <=> recursive, Nothing <=> non-recursive + -> RecFlag -> AnalEnv -> SubDemand -> Id -> CoreExpr -> (AnalEnv, DmdEnv, Id, CoreExpr) @@ -671,8 +681,8 @@ dmdAnalRhsLetDown top_lvl rec_flag env let_dmd id rhs -- we'd have to do an additional iteration. reuseEnv makes sure that -- we never get used-once info for FVs of recursive functions. rhs_fv1 = case rec_flag of - Just bs -> reuseEnv (delVarEnvList rhs_fv bs) - Nothing -> rhs_fv + Recursive -> reuseEnv rhs_fv + NonRecursive -> rhs_fv rhs_fv2 = rhs_fv1 `keepAliveDmdEnv` extra_fvs -- Find the RHS free vars of the unfoldings and RULES @@ -952,8 +962,6 @@ dmdFix :: TopLevelFlag dmdFix top_lvl env let_dmd orig_pairs = loop 1 initial_pairs where - bndrs = map fst orig_pairs - -- See Note [Initialising strictness] initial_pairs | ae_virgin env = [(setIdStrictness id botSig, rhs) | (id, rhs) <- orig_pairs ] | otherwise = orig_pairs @@ -1003,7 +1011,7 @@ dmdFix top_lvl env let_dmd orig_pairs = -- pprTrace "my_downRhs" (ppr id $$ ppr (idStrictness id) $$ ppr sig) $ ((env', lazy_fv'), (id', rhs')) where - (env', lazy_fv1, id', rhs') = dmdAnalRhsLetDown top_lvl (Just bndrs) env let_dmd id rhs + (env', lazy_fv1, id', rhs') = dmdAnalRhsLetDown top_lvl Recursive env let_dmd id rhs lazy_fv' = plusVarEnv_C plusDmd lazy_fv lazy_fv1 zapIdStrictness :: [(Id, CoreExpr)] -> [(Id, CoreExpr)] ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -495,7 +495,7 @@ doCorePass CoreDoExitify = {-# SCC "Exitify" #-} doPass exitifyProgram doCorePass CoreDoDemand = {-# SCC "DmdAnal" #-} - doPassDFM dmdAnal + doPassDFRM dmdAnal doCorePass CoreDoCpr = {-# SCC "CprAnal" #-} doPassDFM cprAnalProgram @@ -575,6 +575,13 @@ doPassDFM do_pass guts = do let fam_envs = (p_fam_env, mg_fam_inst_env guts) doPassM (liftIO . do_pass dflags fam_envs) guts +doPassDFRM :: (DynFlags -> FamInstEnvs -> [CoreRule] -> CoreProgram -> IO CoreProgram) -> ModGuts -> CoreM ModGuts +doPassDFRM do_pass guts = do + dflags <- getDynFlags + p_fam_env <- getPackageFamInstEnv + let fam_envs = (p_fam_env, mg_fam_inst_env guts) + doPassM (liftIO . do_pass dflags fam_envs (mg_rules guts)) guts + doPassDFU :: (DynFlags -> FamInstEnvs -> UniqSupply -> CoreProgram -> CoreProgram) -> ModGuts -> CoreM ModGuts doPassDFU do_pass guts = do dflags <- getDynFlags @@ -1088,12 +1095,12 @@ transferIdInfo exported_id local_id -dmdAnal :: DynFlags -> FamInstEnvs -> CoreProgram -> IO CoreProgram -dmdAnal dflags fam_envs binds = do +dmdAnal :: DynFlags -> FamInstEnvs -> [CoreRule] -> CoreProgram -> IO CoreProgram +dmdAnal dflags fam_envs rules binds = do let opts = DmdAnalOpts { dmd_strict_dicts = gopt Opt_DictsStrict dflags } - binds_plus_dmds = dmdAnalProgram opts fam_envs binds + binds_plus_dmds = dmdAnalProgram opts fam_envs rules binds Err.dumpIfSet_dyn dflags Opt_D_dump_str_signatures "Strictness signatures" FormatText $ dumpIdInfoOfProgram (ppr . strictnessInfo) binds_plus_dmds -- See Note [Stamp out space leaks in demand analysis] in GHC.Core.Opt.DmdAnal View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/87c15c1ad42fe808bbd8e8bda15f9a8e5314fc04 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/87c15c1ad42fe808bbd8e8bda15f9a8e5314fc04 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 Mon Nov 23 23:13:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 18:13:44 -0500 Subject: [Git][ghc/ghc][wip/no-assert] rts/linker: Replace some ASSERTs with CHECK Message-ID: <5fbc42282dbd7_36a73fd2ff413ea0793429@gitlab.mail> Ben Gamari pushed to branch wip/no-assert at Glasgow Haskell Compiler / GHC Commits: ed9d5a1e by Ben Gamari at 2020-11-23T18:12:15-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 5 changed files: - rts/Linker.c - rts/linker/Elf.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c Changes: ===================================== rts/Linker.c ===================================== @@ -49,7 +49,6 @@ #include #include #include -#include #include #if defined(HAVE_SYS_STAT_H) @@ -885,12 +884,11 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) */ IF_DEBUG(linker, debugBelch("lookupSymbol: looking up %s with dlsym\n", lbl)); - ASSERT(lbl[0] == '_'); + CHECK(lbl[0] == '_'); return internal_dlsym(lbl + 1); # else - ASSERT(false); - return NULL; +# error No OBJFORMAT_* macro set # endif } else { if (dependent) { @@ -2112,7 +2110,7 @@ HsInt unloadNativeObj (void *handle) n_unloaded_objects += 1; // dynamic objects have no symbols - ASSERT(nc->symbols == NULL); + CHECK(nc->symbols == NULL); freeOcStablePtrs(nc); // Remove object code from root set ===================================== rts/linker/Elf.c ===================================== @@ -416,7 +416,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) "\nSection header table: start %ld, n_entries %d, ent_size %d\n", (long)ehdr->e_shoff, shnum, ehdr->e_shentsize )); - ASSERT(ehdr->e_shentsize == sizeof(Elf_Shdr)); + CHECK(ehdr->e_shentsize == sizeof(Elf_Shdr)); shdr = (Elf_Shdr*) (ehdrC + ehdr->e_shoff); @@ -537,7 +537,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) #if defined(SHN_XINDEX) /* See Note [Many ELF Sections] */ if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -859,7 +859,7 @@ ocGetNames_ELF ( ObjectCode* oc ) PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); - ASSERT(common_mem != NULL); + CHECK(common_mem != NULL); } //TODO: we ignore local symbols anyway right? So we can use the @@ -888,7 +888,7 @@ ocGetNames_ELF ( ObjectCode* oc ) secno = shndx; #if defined(SHN_XINDEX) if (shndx == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -897,11 +897,11 @@ ocGetNames_ELF ( ObjectCode* oc ) if (shndx == SHN_COMMON) { isLocal = false; - ASSERT(common_used < common_size); - ASSERT(common_mem); + CHECK(common_used < common_size); + CHECK(common_mem); symbol->addr = (void*)((uintptr_t)common_mem + common_used); common_used += symbol->elf_sym->st_size; - ASSERT(common_used <= common_size); + CHECK(common_used <= common_size); IF_DEBUG(linker, debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", @@ -930,7 +930,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ) ) { /* Section 0 is the undefined section, hence > and not >=. */ - ASSERT(secno > 0 && secno < shnum); + CHECK(secno > 0 && secno < shnum); /* if (shdr[secno].sh_type == SHT_NOBITS) { debugBelch(" BSS symbol, size %d off %d name %s\n", @@ -957,7 +957,7 @@ ocGetNames_ELF ( ObjectCode* oc ) /* And the decision is ... */ if (symbol->addr != NULL) { - ASSERT(nm != NULL); + CHECK(nm != NULL); /* Acquire! */ if (!isLocal) { @@ -1040,7 +1040,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, break; } } - ASSERT(stab != NULL); + CHECK(stab != NULL); targ = (Elf_Word*)oc->sections[target_shndx].start; IF_DEBUG(linker,debugBelch( @@ -1246,7 +1246,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, result = ((S + A) | T) - P; result &= ~1; // Clear thumb indicator bit - ASSERT(isInt(26, result)); /* X in range */ + CHECK(isInt(26, result)); /* X in range */ } // Update the branch target @@ -1421,7 +1421,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, case COMPAT_R_ARM_GOT_PREL: { int32_t A = *pP; void* GOT_S = symbol->got_addr; - ASSERT(GOT_S); + CHECK(GOT_S); *(uint32_t *)P = (uint32_t) GOT_S + A - P; break; } @@ -1547,21 +1547,21 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, case R_SPARC_WDISP30: w1 = *pP & 0xC0000000; w2 = (Elf_Word)((value - P) >> 2); - ASSERT((w2 & 0xC0000000) == 0); + CHECK((w2 & 0xC0000000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_HI22: w1 = *pP & 0xFFC00000; w2 = (Elf_Word)(value >> 10); - ASSERT((w2 & 0xFFC00000) == 0); + CHECK((w2 & 0xFFC00000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_LO10: w1 = *pP & ~0x3FF; w2 = (Elf_Word)(value & 0x3FF); - ASSERT((w2 & ~0x3FF) == 0); + CHECK((w2 & ~0x3FF) == 0); w1 |= w2; *pP = w1; break; @@ -1861,12 +1861,12 @@ ocResolve_ELF ( ObjectCode* oc ) Elf_Word secno = symbol->elf_sym->st_shndx; #if defined(SHN_XINDEX) if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[i]; } #endif - ASSERT(symbol->elf_sym->st_name == 0); - ASSERT(symbol->elf_sym->st_value == 0); + CHECK(symbol->elf_sym->st_name == 0); + CHECK(symbol->elf_sym->st_value == 0); symbol->addr = oc->sections[ secno ].start; } } ===================================== rts/linker/MachO.c ===================================== @@ -252,7 +252,6 @@ resolveImports( "%s: unknown symbol `%s'", oc->fileName, symbol->name); return 0; } - ASSERT(addr); checkProddableBlock(oc, ((void**)(oc->image + sect->offset)) + i, @@ -847,7 +846,7 @@ relocateSection(ObjectCode* oc, int curSection) IF_DEBUG(linker, debugBelch(" : value = %p\n", (void *)symbol->nlist->n_value)); if ((symbol->nlist->n_type & N_TYPE) == N_SECT) { - ASSERT(symbol->addr != NULL); + CHECK(symbol->addr != NULL); value = (uint64_t) symbol->addr; IF_DEBUG(linker, debugBelch("relocateSection, defined external symbol %s, relocated address %p\n", nm, (void *)value)); @@ -949,29 +948,29 @@ relocateSection(ObjectCode* oc, int curSection) { if((int32_t)(value - baseValue) != (int64_t)(value - baseValue)) { - ASSERT(reloc->r_extern); + CHECK(reloc->r_extern); value = (uint64_t) &makeSymbolExtra(oc, reloc->r_symbolnum, value) -> jumpIsland; } - ASSERT((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); + CHECK((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); type = X86_64_RELOC_SIGNED; } switch(type) { case X86_64_RELOC_UNSIGNED: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing += value; break; case X86_64_RELOC_SIGNED: case X86_64_RELOC_SIGNED_1: case X86_64_RELOC_SIGNED_2: case X86_64_RELOC_SIGNED_4: - ASSERT(reloc->r_pcrel); + CHECK(reloc->r_pcrel); thing += value - baseValue; break; case X86_64_RELOC_SUBTRACTOR: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing -= value; break; default: ===================================== rts/linker/PEi386.c ===================================== @@ -1594,7 +1594,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) barf ("Could not allocate any heap memory from private heap."); } - ASSERT(section.size == 0 || section.info->virtualSize == 0); + CHECK(section.size == 0 || section.info->virtualSize == 0); sz = section.size; if (sz < section.info->virtualSize) sz = section.info->virtualSize; @@ -2032,7 +2032,7 @@ ocRunInit_PEi386 ( ObjectCode *oc ) getProgEnvv(&envc, &envv); Section section = *oc->info->init; - ASSERT(SECTIONKIND_INIT_ARRAY == section.kind); + CHECK(SECTIONKIND_INIT_ARRAY == section.kind); uint8_t *init_startC = section.start; init_t *init_start = (init_t*)init_startC; ===================================== rts/linker/elf_got.c ===================================== @@ -136,10 +136,10 @@ verifyGot(ObjectCode * oc) { for(size_t i=0; i < symTab->n_symbols; i++) { ElfSymbol * symbol = &symTab->symbols[i]; if(symbol->got_addr) { - ASSERT((void*)(*(void**)symbol->got_addr) - == (void*)symbol->addr); + CHECK((void*)(*(void**)symbol->got_addr) + == (void*)symbol->addr); } - ASSERT(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); + CHECK(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); } } return EXIT_SUCCESS; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ed9d5a1e195f7ce19ea27dec040d8e9bbb18e661 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ed9d5a1e195f7ce19ea27dec040d8e9bbb18e661 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 Mon Nov 23 23:29:17 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 18:29:17 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] 9 commits: rts: Post ticky entry counts to the eventlog Message-ID: <5fbc45cd94f4b_36a71600f92c7942d2@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - ddfa9629 by Moritz Angermann at 2020-11-23T18:29:09-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in - docs/users_guide/debugging.rst - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/profiling.rst - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b200e0ab7d03a8fb8c6c6a453f394e75416f3726...ddfa962992b856b4f9eff75971e129ec897a20df -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b200e0ab7d03a8fb8c6c6a453f394e75416f3726...ddfa962992b856b4f9eff75971e129ec897a20df 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 Tue Nov 24 01:36:41 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 20:36:41 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/tsan-ghc-9.0 Message-ID: <5fbc63a9b7fee_36a7643e3008091ed@gitlab.mail> Ben Gamari pushed new branch wip/tsan-ghc-9.0 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/tsan-ghc-9.0 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 Tue Nov 24 01:40:05 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 20:40:05 -0500 Subject: [Git][ghc/ghc][wip/keepAlive-the-return-of-the-primop] 221 commits: Parser regression tests, close #12862 #12446 Message-ID: <5fbc6475bfab4_36a71579be448108f7@gitlab.mail> Ben Gamari pushed to branch wip/keepAlive-the-return-of-the-primop at Glasgow Haskell Compiler / GHC Commits: e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - 577f22cd by Ben Gamari at 2020-11-23T19:23:43-05:00 base: Use keepAlive# in withForeignPtr - - - - - fd3f4be1 by Ben Gamari at 2020-11-23T19:23:43-05:00 base: Add unsafeWithForeignPtr - - - - - bd7558bb by Ben Gamari at 2020-11-23T19:23:43-05:00 base: Introduce GHC.ForeignPtr.Ops module This contains a variety of peek/poke operations for ForeignPtr accesses. - - - - - 15e942d3 by Ben Gamari at 2020-11-23T19:23:43-05:00 GHC.IO.Buffer: Use ForeignPtr-specialised peek/poke - - - - - a18d35cd by Ben Gamari at 2020-11-23T19:23:43-05:00 StringBuffer: Rid it of ForeignPtrs - - - - - 467e244b by Ben Gamari at 2020-11-23T19:23:43-05:00 GHC.Data.ByteArray: Initial commit - - - - - 23ba1a17 by Ben Gamari at 2020-11-23T19:23:43-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - dd674a82 by Ben Gamari at 2020-11-23T19:23:43-05:00 Binary: Fix - - - - - 731ebcf7 by Ben Gamari at 2020-11-23T19:23:43-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - e753c06c by Ben Gamari at 2020-11-23T19:23:43-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - 476ae594 by Ben Gamari at 2020-11-23T19:23:43-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - 8cfc4357 by Ben Gamari at 2020-11-23T19:23:43-05:00 ForeignPtr Ops without keepAlive - - - - - d03f5f52 by Ben Gamari at 2020-11-23T19:29:46-05:00 CountParserDeps: ByteArray - - - - - b3490130 by Ben Gamari at 2020-11-23T19:29:46-05:00 Revert "ForeignPtr Ops without keepAlive" This reverts commit f931de26edb3d91f42516f39cb88541381c2f455. - - - - - 24446214 by Ben Gamari at 2020-11-23T19:30:33-05:00 genprimopcode: Add a second levity-polymorphic tyvar This will be needed shortly. - - - - - c95ccfa6 by GHC GitLab CI at 2020-11-23T19:30:33-05:00 Introduce keepAlive primop - - - - - 4f0396f3 by Ben Gamari at 2020-11-23T19:30:33-05:00 keepalive fix - - - - - c5a46b1c by Ben Gamari at 2020-11-23T19:30:33-05:00 Revert "hi" This reverts commit e9b1bb7275b39b80a7e064199e119521238e9c20. - - - - - 87120e7d by Ben Gamari at 2020-11-23T19:30:33-05:00 base: Implement GHC.ForeignPtr.Ops in terms of keepAlive# - - - - - 9ec59f53 by Ben Gamari at 2020-11-23T19:30:33-05:00 base: Use keepAlive# in Foreign.Marshal.Alloc - - - - - 91c4aa5c by Ben Gamari at 2020-11-23T19:30:33-05:00 ghc-compact: Use keepAlive# in GHC.Compact.Serialized - - - - - 17ad689a by Ben Gamari at 2020-11-23T19:30:33-05:00 testsuite: Accept - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/BlockLayout.hs - compiler/GHC/CmmToAsm/CFG/Dominators.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/435a4b0898db0df3359d2b962c8da735eae48dc9...17ad689a701eae4c7647574c857530515a0d344b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/435a4b0898db0df3359d2b962c8da735eae48dc9...17ad689a701eae4c7647574c857530515a0d344b 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 Tue Nov 24 02:09:17 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 21:09:17 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fbc6b4d751d_36a71600f92c814225@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: b77ce429 by Moritz Angermann at 2020-11-23T21:08:53-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b77ce429b263263d5be411534926d7a87d717376 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b77ce429b263263d5be411534926d7a87d717376 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 Tue Nov 24 02:10:09 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Mon, 23 Nov 2020 21:10:09 -0500 Subject: [Git][ghc/ghc][wip/T18599] Add RecordDotUpd syntax Message-ID: <5fbc6b81341d0_36a73fd2f1d86400815762@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: b6ca0350 by Shayne Fletcher at 2020-11-23T21:09:55-05:00 Add RecordDotUpd syntax - - - - - 7 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax + +-- e.g. "foo.bar.baz = 42" is +-- ProjUpdate { +-- pb_fIELDS=["foo","bar","baz"] +-- , pb_exp=42 +-- , pb_func=\a -> setField@"foo" a .... 42 +-- } +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -473,31 +495,36 @@ data HsExpr p } -- Record update. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDotdot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. - -- We call this RecordDotUpd in sympathy with RecordUpd. - -- e.g. a{foo.bar.baz=1, quux} = RecordDotUpd { -- rdupd_ext=noExtField, rdupd_expr=a, rdupd_updates=[...], rdupd_setField=setField@"quux" (setField@"foo"...a... 1) quux -- }, - -- | RecordDotUpd - -- { rdupd_ext :: XRecordDotUpd - -- , rdupd_expr :: LHsExpr GhcPs - -- , rdupd_updates :: [LHsProjUpdate GhcPs (LHsExpr GhcPs)] - -- , rdupd_setField :: LHsExpr GhcPs -- Equivalent 'setField' term. - -- } + + + | RecordDotUpd + { rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } -- | Record field selector. -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. - -- e.g. .x = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x - -- }, - -- .x.y = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) - -- } + -- e.g. (.x) = Projection { + -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x + -- }, + -- (.x.y) = Projection { + -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) + -- } | Projection { proj_ext :: XProjection p , proj_fIELDS :: [Located FastString] @@ -629,6 +656,7 @@ data RecordUpdTc = RecordUpdTc data GetFieldTc = GetFieldTc data ProjectionTc = ProjectionTc +data RecordDotUpdTc = RecordDotUpdTc -- | HsWrap appears only in typechecker output -- Invariant: The contained Expr is *NOT* itself an HsWrap. @@ -706,6 +734,10 @@ type instance XProjection GhcPs = NoExtField type instance XProjection GhcRn = NoExtField type instance XProjection GhcTc = NoExtField +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1257,6 +1289,9 @@ ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field, gf_getField = _}) ppr_expr (Projection { proj_fIELDS = _, proj_projection = _}) = undefined {- TODO: implement this -} +ppr_expr (RecordDotUpd { rdupd_expr = _, rdupd_upds = _, rdupd_setField =_ }) + = undefined {- TODO: implement this -} + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1414,6 +1449,7 @@ hsExprNeedsParens p = go go (Projection{}) = True go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False go (XExpr x) | GhcTc <- ghcPass @p ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -557,6 +557,7 @@ type family XRecordCon x type family XRecordUpd x type family XGetField x type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -273,6 +273,7 @@ dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" -- getField expressions by now. dsExpr (GetField{}) = panic "dsExpr: GetField" dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -153,22 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" --- e.g. "foo.bar.baz = 42" is --- ProjBind { --- pb_fIELDS=["foo","bar","baz"] --- , pb_exp=42 --- , pb_func=\a -> setField@"foo" a .... 42 --- } -data ProjUpdate' p arg = - ProjUpdate { - pb_fIELDS :: [Located FastString] - , pb_arg :: arg -- Field's new value e.g. 42 - , pb_func :: arg -> arg - } -type ProjUpdate p arg = ProjUpdate' p arg -type LHsProjUpdate p arg = Located (ProjUpdate p arg) -type RecUpdProj p = ProjUpdate' p (LHsExpr p) -type LHsRecUpdProj p = Located (RecUpdProj p) +-- -- e.g. "foo.bar.baz = 42" is +-- -- ProjUpdate { +-- -- pb_fIELDS=["foo","bar","baz"] +-- -- , pb_exp=42 +-- -- , pb_func=\a -> setField@"foo" a .... 42 +-- -- } +-- data ProjUpdate' p arg = +-- ProjUpdate { +-- pb_fIELDS :: [Located FastString] +-- , pb_arg :: arg -- Field's new value e.g. 42 +-- , pb_func :: arg -> arg +-- } +-- type ProjUpdate p arg = ProjUpdate' p arg +-- type LHsProjUpdate p arg = Located (ProjUpdate p arg) +-- type RecUpdProj p = ProjUpdate' p (LHsExpr p) +-- type LHsRecUpdProj p = Located (RecUpdProj p) data Fbind b = Fbind (LHsRecField GhcPs (Located b)) | Pbind (LHsProjUpdate GhcPs (Located b)) @@ -187,15 +187,6 @@ fbindsToEithers = fmap fbindToEither fbindToEither (Fbind x) = Left x fbindToEither (Pbind x) = Right x --- Next fix mkRdrRecordUpd' to return one of these. --- RecordDotUpdate { --- rdupd_ext :: XRecordDotUpdate --- , rdupd_expr :: LHsExpr GhcPs --- , rdupd_updates :: [LHsRecUpdProj GhcPs] --- , rupd_setField :: LHsExpr GhcPs -- The equivalent setField term. --- } --- - {- ********************************************************************** Construction functions for Rdr stuff @@ -2406,10 +2397,10 @@ mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = mkRdrRecordUpd' dot exp fs + | otherwise = mkRdrRecordDotUpd dot exp fs -mkRdrRecordUpd' :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) -mkRdrRecordUpd' dot exp@(L _ _) fbinds = +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = if not dot then do let (fs, ps) = partitionEithers $ fbindsToEithers fbinds @@ -2421,7 +2412,13 @@ mkRdrRecordUpd' dot exp@(L _ _) fbinds = panic "mkRdrRecordUpd': The impossible happened!" else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) else - return $ foldl' fieldUpdate (unLoc exp) (toProjUpdates fbinds) + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } where toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] toProjUpdates = map (\case { Pbind p -> p @@ -2429,7 +2426,7 @@ mkRdrRecordUpd' dot exp@(L _ _) fbinds = }) fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs - fieldUpdate acc (L _ pu) = unLoc ((pb_func pu) (noLoc acc)) + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -3063,26 +3060,20 @@ mkProjection loc fIELDS = , proj_projection = mkProj fIELDS } --- mkProjection :: SrcSpan -> Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs --- mkProjection loc maybeRhs fIELD = --- L loc Projection { --- proj_ext = noExtField --- , proj_rhs = maybeRhs --- , proj_fIELD = fIELD --- , proj_projection = mkProj maybeRhs fIELD --- } - -- mkSet a fIELD b calculates a set_field @fIELD expression. -- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b --- mkProjUpdate calculates functions representing dot notation record updates. mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) mkProjUpdate -- e.g {foo.bar.baz.quux = 43} l - fIELDS -- [foo, bar, baz, quux] - arg -- This is 'texp' (43 in the example). + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) = let { ; final = last fIELDS -- quux ; fields = init fIELDS -- [foo, bar, baz] @@ -3091,12 +3082,32 @@ mkProjUpdate -- e.g {foo.bar.baz.quux = 43} ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] } - in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} + in (\a -> foldl' mkSet' arg (zips a)) -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) where mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) +-- -- mkProjUpdate calculates functions representing dot notation record updates. +-- mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +-- mkProjUpdate -- e.g {foo.bar.baz.quux = 43} +-- l +-- fIELDS -- [foo, bar, baz, quux] +-- arg -- This is 'texp' (43 in the example). +-- = let { +-- ; final = last fIELDS -- quux +-- ; fields = init fIELDS -- [foo, bar, baz] +-- ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. +-- -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] +-- ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. +-- -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] +-- } +-- in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} +-- -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) +-- where +-- mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs +-- mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + -- Transform a regular record field update into a projection update. recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -223,6 +223,19 @@ rnExpr (Projection x fs p) ; return (Projection x fs p', fv) } +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1038,6 +1038,7 @@ tcExpr (ArithSeq _ witness seq) res_ty -} tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty {- ************************************************************************ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -513,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6ca03504803d48fa78347977d26f527c3e9a08c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6ca03504803d48fa78347977d26f527c3e9a08c 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 Tue Nov 24 02:11:01 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Mon, 23 Nov 2020 21:11:01 -0500 Subject: [Git][ghc/ghc][wip/T18599] Add RecordDotUpd syntax Message-ID: <5fbc6bb5b0f4c_36a7643e300815997@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 9565c153 by Shayne Fletcher at 2020-11-23T21:10:49-05:00 Add RecordDotUpd syntax - - - - - 7 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax + +-- e.g. "foo.bar.baz = 42" is +-- ProjUpdate { +-- pb_fIELDS=["foo","bar","baz"] +-- , pb_exp=42 +-- , pb_func=\a -> setField@"foo" a .... 42 +-- } +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -473,31 +495,35 @@ data HsExpr p } -- Record update. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDotdot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. - -- We call this RecordDotUpd in sympathy with RecordUpd. - -- e.g. a{foo.bar.baz=1, quux} = RecordDotUpd { -- rdupd_ext=noExtField, rdupd_expr=a, rdupd_updates=[...], rdupd_setField=setField@"quux" (setField@"foo"...a... 1) quux -- }, - -- | RecordDotUpd - -- { rdupd_ext :: XRecordDotUpd - -- , rdupd_expr :: LHsExpr GhcPs - -- , rdupd_updates :: [LHsProjUpdate GhcPs (LHsExpr GhcPs)] - -- , rdupd_setField :: LHsExpr GhcPs -- Equivalent 'setField' term. - -- } + + | RecordDotUpd + { rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } -- | Record field selector. -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. - -- e.g. .x = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x - -- }, - -- .x.y = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) - -- } + -- e.g. (.x) = Projection { + -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x + -- }, + -- (.x.y) = Projection { + -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) + -- } | Projection { proj_ext :: XProjection p , proj_fIELDS :: [Located FastString] @@ -629,6 +655,7 @@ data RecordUpdTc = RecordUpdTc data GetFieldTc = GetFieldTc data ProjectionTc = ProjectionTc +data RecordDotUpdTc = RecordDotUpdTc -- | HsWrap appears only in typechecker output -- Invariant: The contained Expr is *NOT* itself an HsWrap. @@ -706,6 +733,10 @@ type instance XProjection GhcPs = NoExtField type instance XProjection GhcRn = NoExtField type instance XProjection GhcTc = NoExtField +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1257,6 +1288,9 @@ ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field, gf_getField = _}) ppr_expr (Projection { proj_fIELDS = _, proj_projection = _}) = undefined {- TODO: implement this -} +ppr_expr (RecordDotUpd { rdupd_expr = _, rdupd_upds = _, rdupd_setField =_ }) + = undefined {- TODO: implement this -} + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1414,6 +1448,7 @@ hsExprNeedsParens p = go go (Projection{}) = True go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False go (XExpr x) | GhcTc <- ghcPass @p ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -557,6 +557,7 @@ type family XRecordCon x type family XRecordUpd x type family XGetField x type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -273,6 +273,7 @@ dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" -- getField expressions by now. dsExpr (GetField{}) = panic "dsExpr: GetField" dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -153,22 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" --- e.g. "foo.bar.baz = 42" is --- ProjBind { --- pb_fIELDS=["foo","bar","baz"] --- , pb_exp=42 --- , pb_func=\a -> setField@"foo" a .... 42 --- } -data ProjUpdate' p arg = - ProjUpdate { - pb_fIELDS :: [Located FastString] - , pb_arg :: arg -- Field's new value e.g. 42 - , pb_func :: arg -> arg - } -type ProjUpdate p arg = ProjUpdate' p arg -type LHsProjUpdate p arg = Located (ProjUpdate p arg) -type RecUpdProj p = ProjUpdate' p (LHsExpr p) -type LHsRecUpdProj p = Located (RecUpdProj p) +-- -- e.g. "foo.bar.baz = 42" is +-- -- ProjUpdate { +-- -- pb_fIELDS=["foo","bar","baz"] +-- -- , pb_exp=42 +-- -- , pb_func=\a -> setField@"foo" a .... 42 +-- -- } +-- data ProjUpdate' p arg = +-- ProjUpdate { +-- pb_fIELDS :: [Located FastString] +-- , pb_arg :: arg -- Field's new value e.g. 42 +-- , pb_func :: arg -> arg +-- } +-- type ProjUpdate p arg = ProjUpdate' p arg +-- type LHsProjUpdate p arg = Located (ProjUpdate p arg) +-- type RecUpdProj p = ProjUpdate' p (LHsExpr p) +-- type LHsRecUpdProj p = Located (RecUpdProj p) data Fbind b = Fbind (LHsRecField GhcPs (Located b)) | Pbind (LHsProjUpdate GhcPs (Located b)) @@ -187,15 +187,6 @@ fbindsToEithers = fmap fbindToEither fbindToEither (Fbind x) = Left x fbindToEither (Pbind x) = Right x --- Next fix mkRdrRecordUpd' to return one of these. --- RecordDotUpdate { --- rdupd_ext :: XRecordDotUpdate --- , rdupd_expr :: LHsExpr GhcPs --- , rdupd_updates :: [LHsRecUpdProj GhcPs] --- , rupd_setField :: LHsExpr GhcPs -- The equivalent setField term. --- } --- - {- ********************************************************************** Construction functions for Rdr stuff @@ -2406,10 +2397,10 @@ mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = mkRdrRecordUpd' dot exp fs + | otherwise = mkRdrRecordDotUpd dot exp fs -mkRdrRecordUpd' :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) -mkRdrRecordUpd' dot exp@(L _ _) fbinds = +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = if not dot then do let (fs, ps) = partitionEithers $ fbindsToEithers fbinds @@ -2421,7 +2412,13 @@ mkRdrRecordUpd' dot exp@(L _ _) fbinds = panic "mkRdrRecordUpd': The impossible happened!" else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) else - return $ foldl' fieldUpdate (unLoc exp) (toProjUpdates fbinds) + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } where toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] toProjUpdates = map (\case { Pbind p -> p @@ -2429,7 +2426,7 @@ mkRdrRecordUpd' dot exp@(L _ _) fbinds = }) fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs - fieldUpdate acc (L _ pu) = unLoc ((pb_func pu) (noLoc acc)) + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -3063,26 +3060,20 @@ mkProjection loc fIELDS = , proj_projection = mkProj fIELDS } --- mkProjection :: SrcSpan -> Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs --- mkProjection loc maybeRhs fIELD = --- L loc Projection { --- proj_ext = noExtField --- , proj_rhs = maybeRhs --- , proj_fIELD = fIELD --- , proj_projection = mkProj maybeRhs fIELD --- } - -- mkSet a fIELD b calculates a set_field @fIELD expression. -- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b --- mkProjUpdate calculates functions representing dot notation record updates. mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) mkProjUpdate -- e.g {foo.bar.baz.quux = 43} l - fIELDS -- [foo, bar, baz, quux] - arg -- This is 'texp' (43 in the example). + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) = let { ; final = last fIELDS -- quux ; fields = init fIELDS -- [foo, bar, baz] @@ -3091,12 +3082,32 @@ mkProjUpdate -- e.g {foo.bar.baz.quux = 43} ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] } - in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} + in (\a -> foldl' mkSet' arg (zips a)) -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) where mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) +-- -- mkProjUpdate calculates functions representing dot notation record updates. +-- mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +-- mkProjUpdate -- e.g {foo.bar.baz.quux = 43} +-- l +-- fIELDS -- [foo, bar, baz, quux] +-- arg -- This is 'texp' (43 in the example). +-- = let { +-- ; final = last fIELDS -- quux +-- ; fields = init fIELDS -- [foo, bar, baz] +-- ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. +-- -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] +-- ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. +-- -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] +-- } +-- in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} +-- -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) +-- where +-- mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs +-- mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + -- Transform a regular record field update into a projection update. recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -223,6 +223,19 @@ rnExpr (Projection x fs p) ; return (Projection x fs p', fv) } +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1038,6 +1038,7 @@ tcExpr (ArithSeq _ witness seq) res_ty -} tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty {- ************************************************************************ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -513,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9565c1533e19c65df0e949d07f0b14d905f9dcd9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9565c1533e19c65df0e949d07f0b14d905f9dcd9 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 Tue Nov 24 02:18:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 21:18:56 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/tsan-ghc-8.10 Message-ID: <5fbc6d909db67_36a73fd2f208ef80816135@gitlab.mail> Ben Gamari pushed new branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/tsan-ghc-8.10 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 Tue Nov 24 02:29:44 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Mon, 23 Nov 2020 21:29:44 -0500 Subject: [Git][ghc/ghc][wip/T18599] Add RecordDotUpd syntax Message-ID: <5fbc7018a2289_36a715ae31b0819284@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 15fdebc8 by Shayne Fletcher at 2020-11-23T21:29:26-05:00 Add RecordDotUpd syntax - - - - - 7 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax + +-- e.g. "foo.bar.baz = 42" is +-- ProjUpdate { +-- pb_fIELDS=["foo","bar","baz"] +-- , pb_exp=42 +-- , pb_func=\a -> setField@"foo" a .... 42 +-- } +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -473,31 +495,35 @@ data HsExpr p } -- Record update. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDotdot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. - -- We call this RecordDotUpd in sympathy with RecordUpd. - -- e.g. a{foo.bar.baz=1, quux} = RecordDotUpd { -- rdupd_ext=noExtField, rdupd_expr=a, rdupd_updates=[...], rdupd_setField=setField@"quux" (setField@"foo"...a... 1) quux -- }, - -- | RecordDotUpd - -- { rdupd_ext :: XRecordDotUpd - -- , rdupd_expr :: LHsExpr GhcPs - -- , rdupd_updates :: [LHsProjUpdate GhcPs (LHsExpr GhcPs)] - -- , rdupd_setField :: LHsExpr GhcPs -- Equivalent 'setField' term. - -- } + + | RecordDotUpd + { rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } -- | Record field selector. -- Expressions of these cases arise only when the RecordDotSyntax -- langauge extensions is enabled. - -- e.g. .x = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x - -- }, - -- .x.y = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) - -- } + -- e.g. (.x) = Projection { + -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x + -- }, + -- (.x.y) = Projection { + -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) + -- } | Projection { proj_ext :: XProjection p , proj_fIELDS :: [Located FastString] @@ -629,6 +655,7 @@ data RecordUpdTc = RecordUpdTc data GetFieldTc = GetFieldTc data ProjectionTc = ProjectionTc +data RecordDotUpdTc = RecordDotUpdTc -- | HsWrap appears only in typechecker output -- Invariant: The contained Expr is *NOT* itself an HsWrap. @@ -706,6 +733,10 @@ type instance XProjection GhcPs = NoExtField type instance XProjection GhcRn = NoExtField type instance XProjection GhcTc = NoExtField +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1257,6 +1288,9 @@ ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field, gf_getField = _}) ppr_expr (Projection { proj_fIELDS = _, proj_projection = _}) = undefined {- TODO: implement this -} +ppr_expr (RecordDotUpd { rdupd_expr = _, rdupd_upds = _, rdupd_setField =_ }) + = undefined {- TODO: implement this -} + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1414,6 +1448,7 @@ hsExprNeedsParens p = go go (Projection{}) = True go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False go (XExpr x) | GhcTc <- ghcPass @p ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -557,6 +557,7 @@ type family XRecordCon x type family XRecordUpd x type family XGetField x type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -273,6 +273,7 @@ dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" -- getField expressions by now. dsExpr (GetField{}) = panic "dsExpr: GetField" dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -153,23 +153,6 @@ import Data.Kind ( Type ) #include "HsVersions.h" --- e.g. "foo.bar.baz = 42" is --- ProjBind { --- pb_fIELDS=["foo","bar","baz"] --- , pb_exp=42 --- , pb_func=\a -> setField@"foo" a .... 42 --- } -data ProjUpdate' p arg = - ProjUpdate { - pb_fIELDS :: [Located FastString] - , pb_arg :: arg -- Field's new value e.g. 42 - , pb_func :: arg -> arg - } -type ProjUpdate p arg = ProjUpdate' p arg -type LHsProjUpdate p arg = Located (ProjUpdate p arg) -type RecUpdProj p = ProjUpdate' p (LHsExpr p) -type LHsRecUpdProj p = Located (RecUpdProj p) - data Fbind b = Fbind (LHsRecField GhcPs (Located b)) | Pbind (LHsProjUpdate GhcPs (Located b)) @@ -187,15 +170,6 @@ fbindsToEithers = fmap fbindToEither fbindToEither (Fbind x) = Left x fbindToEither (Pbind x) = Right x --- Next fix mkRdrRecordUpd' to return one of these. --- RecordDotUpdate { --- rdupd_ext :: XRecordDotUpdate --- , rdupd_expr :: LHsExpr GhcPs --- , rdupd_updates :: [LHsRecUpdProj GhcPs] --- , rupd_setField :: LHsExpr GhcPs -- The equivalent setField term. --- } --- - {- ********************************************************************** Construction functions for Rdr stuff @@ -2406,10 +2380,10 @@ mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = mkRdrRecordUpd' dot exp fs + | otherwise = mkRdrRecordDotUpd dot exp fs -mkRdrRecordUpd' :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) -mkRdrRecordUpd' dot exp@(L _ _) fbinds = +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = if not dot then do let (fs, ps) = partitionEithers $ fbindsToEithers fbinds @@ -2421,7 +2395,13 @@ mkRdrRecordUpd' dot exp@(L _ _) fbinds = panic "mkRdrRecordUpd': The impossible happened!" else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) else - return $ foldl' fieldUpdate (unLoc exp) (toProjUpdates fbinds) + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } where toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] toProjUpdates = map (\case { Pbind p -> p @@ -2429,7 +2409,7 @@ mkRdrRecordUpd' dot exp@(L _ _) fbinds = }) fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs - fieldUpdate acc (L _ pu) = unLoc ((pb_func pu) (noLoc acc)) + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -3063,26 +3043,20 @@ mkProjection loc fIELDS = , proj_projection = mkProj fIELDS } --- mkProjection :: SrcSpan -> Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs --- mkProjection loc maybeRhs fIELD = --- L loc Projection { --- proj_ext = noExtField --- , proj_rhs = maybeRhs --- , proj_fIELD = fIELD --- , proj_projection = mkProj maybeRhs fIELD --- } - -- mkSet a fIELD b calculates a set_field @fIELD expression. -- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b --- mkProjUpdate calculates functions representing dot notation record updates. mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) mkProjUpdate -- e.g {foo.bar.baz.quux = 43} l - fIELDS -- [foo, bar, baz, quux] - arg -- This is 'texp' (43 in the example). + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) = let { ; final = last fIELDS -- quux ; fields = init fIELDS -- [foo, bar, baz] @@ -3091,12 +3065,32 @@ mkProjUpdate -- e.g {foo.bar.baz.quux = 43} ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] } - in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} + in (\a -> foldl' mkSet' arg (zips a)) -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) where mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) +-- -- mkProjUpdate calculates functions representing dot notation record updates. +-- mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +-- mkProjUpdate -- e.g {foo.bar.baz.quux = 43} +-- l +-- fIELDS -- [foo, bar, baz, quux] +-- arg -- This is 'texp' (43 in the example). +-- = let { +-- ; final = last fIELDS -- quux +-- ; fields = init fIELDS -- [foo, bar, baz] +-- ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. +-- -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] +-- ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. +-- -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] +-- } +-- in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} +-- -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) +-- where +-- mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs +-- mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + -- Transform a regular record field update into a projection update. recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -223,6 +223,19 @@ rnExpr (Projection x fs p) ; return (Projection x fs p', fv) } +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1038,6 +1038,7 @@ tcExpr (ArithSeq _ witness seq) res_ty -} tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty {- ************************************************************************ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -513,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/15fdebc88d742a5f84bf6ccc0d0525f395d38920 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/15fdebc88d742a5f84bf6ccc0d0525f395d38920 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 Tue Nov 24 02:29:59 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 21:29:59 -0500 Subject: [Git][ghc/ghc][wip/win32-m32] 5 commits: rts: Introduce mmapAnonForLinker Message-ID: <5fbc7027d55d9_36a715ae31b081942d@gitlab.mail> Ben Gamari pushed to branch wip/win32-m32 at Glasgow Haskell Compiler / GHC Commits: 212a811d by Ben Gamari at 2020-11-23T21:29:50-05:00 rts: Introduce mmapAnonForLinker Previously most of the uses of mmapForLinker were mapping anonymous memory, resulting in a great deal of unnecessary repetition. Factor this out into a new helper. Also fixes a few places where error checking was missing or suboptimal. - - - - - f602af1a by Ben Gamari at 2020-11-23T21:29:50-05:00 rts/linker: Introduce munmapForLinker Consolidates munmap calls to ensure consistent error handling. - - - - - 76637b92 by Ben Gamari at 2020-11-23T21:29:50-05:00 rts/Linker: Introduce Windows implementations for mmapForLinker, et al. - - - - - 4b7ef096 by Ben Gamari at 2020-11-23T21:29:50-05:00 rts/m32: Introduce NEEDS_M32 macro Instead of relying on RTS_LINKER_USE_MMAP - - - - - 267c1245 by Ben Gamari at 2020-11-23T21:29:50-05:00 rts/linker: Use m32 to allocate symbol extras in PEi386 - - - - - 10 changed files: - rts/Linker.c - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/M32Alloc.c - rts/linker/M32Alloc.h - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/SymbolExtras.c - rts/linker/elf_got.c Changes: ===================================== rts/Linker.c ===================================== @@ -45,6 +45,8 @@ #include #endif +#include +#include #include #include #include @@ -1026,7 +1028,38 @@ resolveSymbolAddr (pathchar* buffer, int size, #endif /* OBJFORMAT_PEi386 */ } -#if RTS_LINKER_USE_MMAP +#if defined(mingw32_HOST_OS) + +// +// Returns NULL on failure. +// +void * +mmapAnonForLinker (size_t bytes) +{ + return VirtualAlloc(NULL, bytes, MEM_COMMIT | MEM_RESERVE, PAGE_READWRITE); +} + +void +munmapForLinker (void *addr, size_t bytes, const char *caller) +{ + if (VirtualFree(addr, 0, MEM_RELEASE) == 0) { + sysErrorBelch("munmapForLinker: %s: Failed to unmap %zd bytes at %p", + caller, bytes, addr); + } +} + +void +mmapForLinkerMarkExecutable(void *start, size_t len) +{ + DWORD old; + if (VirtualProtect(start, len, PAGE_EXECUTE_READ, &old) == 0) { + sysErrorBelch("mmapForLinkerMarkExecutable: failed to protect %zd bytes at %p", + len, start); + ASSERT(false); + } +} + +#elif RTS_LINKER_USE_MMAP // // Returns NULL on failure. // @@ -1085,7 +1118,7 @@ mmap_again: fixed = MAP_FIXED; goto mmap_again; #else - errorBelch("loadObj: failed to mmap() memory below 2Gb; " + errorBelch("mmapForLinker: failed to mmap() memory below 2Gb; " "asked for %lu bytes at %p. " "Try specifying an address with +RTS -xm -RTS", size, map_addr); @@ -1145,6 +1178,24 @@ mmap_again: return result; } +/* + * Map read/write pages in low memory. Returns NULL on failure. + */ +void * +mmapAnonForLinker (size_t bytes) +{ + return mmapForLinker (bytes, PROT_READ|PROT_WRITE, MAP_ANONYMOUS, -1, 0); +} + +void munmapForLinker (void *addr, size_t bytes, const char *caller) +{ + int r = munmap(addr, bytes); + if (r == -1) { + // Should we abort here? + sysErrorBelch("munmap: %s", caller); + } +} + /* Note [Memory protection in the linker] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * For many years the linker would simply map all of its memory @@ -1230,7 +1281,7 @@ freePreloadObjectFile (ObjectCode *oc) #else if (RTS_LINKER_USE_MMAP && oc->imageMapped) { - munmap(oc->image, oc->fileSize); + munmapForLinker(oc->image, oc->fileSize, "freePreloadObjectFile"); } else { stgFree(oc->image); @@ -1278,13 +1329,15 @@ void freeObjectCode (ObjectCode *oc) switch(oc->sections[i].alloc){ #if RTS_LINKER_USE_MMAP case SECTION_MMAP: - munmap(oc->sections[i].mapped_start, - oc->sections[i].mapped_size); + munmapForLinker( + oc->sections[i].mapped_start, + oc->sections[i].mapped_size, + "freeObjectCode"); break; +#endif case SECTION_M32: // Freed by m32_allocator_free break; -#endif case SECTION_MALLOC: IF_DEBUG(zero_on_gc, memset(oc->sections[i].start, @@ -1327,7 +1380,7 @@ void freeObjectCode (ObjectCode *oc) ocDeinit_ELF(oc); #endif -#if RTS_LINKER_USE_MMAP == 1 +#if defined(NEED_M32) m32_allocator_free(oc->rx_m32); m32_allocator_free(oc->rw_m32); #endif @@ -1405,7 +1458,7 @@ mkOc( ObjectType type, pathchar *path, char *image, int imageSize, oc->mark = object_code_mark_bit; oc->dependencies = allocHashSet(); -#if RTS_LINKER_USE_MMAP +#if defined(NEED_M32) oc->rw_m32 = m32_allocator_new(false); oc->rx_m32 = m32_allocator_new(true); #endif @@ -1742,7 +1795,7 @@ int ocTryLoad (ObjectCode* oc) { // We have finished loading and relocating; flush the m32 allocators to // setup page protections. -#if RTS_LINKER_USE_MMAP +#if defined(NEED_M32) m32_allocator_flush(oc->rx_m32); m32_allocator_flush(oc->rw_m32); #endif @@ -2168,7 +2221,7 @@ void freeSegments (ObjectCode *oc) continue; } else { #if RTS_LINKER_USE_MMAP - CHECKM(0 == munmap(s->start, s->size), "freeSegments: failed to unmap memory"); + munmapForLinker(s->start, s->size, "freeSegments"); #else stgFree(s->start); #endif ===================================== rts/LinkerInternals.h ===================================== @@ -145,6 +145,14 @@ typedef struct _Segment { #define NEED_SYMBOL_EXTRAS 1 #endif +/* + * We use the m32 allocator for symbol extras on Windows and other mmap-using + * platforms. + */ +#if RTS_LINKER_USE_MMAP || defined(mingw32_HOST_ARCH) +#define NEED_M32 1 +#endif + /* Jump Islands are sniplets of machine code required for relative * address relocations on the PowerPC, x86_64 and ARM. */ @@ -276,7 +284,7 @@ typedef struct _ObjectCode { require extra information.*/ StrHashTable *extraInfos; -#if RTS_LINKER_USE_MMAP == 1 +#if defined(NEED_M32) /* The m32 allocators used for allocating small sections and symbol extras * during loading. We have two: one for (writeable) data and one for * (read-only/executable) code. */ @@ -334,8 +342,10 @@ void exitLinker( void ); void freeObjectCode (ObjectCode *oc); SymbolAddr* loadSymbol(SymbolName *lbl, RtsSymbolInfo *pinfo); +void *mmapAnonForLinker (size_t bytes); void *mmapForLinker (size_t bytes, uint32_t prot, uint32_t flags, int fd, int offset); void mmapForLinkerMarkExecutable (void *start, size_t len); +void munmapForLinker (void *addr, size_t bytes, const char *caller); void addProddableBlock ( ObjectCode* oc, void* start, int size ); void checkProddableBlock (ObjectCode *oc, void *addr, size_t size ); ===================================== rts/linker/Elf.c ===================================== @@ -25,6 +25,7 @@ #include "linker/elf_util.h" #include +#include #include #if defined(HAVE_SYS_STAT_H) #include @@ -709,7 +710,11 @@ ocGetNames_ELF ( ObjectCode* oc ) * address might be out of range for sections that are mmaped. */ alloc = SECTION_MMAP; - start = mmapForLinker(size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + start = mmapAnonForLinker(size); + if (start == NULL) { + barf("failed to mmap memory for bss. " + "errno = %d", errno); + } mapped_start = start; mapped_offset = 0; mapped_size = roundUpToPage(size); @@ -751,9 +756,9 @@ ocGetNames_ELF ( ObjectCode* oc ) unsigned nstubs = numberOfStubsForSection(oc, i); unsigned stub_space = STUB_SIZE * nstubs; - void * mem = mmapForLinker(size+stub_space, PROT_READ | PROT_WRITE, MAP_ANON, -1, 0); + void * mem = mmapAnonForLinker(size+stub_space); - if( mem == MAP_FAILED ) { + if( mem == NULL ) { barf("failed to mmap allocated memory to load section %d. " "errno = %d", i, errno); } @@ -855,11 +860,10 @@ ocGetNames_ELF ( ObjectCode* oc ) } void * common_mem = NULL; if(common_size > 0) { - common_mem = mmapForLinker(common_size, - PROT_READ | PROT_WRITE, - MAP_ANON | MAP_PRIVATE, - -1, 0); - ASSERT(common_mem != NULL); + common_mem = mmapAnonForLinker(common_size); + if (common_mem == NULL) { + barf("ocGetNames_ELF: Failed to allocate memory for SHN_COMMONs"); + } } //TODO: we ignore local symbols anyway right? So we can use the ===================================== rts/linker/LoadArchive.c ===================================== @@ -489,7 +489,7 @@ static HsInt loadArchive_ (pathchar *path) #if defined(darwin_HOST_OS) || defined(ios_HOST_OS) if (RTS_LINKER_USE_MMAP) - image = mmapForLinker(memberSize, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + image = mmapAnonForLinker(memberSize); else { /* See loadObj() */ misalignment = machoGetMisalignment(f); @@ -549,7 +549,7 @@ while reading filename from `%" PATH_FMT "'", path); } DEBUG_LOG("Found GNU-variant file index\n"); #if RTS_LINKER_USE_MMAP - gnuFileIndex = mmapForLinker(memberSize + 1, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + gnuFileIndex = mmapAnonForLinker(memberSize + 1); #else gnuFileIndex = stgMallocBytes(memberSize + 1, "loadArchive(image)"); #endif @@ -613,7 +613,7 @@ fail: stgFree(fileName); if (gnuFileIndex != NULL) { #if RTS_LINKER_USE_MMAP - munmap(gnuFileIndex, gnuFileIndexSize + 1); + munmapForLinker(gnuFileIndex, gnuFileIndexSize + 1, "loadArchive_"); #else stgFree(gnuFileIndex); #endif ===================================== rts/linker/M32Alloc.c ===================================== @@ -42,7 +42,7 @@ still check the call for syntax and correct function parameter types. */ -#if RTS_LINKER_USE_MMAP == 1 +#if defined(NEED_M32) /* @@ -216,25 +216,6 @@ struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO -/** - * Wrapper for `unmap` that handles error cases. - * This is the real implementation. There is another dummy implementation below. - * See the note titled "Compile Time Trickery" at the top of this file. - */ -static void -munmapForLinker (void * addr, size_t size) -{ - IF_DEBUG(linker, - debugBelch("m32_alloc: Unmapping %zu bytes at %p\n", - size, addr)); - - int r = munmap(addr,size); - if (r == -1) { - // Should we abort here? - sysErrorBelch("munmap"); - } -} - /** * Free a page or, if possible, place it in the free page pool. */ @@ -246,7 +227,7 @@ m32_release_page(struct m32_page_t *page) m32_free_page_pool = page; m32_free_page_pool_size ++; } else { - munmapForLinker((void *) page, getPageSize()); + munmapForLinker((void *) page, getPageSize(), "m32_release_page"); } } @@ -263,7 +244,7 @@ m32_alloc_page(void) * pages. */ const size_t pgsz = getPageSize(); - char *chunk = mmapForLinker(pgsz * M32_MAP_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + char *chunk = mmapAnonForLinker(pgsz * M32_MAP_PAGES); if (chunk > (char *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } @@ -309,7 +290,7 @@ m32_allocator_unmap_list(struct m32_page_t *head) { while (head != NULL) { struct m32_page_t *next = m32_filled_page_get_next(head); - munmapForLinker((void *) head, head->filled_page.size); + munmapForLinker((void *) head, head->filled_page.size, "m32_allocator_unmap_list"); head = next; } } @@ -327,7 +308,7 @@ void m32_allocator_free(m32_allocator *alloc) const size_t pgsz = getPageSize(); for (int i=0; i < M32_MAX_PAGES; i++) { if (alloc->pages[i]) { - munmapForLinker(alloc->pages[i], pgsz); + munmapForLinker(alloc->pages[i], pgsz, "m32_allocator_free"); } } @@ -407,7 +388,14 @@ m32_alloc(struct m32_allocator_t *alloc, size_t size, size_t alignment) if (m32_is_large_object(size,alignment)) { // large object size_t alsize = ROUND_UP(sizeof(struct m32_page_t), alignment); - struct m32_page_t *page = mmapForLinker(alsize+size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); + struct m32_page_t *page = mmapAnonForLinker(alsize+size); + if (page == NULL) { + sysErrorBelch("m32_alloc: Failed to map pages for %zd bytes", size); + return NULL; + } else if (page > (struct m32_page_t *) 0xffffffff) { + debugBelch("m32_alloc: warning: Allocation of %zd bytes resulted in pages above 4GB (%p)", + size, page); + } page->filled_page.size = alsize + size; m32_allocator_push_filled_list(&alloc->unprotected_list, (struct m32_page_t *) page); return (char*) page + alsize; @@ -460,7 +448,7 @@ m32_alloc(struct m32_allocator_t *alloc, size_t size, size_t alignment) return (char*)page + ROUND_UP(sizeof(struct m32_page_t),alignment); } -#elif RTS_LINKER_USE_MMAP == 0 +#else // The following implementations of these functions should never be called. If // they are, there is a bug at the call site. @@ -491,8 +479,4 @@ m32_alloc(m32_allocator *alloc STG_UNUSED, barf("%s: RTS_LINKER_USE_MMAP is %d", __func__, RTS_LINKER_USE_MMAP); } -#else - -#error RTS_LINKER_USE_MMAP should be either `0` or `1`. - #endif ===================================== rts/linker/M32Alloc.h ===================================== @@ -8,19 +8,17 @@ #pragma once -#if RTS_LINKER_USE_MMAP == 1 -#include -#include - -#if defined(HAVE_UNISTD_H) -#include -#endif - +/* + * We use the m32 allocator for symbol extras on Windows and other mmap-using + * platforms. + */ +#if RTS_LINKER_USE_MMAP || defined(mingw32_HOST_OS) +#define NEED_M32 1 #endif #include "BeginPrivate.h" -#if RTS_LINKER_USE_MMAP +#if defined(NEED_M32) #define M32_NO_RETURN /* Nothing */ #else #define M32_NO_RETURN GNUC3_ATTRIBUTE(__noreturn__) ===================================== rts/linker/MachO.c ===================================== @@ -508,11 +508,8 @@ makeGot(ObjectCode * oc) { if(got_slots > 0) { oc->info->got_size = got_slots * sizeof(void*); - oc->info->got_start = mmapForLinker(oc->info->got_size, - PROT_READ | PROT_WRITE, - MAP_ANON | MAP_PRIVATE, - -1, 0); - if( oc->info->got_start == MAP_FAILED ) { + oc->info->got_start = mmapAnonForLinker(oc->info->got_size); + if( oc->info->got_start == NULL ) { barf("MAP_FAILED. errno=%d", errno ); return EXIT_FAILURE; } @@ -529,7 +526,7 @@ makeGot(ObjectCode * oc) { void freeGot(ObjectCode * oc) { - munmap(oc->info->got_start, oc->info->got_size); + munmapForLinker(oc->info->got_start, oc->info->got_size, "freeGot"); oc->info->got_start = NULL; oc->info->got_size = 0; } @@ -1114,7 +1111,7 @@ ocBuildSegments_MachO(ObjectCode *oc) return 1; } - mem = mmapForLinker(size_compound, PROT_READ | PROT_WRITE, MAP_ANON, -1, 0); + mem = mmapAnonForLinker(size_compound); if (NULL == mem) return 0; IF_DEBUG(linker, debugBelch("ocBuildSegments: allocating %d segments\n", n_activeSegments)); ===================================== rts/linker/PEi386.c ===================================== @@ -1788,42 +1788,28 @@ ocGetNames_PEi386 ( ObjectCode* oc ) bool ocAllocateExtras_PEi386 ( ObjectCode* oc ) { - /* If the ObjectCode was unloaded we don't need a trampoline, it's likely - an import library so we're discarding it earlier. */ - if (!oc->info) - return false; + /* If the ObjectCode was unloaded we don't need a trampoline, it's likely + an import library so we're discarding it earlier. */ + if (!oc->info) + return false; - const int mask = default_alignment - 1; - size_t origin = oc->info->trampoline; - oc->symbol_extras - = (SymbolExtra*)((uintptr_t)(oc->info->image + origin + mask) & ~mask); - oc->first_symbol_extra = 0; - COFF_HEADER_INFO *info = oc->info->ch_info; - oc->n_symbol_extras = info->numberOfSymbols; + // These are allocated on-demand from m32 by makeSymbolExtra_PEi386 + oc->first_symbol_extra = 0; + oc->n_symbol_extras = 0; + oc->symbol_extras = NULL; - return true; + return true; } static size_t -makeSymbolExtra_PEi386( ObjectCode* oc, uint64_t index, size_t s, char* symbol ) +makeSymbolExtra_PEi386( ObjectCode* oc, uint64_t index STG_UNUSED, size_t s, char* symbol STG_UNUSED ) { - unsigned int curr_thunk; - SymbolExtra *extra; - curr_thunk = oc->first_symbol_extra + index; - if (index >= oc->n_symbol_extras) { - IF_DEBUG(linker, debugBelch("makeSymbolExtra first:%d, num:%lu, member:%" PATH_FMT ", index:%llu\n", curr_thunk, oc->n_symbol_extras, oc->archiveMemberName, index)); - barf("Can't allocate thunk for `%s' in `%" PATH_FMT "' with member `%" PATH_FMT "'", symbol, oc->fileName, oc->archiveMemberName); - } - - extra = oc->symbol_extras + curr_thunk; + SymbolExtra *extra = m32_alloc(oc->rx_m32, sizeof(SymbolExtra), 8); - if (!extra->addr) - { - // jmp *-14(%rip) - static uint8_t jmp[] = { 0xFF, 0x25, 0xF2, 0xFF, 0xFF, 0xFF }; - extra->addr = (uint64_t)s; - memcpy(extra->jumpIsland, jmp, 6); - } + // jmp *-14(%rip) + static uint8_t jmp[] = { 0xFF, 0x25, 0xF2, 0xFF, 0xFF, 0xFF }; + extra->addr = (uint64_t)s; + memcpy(extra->jumpIsland, jmp, 6); return (size_t)extra->jumpIsland; } ===================================== rts/linker/SymbolExtras.c ===================================== @@ -81,11 +81,11 @@ int ocAllocateExtras(ObjectCode* oc, int count, int first, int bssSize) // symbol_extras is aligned to a page boundary so it can be mprotect'd. bssSize = roundUpToPage(bssSize); size_t allocated_size = n + bssSize + extras_size; - void *new = mmapForLinker(allocated_size, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + void *new = mmapAnonForLinker(allocated_size); if (new) { memcpy(new, oc->image, oc->fileSize); if (oc->imageMapped) { - munmap(oc->image, n); + munmapForLinker(oc->image, n, "ocAllocateExtras"); } oc->image = new; oc->imageMapped = true; ===================================== rts/linker/elf_got.c ===================================== @@ -48,11 +48,8 @@ makeGot(ObjectCode * oc) { } if(got_slots > 0) { oc->info->got_size = got_slots * sizeof(void *); - void * mem = mmapForLinker(oc->info->got_size, - PROT_READ | PROT_WRITE, - MAP_ANON | MAP_PRIVATE, - -1, 0); - if (mem == MAP_FAILED) { + void * mem = mmapAnonForLinker(oc->info->got_size); + if (mem == NULL) { errorBelch("MAP_FAILED. errno=%d", errno); return EXIT_FAILURE; } @@ -147,7 +144,7 @@ verifyGot(ObjectCode * oc) { void freeGot(ObjectCode * oc) { -// munmap(oc->info->got_start, oc->info->got_size); +// munmapForLinker(oc->info->got_start, oc->info->got_size, "freeGot); oc->info->got_start = 0x0; oc->info->got_size = 0; } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4cd87229f71c639f2f8b1217c22c92b8bcb18d7a...267c1245823d18567e00663c10c0afd92e5b3977 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4cd87229f71c639f2f8b1217c22c92b8bcb18d7a...267c1245823d18567e00663c10c0afd92e5b3977 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 Tue Nov 24 02:40:34 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 21:40:34 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] 2 commits: 8.10 - dirty MVAR after mutating TSO queue head Message-ID: <5fbc72a272d_36a73fd2f1d864008279d@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 1e9486bd by Viktor Dukhovni at 2020-11-23T21:40:16-05:00 8.10 - dirty MVAR after mutating TSO queue head While the original head and tail of the TSO queue may be in the same generation as the MVAR, interior elements of the queue could be younger after a GC run and may then be exposed by putMVar operation that updates the queue head. Resolves #18919 (cherry picked from commit 699facec0bc8dd7d5b82cc537fbf131b74f5bd2c) - - - - - 3bcb5522 by Ömer Sinan Ağacan at 2020-11-23T21:40:17-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 27 changed files: - compiler/ghci/Linker.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/PrimOps.cmm - rts/RtsStartup.c - rts/Threads.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/linker_error.c Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1134,14 +1134,15 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do where unloadObjs :: Linkable -> IO () unloadObjs lnk + -- The RTS's PEi386 linker currently doesn't support unloading. + | isWindowsHost = return () + | dynamicGhc = return () -- We don't do any cleanup when linking objects with the -- dynamic linker. Doing so introduces extra complexity for -- not much benefit. - -- Code unloading currently disabled due to instability. - -- See #16841. - | False -- otherwise + | otherwise = mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk] -- The components of a BCO linkable may contain -- dot-o files. Which is very confusing. @@ -1149,7 +1150,6 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do -- But the BCO parts can be unlinked just by -- letting go of them (plus of course depopulating -- the symbol table which is done in the main body) - | otherwise = return () -- see #16841 {- ********************************************************************** ===================================== rts/CheckUnload.c ===================================== @@ -17,43 +17,99 @@ #include "CheckUnload.h" #include "sm/Storage.h" #include "sm/GCThread.h" +#include "sm/HeapUtils.h" // -// Code that we unload may be referenced from: -// - info pointers in heap objects and stack frames -// - pointers to static objects from the heap -// - StablePtrs to static objects -// - pointers to cost centres from the cost centre tree +// Note [Object unloading] +// ~~~~~~~~~~~~~~~~~~~~~~~ // -// We can find live static objects after a major GC, so we don't have -// to look at every closure pointer in the heap. However, we do have -// to look at every info pointer. So this is like a heap census -// traversal: we look at the header of every object, but not its -// contents. +// Overview of object unloading: // -// On the assumption that there aren't many different info pointers in -// a typical heap, we insert addresses into a hash table. The -// first time we see an address, we check it against the pending -// unloadable objects and if it lies within any of them, we mark that -// object as referenced so that it won't get unloaded in this round. +// - In a major GC, for every static object we mark the object's object code and +// its dependencies as 'live'. This is done by `markObjectCode`, called by +// `evacuate`. // - -// Note [Speeding up checkUnload] -// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -// In certain circumstances, there may be a lot of unloaded ObjectCode structs -// chained in `unloaded_objects` (such as when users `:load` a module in a very -// big repo in GHCi). To speed up checking whether an address lies within any of -// these objects, we populate the addresses of their mapped sections in -// an array sorted by their `start` address and do binary search for our address -// on that array. Note that this works because the sections are mapped to mutual -// exclusive memory regions, so we can simply find the largest lower bound among -// the `start` addresses of the sections and then check if our address is inside -// that section. In particular, we store the start address and end address of -// each mapped section in a OCSectionIndex, arrange them all on a contiguous -// memory range and then sort by start address. We then put this array in an -// OCSectionIndices struct to be passed into `checkAddress` to do binary search -// on. +// - Marking object code is done using a global "section index table" +// (global_s_indices below). When we load an object code we add its section +// indices to the table. `markObjectCode` does binary search on this table to +// find object code for the marked object, and mark it and its dependencies. +// +// Dependency of an object code is simply other object code that the object +// code refers to in its code. We know these dependencies by the relocations +// present in the referent. This is recorded by lookupSymbolDependent. +// +// - global_s_indices is updated as we load and unload objects. When we load an +// object code we add its section indices to the table, we remove those +// indices when we unload. +// +// The table is sorted and old indices are removed in `checkUnload`, instead +// on every load/unload, to avoid quadratic behavior when we load a list of +// objects. +// +// - After a major GC `checkUnload` unloads objects that are (1) explicitly +// asked for unloading (via `unloadObj`) and (2) are not marked during GC. +// +// Note that, crucially, we don't unload an object code even if it's not +// reachable from the heap, unless it's explicitly asked for unloading (via +// `unloadObj`). This is a feature and not a but! Two use cases: +// +// - The user might request a symbol from a loaded object at any point with +// lookupSymbol (e.g. GHCi might do this). +// +// - Sometimes we load objects that are not Haskell objects. +// +// To avoid unloading objects that are unreachable but are not asked for +// unloading we maintain a "root set" of object code, `loaded_objects` below. +// `loadObj` adds the loaded objects (and its dependencies) to the list. +// `unloadObj` removes. After a major GC, `checkUnload` first marks the root set +// (`loaded_objects`) to avoid unloading objects that are not asked for +// unloading. +// +// Two other lists `objects` and `old_objects` are similar to large object lists +// in GC. Before a major GC we move `objects` to `old_objects`, and move marked +// objects back to `objects` during evacuation and when marking roots in +// `checkUnload`. Any objects in `old_objects` after that is unloaded. +// +// TODO: We currently don't unload objects when non-moving GC is enabled. The +// implementation would be similar to `nonmovingGcCafs`: +// +// - Maintain a "snapshot": +// +// - Copy `loaded_objects` as the root set of the snapshot +// +// - Stash `objects` to `old_objects` as the snapshot. We don't need a new +// list for this as `old_objects` won't be used by any other code when +// non-moving GC is enabled. +// +// - Copy `global_s_indices` table to be able to mark objects while mutators +// call `loadObj_` and `unloadObj_` concurrently. +// +// - Don't mark object code in `evacuate`, marking will be done in the +// non-moving collector. // +// - After preparation, bump the object code mark bit (`object_code_mark_bit` +// below) and mark static objects using a version of `markObjectCode` that +// basically does the same thing but: +// +// - Needs to update `objects` list in a thread-safe way, as mutators will be +// concurrently calling `loadObj_` and add new stuff to `objects`. +// (alternatively we could have a new list for non-moving GC's objects list, +// and then merge it to the global list in the pause before moving to +// concurrent sweep phase) +// +// - Needs to use the copied `global_s_indices` +// +// - After marking anything left in `old_objects` are unreachable objects within +// the snapshot, unload those. The unload loop will be the same as in +// `checkUnload`. This step needs to happen in the final sync (before sweep +// begins) to avoid races when updating `global_s_indices`. +// +// - NOTE: We don't need write barriers in loadObj/unloadObj as we don't +// introduce a dependency from an already-loaded object to a newly loaded +// object and we don't delete existing dependencies. +// + +uint8_t object_code_mark_bit = 0; typedef struct { W_ start; @@ -62,20 +118,85 @@ typedef struct { } OCSectionIndex; typedef struct { + int capacity; // Doubled on resize int n_sections; + bool sorted; // Invalidated on insertion. Sorted in checkUnload. + bool unloaded; // Whether we removed anything from the table in + // removeOCSectionIndices. If this is set we "compact" the + // table (remove unused entries) in `sortOCSectionIndices. OCSectionIndex *indices; } OCSectionIndices; -static OCSectionIndices *createOCSectionIndices(int n_sections) +// List of currently live objects. Moved to `old_objects` before unload check. +// Marked objects moved back to this list in `markObjectLive`. Remaining objects +// are freed at the end of `checkUnload`. +// +// Double-linked list to be able to remove marked objects. List formed with +// `next` and `prev` fields of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *objects = NULL; + +// `objects` list is moved here before unload check. Marked objects are moved +// back to `objects`. Remaining objects are freed. +static ObjectCode *old_objects = NULL; + +// Number of objects that we want to unload. When this value is 0 we skip static +// object marking during GC and `checkUnload`. +// +// Not static: we use this value to skip static object marking in evacuate when +// this is 0. +// +// Incremented in `unloadObj_`, decremented as we unload objects in +// `checkUnload`. +int n_unloaded_objects = 0; + +// List of objects that we don't want to unload (i.e. we haven't called +// unloadObj on these yet). Used as root set for unload check in checkUnload. +// Objects are added with loadObj_ and removed with unloadObj_. +// +// List formed with `next_loaded_object` field of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *loaded_objects; + +// Section index table for currently loaded objects. New indices are added by +// `loadObj_`, indices of unloaded objects are removed in `checkUnload`. Used to +// map static closures to their ObjectCode. +static OCSectionIndices *global_s_indices = NULL; + +static OCSectionIndices *createOCSectionIndices(void) { - OCSectionIndices *s_indices; - s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); - s_indices->n_sections = n_sections; - s_indices->indices = stgMallocBytes(n_sections*sizeof(OCSectionIndex), + // TODO (osa): Maybe initialize as empty (without allocation) and allocate + // on first insertion? + OCSectionIndices *s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); + int capacity = 1024; + s_indices->capacity = capacity; + s_indices->n_sections = 0; + s_indices->sorted = true; + s_indices->unloaded = false; + s_indices->indices = stgMallocBytes(capacity * sizeof(OCSectionIndex), "OCSectionIndices::indices"); return s_indices; } +static void freeOCSectionIndices(OCSectionIndices *s_indices) +{ + free(s_indices->indices); + free(s_indices); +} + +void initUnloadCheck() +{ + global_s_indices = createOCSectionIndices(); +} + +void exitUnloadCheck() +{ + freeOCSectionIndices(global_s_indices); + global_s_indices = NULL; +} + static int cmpSectionIndex(const void* indexa, const void *indexb) { W_ s1 = ((OCSectionIndex*)indexa)->start; @@ -88,44 +209,124 @@ static int cmpSectionIndex(const void* indexa, const void *indexb) return 0; } -static OCSectionIndices* buildOCSectionIndices(ObjectCode *ocs) +static void reserveOCSectionIndices(OCSectionIndices *s_indices, int len) { - int cnt_sections = 0; - ObjectCode *oc; - for (oc = ocs; oc; oc = oc->next) { - cnt_sections += oc->n_sections; + int current_capacity = s_indices->capacity; + int current_len = s_indices->n_sections; + if (current_capacity - current_len >= len) { + return; + } + + // Round up to nearest power of 2 + int new_capacity = 1 << (int)ceil(log2(current_len + len)); + + OCSectionIndex *old_indices = s_indices->indices; + OCSectionIndex *new_indices = stgMallocBytes(new_capacity * sizeof(OCSectionIndex), + "reserveOCSectionIndices"); + + for (int i = 0; i < current_len; ++i) { + new_indices[i] = old_indices[i]; } - OCSectionIndices* s_indices = createOCSectionIndices(cnt_sections); - int s_i = 0, i; - for (oc = ocs; oc; oc = oc->next) { - for (i = 0; i < oc->n_sections; i++) { - if (oc->sections[i].kind != SECTIONKIND_OTHER) { - s_indices->indices[s_i].start = (W_)oc->sections[i].start; - s_indices->indices[s_i].end = (W_)oc->sections[i].start - + oc->sections[i].size; - s_indices->indices[s_i].oc = oc; - s_i++; + + s_indices->capacity = new_capacity; + s_indices->indices = new_indices; + + free(old_indices); +} + +// Insert object section indices of a single ObjectCode. Invalidates 'sorted' +// state. +void insertOCSectionIndices(ObjectCode *oc) +{ + reserveOCSectionIndices(global_s_indices, oc->n_sections); + global_s_indices->sorted = false; + + int s_i = global_s_indices->n_sections; + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + global_s_indices->indices[s_i].start = (W_)oc->sections[i].start; + global_s_indices->indices[s_i].end = (W_)oc->sections[i].start + + oc->sections[i].size; + global_s_indices->indices[s_i].oc = oc; + s_i++; + } + } + + global_s_indices->n_sections = s_i; + + // Add object to 'objects' list + if (objects != NULL) { + objects->prev = oc; + } + oc->next = objects; + objects = oc; +} + +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr); + +static void removeOCSectionIndices(OCSectionIndices *s_indices, ObjectCode *oc) +{ + // To avoid quadratic behavior in checkUnload we set `oc` fields of indices + // of unloaded objects NULL here. Removing unused entries is done in + // `sortOCSectionIndices`. + + s_indices->unloaded = true; + + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + int section_idx = findSectionIdx(s_indices, oc->sections[i].start); + if (section_idx != -1) { + s_indices->indices[section_idx].oc = NULL; } } } - s_indices->n_sections = s_i; +} + +static void sortOCSectionIndices(OCSectionIndices *s_indices) { + if (s_indices->sorted) { + return; + } + qsort(s_indices->indices, s_indices->n_sections, sizeof(OCSectionIndex), cmpSectionIndex); - return s_indices; + + s_indices->sorted = true; } -static void freeOCSectionIndices(OCSectionIndices *section_indices) -{ - free(section_indices->indices); - free(section_indices); +static void removeRemovedOCSections(OCSectionIndices *s_indices) { + if (!s_indices->unloaded) { + return; + } + + int next_free_idx = 0; + for (int i = 0; i < s_indices->n_sections; ++i) { + if (s_indices->indices[i].oc == NULL) { + // free entry, skip + } else if (i == next_free_idx) { + ++next_free_idx; + } else { + s_indices->indices[next_free_idx] = s_indices->indices[i]; + ++next_free_idx; + } + } + + s_indices->n_sections = next_free_idx; + s_indices->unloaded = true; } -static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { +// Returns -1 if not found +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr) { + ASSERT(s_indices->sorted); + W_ w_addr = (W_)addr; - if (s_indices->n_sections <= 0) return NULL; - if (w_addr < s_indices->indices[0].start) return NULL; + if (s_indices->n_sections <= 0) { + return -1; + } + if (w_addr < s_indices->indices[0].start) { + return -1; + } int left = 0, right = s_indices->n_sections; while (left + 1 < right) { @@ -139,330 +340,125 @@ static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { } ASSERT(w_addr >= s_indices->indices[left].start); if (w_addr < s_indices->indices[left].end) { - return s_indices->indices[left].oc; + return left; } - return NULL; + return -1; } -static void checkAddress (HashTable *addrs, const void *addr, - OCSectionIndices *s_indices) -{ - ObjectCode *oc; - - if (!lookupHashTable(addrs, (W_)addr)) { - insertHashTable(addrs, (W_)addr, addr); +static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { + int oc_idx = findSectionIdx(s_indices, addr); - oc = findOC(s_indices, addr); - if (oc != NULL) { - oc->referenced = 1; - return; - } + if (oc_idx == -1) { + return NULL; } + + return s_indices->indices[oc_idx].oc; } -static void searchStackChunk (HashTable *addrs, StgPtr sp, StgPtr stack_end, - OCSectionIndices *s_indices) -{ - StgPtr p; - const StgRetInfoTable *info; +static bool markObjectLive(void *data STG_UNUSED, StgWord key, const void *value STG_UNUSED) { + ObjectCode *oc = (ObjectCode*)key; + if (oc->mark == object_code_mark_bit) { + return true; // for hash table iteration + } + + oc->mark = object_code_mark_bit; + // Remove from 'old_objects' list + if (oc->prev != NULL) { + // TODO(osa): Maybe 'prev' should be a pointer to the referencing + // *field* ? (instead of referencing *object*) + oc->prev->next = oc->next; + } else { + old_objects = oc->next; + } + if (oc->next != NULL) { + oc->next->prev = oc->prev; + } - p = sp; - while (p < stack_end) { - info = get_ret_itbl((StgClosure *)p); + // Add it to 'objects' list + oc->prev = NULL; + oc->next = objects; + if (objects != NULL) { + objects->prev = oc; + } + objects = oc; - switch (info->i.type) { - case RET_SMALL: - case RET_BIG: - checkAddress(addrs, (const void*)info, s_indices); - break; + // Mark its dependencies + iterHashTable(oc->dependencies, NULL, markObjectLive); - default: - break; - } + return true; // for hash table iteration +} + +void markObjectCode(const void *addr) +{ + if (global_s_indices == NULL) { + return; + } - p += stack_frame_sizeW((StgClosure*)p); + // This should be checked at the call site + ASSERT(!HEAP_ALLOCED(addr)); + + ObjectCode *oc = findOC(global_s_indices, addr); + if (oc != NULL) { + // Mark the object code and its dependencies + markObjectLive(NULL, (W_)oc, NULL); } } - -static void searchHeapBlocks (HashTable *addrs, bdescr *bd, - OCSectionIndices *s_indices) +// Returns whether or not the GC that follows needs to mark code for potential +// unloading. +bool prepareUnloadCheck() { - StgPtr p; - const StgInfoTable *info; - uint32_t size; - bool prim; + if (global_s_indices == NULL) { + return false; + } - for (; bd != NULL; bd = bd->link) { + removeRemovedOCSections(global_s_indices); + sortOCSectionIndices(global_s_indices); - if (bd->flags & BF_PINNED) { - // Assume that objects in PINNED blocks cannot refer to - continue; - } + ASSERT(old_objects == NULL); - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); - prim = false; - - switch (info->type) { - - case THUNK: - size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case FUN: - case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR: - case CONSTR_NOCAF: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case BLACKHOLE: - case BLOCKING_QUEUE: - prim = true; - size = sizeW_fromITBL(info); - break; - - case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. - prim = true; - size = BLACKHOLE_sizeW(); - break; - - case BCO: - prim = true; - size = bco_sizeW((StgBCO *)p); - break; - - case MVAR_CLEAN: - case MVAR_DIRTY: - case TVAR: - case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = true; - size = sizeW_fromITBL(info); - break; - - case AP: - prim = true; - size = ap_sizeW((StgAP *)p); - break; - - case PAP: - prim = true; - size = pap_sizeW((StgPAP *)p); - break; - - case AP_STACK: - { - StgAP_STACK *ap = (StgAP_STACK *)p; - prim = true; - size = ap_stack_sizeW(ap); - searchStackChunk(addrs, (StgPtr)ap->payload, - (StgPtr)ap->payload + ap->size, s_indices); - break; - } + object_code_mark_bit = ~object_code_mark_bit; + old_objects = objects; + objects = NULL; + return true; +} - case ARR_WORDS: - prim = true; - size = arr_words_sizeW((StgArrBytes*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN_CLEAN: - case MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = true; - size = sizeofW(StgTSO); - break; - - case STACK: { - StgStack *stack = (StgStack*)p; - prim = true; - searchStackChunk(addrs, stack->sp, - stack->stack + stack->stack_size, s_indices); - size = stack_sizeW(stack); - break; - } +void checkUnload() +{ + if (global_s_indices == NULL) { + return; + } - case TREC_CHUNK: - prim = true; - size = sizeofW(StgTRecChunk); - break; + // At this point we've marked all dynamically loaded static objects + // (including their dependencies) during GC, but not the root set of object + // code (loaded_objects). Mark the roots first, then unload any unmarked + // objects. - default: - barf("searchHeapBlocks, unknown object: %d", info->type); - } + OCSectionIndices *s_indices = global_s_indices; + ASSERT(s_indices->sorted); - if (!prim) { - checkAddress(addrs,info, s_indices); - } - - p += size; - } + // Mark roots + for (ObjectCode *oc = loaded_objects; oc != NULL; oc = oc->next_loaded_object) { + markObjectLive(NULL, (W_)oc, NULL); } -} -#if defined(PROFILING) -// -// Do not unload the object if the CCS tree refers to a CCS or CC which -// originates in the object. -// -static void searchCostCentres (HashTable *addrs, CostCentreStack *ccs, - OCSectionIndices* s_indices) -{ - IndexTable *i; + // Free unmarked objects + ObjectCode *next = NULL; + for (ObjectCode *oc = old_objects; oc != NULL; oc = next) { + next = oc->next; - checkAddress(addrs, ccs, s_indices); - checkAddress(addrs, ccs->cc, s_indices); - for (i = ccs->indexTable; i != NULL; i = i->next) { - if (!i->back_edge) { - searchCostCentres(addrs, i->ccs, s_indices); - } + removeOCSectionIndices(s_indices, oc); + + // Symbols should be removed by unloadObj_. + // NB (osa): If this assertion doesn't hold then freeObjectCode below + // will corrupt symhash as keys of that table live in ObjectCodes. If + // you see a segfault in a hash table operation in linker (in non-debug + // RTS) then it's probably becuse this assertion did not hold. + ASSERT(oc->symbols == NULL); + + freeObjectCode(oc); + n_unloaded_objects -= 1; } -} -#endif -// -// Check whether we can unload any object code. This is called at the -// appropriate point during a GC, where all the heap data is nice and -// packed together and we have a linked list of the static objects. -// -// The check involves a complete heap traversal, but you only pay for -// this (a) when you have called unloadObj(), and (b) at a major GC, -// which is much more expensive than the traversal we're doing here. -// -void checkUnload (StgClosure *static_objects) -{ - uint32_t g, n; - HashTable *addrs; - StgClosure* p; - const StgInfoTable *info; - ObjectCode *oc, *prev, *next; - gen_workspace *ws; - StgClosure* link; - - if (unloaded_objects == NULL) return; - - ACQUIRE_LOCK(&linker_unloaded_mutex); - - OCSectionIndices *s_indices = buildOCSectionIndices(unloaded_objects); - // Mark every unloadable object as unreferenced initially - for (oc = unloaded_objects; oc; oc = oc->next) { - IF_DEBUG(linker, debugBelch("Checking whether to unload %" PATH_FMT "\n", - oc->fileName)); - oc->referenced = false; - } - - addrs = allocHashTable(); - - for (p = static_objects; p != END_OF_STATIC_OBJECT_LIST; p = link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - info = get_itbl(p); - checkAddress(addrs, info, s_indices); - link = *STATIC_LINK(info, p); - } - - // CAFs on revertible_caf_list are not on static_objects - for (p = (StgClosure*)revertible_caf_list; - p != END_OF_CAF_LIST; - p = ((StgIndStatic *)p)->static_link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - } - - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - searchHeapBlocks (addrs, generations[g].blocks, s_indices); - searchHeapBlocks (addrs, generations[g].large_objects, s_indices); - - for (n = 0; n < n_capabilities; n++) { - ws = &gc_threads[n]->gens[g]; - searchHeapBlocks(addrs, ws->todo_bd, s_indices); - searchHeapBlocks(addrs, ws->part_list, s_indices); - searchHeapBlocks(addrs, ws->scavd_list, s_indices); - } - } - -#if defined(PROFILING) - /* Traverse the cost centre tree, calling checkAddress on each CCS/CC */ - searchCostCentres(addrs, CCS_MAIN, s_indices); - - /* Also check each cost centre in the CC_LIST */ - CostCentre *cc; - for (cc = CC_LIST; cc != NULL; cc = cc->link) { - checkAddress(addrs, cc, s_indices); - } -#endif /* PROFILING */ - - freeOCSectionIndices(s_indices); - // Look through the unloadable objects, and any object that is still - // marked as unreferenced can be physically unloaded, because we - // have no references to it. - prev = NULL; - for (oc = unloaded_objects; oc; oc = next) { - next = oc->next; - if (oc->referenced == 0) { - if (prev == NULL) { - unloaded_objects = oc->next; - } else { - prev->next = oc->next; - } - IF_DEBUG(linker, debugBelch("Unloading object file %" PATH_FMT "\n", - oc->fileName)); - freeObjectCode(oc); - } else { - IF_DEBUG(linker, debugBelch("Object file still in use: %" - PATH_FMT "\n", oc->fileName)); - prev = oc; - } - } - - freeHashTable(addrs, NULL); - - RELEASE_LOCK(&linker_unloaded_mutex); + old_objects = NULL; } ===================================== rts/CheckUnload.h ===================================== @@ -12,6 +12,34 @@ #include "BeginPrivate.h" -void checkUnload (StgClosure *static_objects); +#include "LinkerInternals.h" + +// Currently live objects +extern ObjectCode *objects; + +// Root set for object collection +extern ObjectCode *loaded_objects; + +// Mark bit for live objects +extern uint8_t object_code_mark_bit; + +// Number of object code currently marked for unloading. See the definition in +// CheckUnload.c for details. +extern int n_unloaded_objects; + +void initUnloadCheck(void); +void exitUnloadCheck(void); + +// Call before major GC to prepare section index table for marking +bool prepareUnloadCheck(void); + +// Mark object code of a static closure address as 'live' +void markObjectCode(const void *addr); + +// Call after major GC to unload unused and unmarked object code +void checkUnload(void); + +// Call on loaded object code +void insertOCSectionIndices(ObjectCode *oc); #include "EndPrivate.h" ===================================== rts/Hash.c ===================================== @@ -400,6 +400,27 @@ mapHashTable(HashTable *table, void *data, MapHashFn fn) } } +void +iterHashTable(HashTable *table, void *data, IterHashFn fn) +{ + /* The last bucket with something in it is table->max + table->split - 1 */ + long segment = (table->max + table->split - 1) / HSEGSIZE; + long index = (table->max + table->split - 1) % HSEGSIZE; + + while (segment >= 0) { + while (index >= 0) { + for (HashList *hl = table->dir[segment][index]; hl != NULL; hl = hl->next) { + if (!fn(data, hl->key, hl->data)) { + return; + } + } + index--; + } + segment--; + index = HSEGSIZE - 1; + } +} + /* ----------------------------------------------------------------------------- * When we initialize a hash table, we set up the first segment as well, * initializing all of the first segment's hash buckets to NULL. @@ -444,12 +465,6 @@ allocStrHashTable(void) return allocHashTable_(hashStr, compareStr); } -void -exitHashTable(void) -{ - /* nothing to do */ -} - int keyCountHashTable (HashTable *table) { return table->kcount; ===================================== rts/Hash.h ===================================== @@ -33,8 +33,11 @@ int keyCountHashTable (HashTable *table); int keysHashTable(HashTable *table, StgWord keys[], int szKeys); typedef void (*MapHashFn)(void *data, StgWord key, const void *value); +// Return true -> continue; false -> stop +typedef bool (*IterHashFn)(void *data, StgWord key, const void *value); void mapHashTable(HashTable *table, void *data, MapHashFn fn); +void iterHashTable(HashTable *table, void *data, IterHashFn); /* Hash table access where the keys are C strings (the strings are * assumed to be allocated by the caller, and mustn't be deallocated @@ -62,6 +65,32 @@ int hashStr(const HashTable *table, StgWord key); */ void freeHashTable ( HashTable *table, void (*freeDataFun)(void *) ); -void exitHashTable ( void ); +INLINE_HEADER void freeStrHashTable ( HashTable *table, void (*freeDataFun)(void *) ) +{ + freeHashTable((HashTable*)table, freeDataFun); +} + +/* + * Hash set API + * + * A hash set is bascially a hash table where values are NULL. + */ + +typedef struct hashtable HashSet; + +INLINE_HEADER HashSet *allocHashSet ( void ) +{ + return (HashSet*)allocHashTable(); +} + +INLINE_HEADER void freeHashSet ( HashSet *set ) +{ + freeHashTable((HashTable*)set, NULL); +} + +INLINE_HEADER void insertHashSet ( HashSet *set, StgWord key ) +{ + insertHashTable((HashTable*)set, key, NULL); +} #include "EndPrivate.h" ===================================== rts/Linker.c ===================================== @@ -32,6 +32,7 @@ #include "linker/CacheFlush.h" #include "linker/SymbolExtras.h" #include "PathUtils.h" +#include "CheckUnload.h" // createOCSectionIndices #if !defined(mingw32_HOST_OS) #include "posix/Signals.h" @@ -161,23 +162,9 @@ */ /*Str*/HashTable *symhash; -/* List of currently loaded objects */ -ObjectCode *objects = NULL; /* initially empty */ - -/* List of objects that have been unloaded via unloadObj(), but are waiting - to be actually freed via checkUnload() */ -ObjectCode *unloaded_objects = NULL; /* initially empty */ - #if defined(THREADED_RTS) -/* This protects all the Linker's global state except unloaded_objects */ +/* This protects all the Linker's global state */ Mutex linker_mutex; -/* - * This protects unloaded_objects. We have a separate mutex for this, because - * the GC needs to access unloaded_objects in checkUnload, while the linker only - * needs to access unloaded_objects in unloadObj(), so this allows most linker - * operations proceed concurrently with the GC. - */ -Mutex linker_unloaded_mutex; #endif /* Generic wrapper function to try and Resolve and RunInit oc files */ @@ -447,12 +434,10 @@ initLinker_ (int retain_cafs) linker_init_done = 1; } - objects = NULL; - unloaded_objects = NULL; + initUnloadCheck(); #if defined(THREADED_RTS) initMutex(&linker_mutex); - initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -538,6 +523,7 @@ exitLinker( void ) { #endif if (linker_init_done == 1) { freeHashTable(symhash, free); + exitUnloadCheck(); } #if defined(THREADED_RTS) closeMutex(&linker_mutex); @@ -864,18 +850,24 @@ HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data) } /* ----------------------------------------------------------------------------- - * lookup a symbol in the hash table + * Lookup a symbol in the hash table + * + * When 'dependent' is not NULL, adds it as a dependent to the owner of the + * symbol. */ #if defined(OBJFORMAT_PEi386) -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + (void)dependent; // TODO + ASSERT_LOCK_HELD(&linker_mutex); return lookupSymbol_PEi386(lbl); } #else -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + ASSERT_LOCK_HELD(&linker_mutex); IF_DEBUG(linker, debugBelch("lookupSymbol: looking up '%s'\n", lbl)); ASSERT(symhash != NULL); @@ -900,10 +892,18 @@ SymbolAddr* lookupSymbol_ (SymbolName* lbl) return internal_dlsym(lbl + 1); # else - ASSERT(2+2 == 5); + ASSERT(false); return NULL; # endif } else { + if (dependent) { + // Add dependent as symbol's owner's dependency + ObjectCode *owner = pinfo->owner; + if (owner) { + // TODO: what does it mean for a symbol to not have an owner? + insertHashSet(dependent->dependencies, (W_)owner); + } + } return loadSymbol(lbl, pinfo); } } @@ -1342,6 +1342,8 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->fileName); stgFree(oc->archiveMemberName); + freeHashSet(oc->dependencies); + stgFree(oc); } @@ -1403,6 +1405,10 @@ mkOc( pathchar *path, char *image, int imageSize, /* chain it onto the list of objects */ oc->next = NULL; + oc->prev = NULL; + oc->next_loaded_object = NULL; + oc->mark = object_code_mark_bit; + oc->dependencies = allocHashSet(); #if RTS_LINKER_USE_MMAP oc->rw_m32 = m32_allocator_new(false); @@ -1421,9 +1427,9 @@ mkOc( pathchar *path, char *image, int imageSize, HsInt isAlreadyLoaded( pathchar *path ) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path) + && o->status != OBJECT_UNLOADED) { return 1; /* already loaded */ } } @@ -1557,21 +1563,16 @@ preloadObjectFile (pathchar *path) */ static HsInt loadObj_ (pathchar *path) { - ObjectCode* oc; - IF_DEBUG(linker, debugBelch("loadObj: %" PATH_FMT "\n", path)); - - /* debugBelch("loadObj %s\n", path ); */ - - /* Check that we haven't already loaded this object. - Ignore requests to load multiple times */ + // Check that we haven't already loaded this object. + // Ignore requests to load multiple times if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); - return 1; /* success */ + return 1; // success } - oc = preloadObjectFile(path); + ObjectCode *oc = preloadObjectFile(path); if (oc == NULL) return 0; if (! loadOc(oc)) { @@ -1582,8 +1583,10 @@ static HsInt loadObj_ (pathchar *path) return 0; } - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); + + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; return 1; } @@ -1778,15 +1781,15 @@ int ocTryLoad (ObjectCode* oc) { */ static HsInt resolveObjs_ (void) { - ObjectCode *oc; - int r; - IF_DEBUG(linker, debugBelch("resolveObjs: start\n")); - for (oc = objects; oc; oc = oc->next) { - r = ocTryLoad(oc); + for (ObjectCode *oc = objects; oc; oc = oc->next) { + int r = ocTryLoad(oc); if (!r) { + errorBelch("Could not load Object Code %" PATH_FMT ".\n", OC_INFORMATIVE_FILENAME(oc)); + IF_DEBUG(linker, printLoadedObjects()); + fflush(stderr); return r; } } @@ -1813,45 +1816,35 @@ HsInt resolveObjs (void) */ static HsInt unloadObj_ (pathchar *path, bool just_purge) { - ObjectCode *oc, *prev, *next; - HsBool unloadedAnyObj = HS_BOOL_FALSE; - ASSERT(symhash != NULL); ASSERT(objects != NULL); IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); - prev = NULL; - for (oc = objects; oc; oc = next) { - next = oc->next; // oc might be freed - - if (!pathcmp(oc->fileName,path)) { + bool unloadedAnyObj = false; + ObjectCode *prev = NULL; + // NOTE (osa): There may be more than one object with the same file name + // (happens when loading archive files) so we don't stop after unloading one + for (ObjectCode *oc = loaded_objects; oc; oc = oc->next_loaded_object) { + if (pathcmp(oc->fileName,path) == 0) { + oc->status = OBJECT_UNLOADED; - // these are both idempotent, so in just_purge mode we can - // later call unloadObj() to really unload the object. + // These are both idempotent, so in just_purge mode we can later + // call unloadObj() to really unload the object. removeOcSymbols(oc); freeOcStablePtrs(oc); + unloadedAnyObj = true; + if (!just_purge) { + n_unloaded_objects += 1; + // Remove object code from root set if (prev == NULL) { - objects = oc->next; + loaded_objects = oc->next_loaded_object; } else { - prev->next = oc->next; + prev->next_loaded_object = oc->next_loaded_object; } - ACQUIRE_LOCK(&linker_unloaded_mutex); - oc->next = unloaded_objects; - unloaded_objects = oc; - oc->status = OBJECT_UNLOADED; - RELEASE_LOCK(&linker_unloaded_mutex); - // We do not own oc any more; it can be released at any time by - // the GC in checkUnload(). - } else { - prev = oc; } - - /* This could be a member of an archive so continue - * unloading other members. */ - unloadedAnyObj = HS_BOOL_TRUE; } else { prev = oc; } @@ -1859,8 +1852,7 @@ static HsInt unloadObj_ (pathchar *path, bool just_purge) if (unloadedAnyObj) { return 1; - } - else { + } else { errorBelch("unloadObj: can't find `%" PATH_FMT "' to unload", path); return 0; } @@ -1884,13 +1876,7 @@ HsInt purgeObj (pathchar *path) static OStatus getObjectLoadStatus_ (pathchar *path) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } - } - for (o = unloaded_objects; o; o = o->next) { + for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { return o->status; } ===================================== rts/LinkerInternals.h ===================================== @@ -191,9 +191,6 @@ typedef struct _ObjectCode { /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; - /* flag used when deciding whether to unload an object file */ - int referenced; - /* record by how much image has been deliberately misaligned after allocation, so that we can use realloc */ int misalignment; @@ -205,8 +202,37 @@ typedef struct _ObjectCode { int n_segments; Segment *segments; - /* Allow a chain of these things */ - struct _ObjectCode * next; + // + // Garbage collection fields + // + + // Next object in `objects` list + struct _ObjectCode *next; + + // Previous object in `objects` list + struct _ObjectCode *prev; + + // Next object in `loaded_objects` list + struct _ObjectCode *next_loaded_object; + + // Mark bit + uint8_t mark; + + // Set of dependencies (ObjectCode*) of the object file. Traverse + // dependencies using `iterHashTable`. + // + // New entries are added as we resolve symbols in an object file, in + // `lookupDependentSymbol`. When an object file uses multiple symbols from + // another object file we add the dependent multiple times, so we use a + // `HashTable` here rather than a list/array to avoid copies. + // + // Used when unloading object files. See Note [Object unloading] in + // CheckUnload.c. + HashSet *dependencies; + + // + // End of garbage collection fields + // /* SANITY CHECK ONLY: a list of the only memory regions which may safely be prodded during relocation. Any attempt to prod @@ -250,12 +276,8 @@ typedef struct _ObjectCode { (OC)->fileName \ ) -extern ObjectCode *objects; -extern ObjectCode *unloaded_objects; - #if defined(THREADED_RTS) extern Mutex linker_mutex; -extern Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -306,8 +328,9 @@ int ghciInsertSymbolTable( HsBool weak, ObjectCode *owner); -/* lock-free version of lookupSymbol */ -SymbolAddr* lookupSymbol_ (SymbolName* lbl); +/* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a + * dependent to the owner of the symbol. */ +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent); extern /*Str*/HashTable *symhash; ===================================== rts/PrimOps.cmm ===================================== @@ -1816,9 +1816,16 @@ loop: // There are readMVar/takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1843,10 +1850,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); @@ -1901,9 +1906,16 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1928,10 +1940,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/RtsStartup.c ===================================== @@ -512,9 +512,6 @@ hs_exit_(bool wait_foreign) shutdownAsyncIO(wait_foreign); #endif - /* free hash table storage */ - exitHashTable(); - // Finally, free all our storage. However, we only free the heap // memory if we have waited for foreign calls to complete; // otherwise a foreign call in progress may still be referencing ===================================== rts/Threads.c ===================================== @@ -790,9 +790,14 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = q->tso; - mvar->head = q->link; - if (mvar->head == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { + mvar->head = q = q->link; + if (q == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { mvar->tail = (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure; + } else { + if (info == &stg_MVAR_CLEAN_info) { + // Resolve #18919. + dirty_MVAR(&cap->r, (StgClosure*)mvar, mvar->value); + } } ASSERT(tso->block_info.closure == (StgClosure*)mvar); @@ -816,10 +821,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = ((StgMVarTSOQueue*)q)->link; + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/linker/Elf.c ===================================== @@ -1099,7 +1099,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) { S = (Elf_Addr)symbol->addr; } else { - S_tmp = lookupSymbol_( symbol->name ); + S_tmp = lookupDependentSymbol( symbol->name, oc ); S = (Elf_Addr)S_tmp; } if (!S) { @@ -1519,7 +1519,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } else { /* No, so look up the name in our global table. */ symbol = strtab + sym.st_name; - S_tmp = lookupSymbol_( symbol ); + S_tmp = lookupDependentSymbol( symbol, oc ); S = (Elf_Addr)S_tmp; } if (!S) { ===================================== rts/linker/LoadArchive.c ===================================== @@ -5,6 +5,7 @@ #include "sm/OSMem.h" #include "RtsUtils.h" #include "LinkerInternals.h" +#include "CheckUnload.h" // loaded_objects, insertOCSectionIndices #include "linker/M32Alloc.h" /* Platform specific headers */ @@ -241,7 +242,6 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, static HsInt loadArchive_ (pathchar *path) { - ObjectCode* oc = NULL; char *image = NULL; HsInt retcode = 0; int memberSize; @@ -520,8 +520,8 @@ static HsInt loadArchive_ (pathchar *path) sprintf(archiveMemberName, "%" PATH_FMT "(%.*s)", path, (int)thisFileNameSize, fileName); - oc = mkOc(path, image, memberSize, false, archiveMemberName - , misalignment); + ObjectCode *oc = mkOc(path, image, memberSize, false, archiveMemberName, + misalignment); #if defined(OBJFORMAT_MACHO) ocInit_MachO( oc ); #endif @@ -536,8 +536,9 @@ static HsInt loadArchive_ (pathchar *path) fclose(f); return 0; } else { - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); // also adds the object to `objects` list + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; } } else if (isGnuIndex) { ===================================== rts/linker/MachO.c ===================================== @@ -242,7 +242,7 @@ resolveImports( addr = (SymbolAddr*) (symbol->nlist->n_value); IF_DEBUG(linker, debugBelch("resolveImports: undefined external %s has value %p\n", symbol->name, addr)); } else { - addr = lookupSymbol_(symbol->name); + addr = lookupDependentSymbol(symbol->name, oc); IF_DEBUG(linker, debugBelch("resolveImports: looking up %s, %p\n", symbol->name, addr)); } @@ -564,12 +564,12 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { /* external symbols should be able to be - * looked up via the lookupSymbol_ function. + * looked up via the lookupDependentSymbol function. * Either through the global symbol hashmap * or asking the system, if not found * in the symbol hashmap */ - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -609,7 +609,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -784,7 +784,7 @@ relocateSection(ObjectCode* oc, int curSection) // symtab, or it is undefined, meaning dlsym must be used // to resolve it. - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); IF_DEBUG(linker, debugBelch("relocateSection: looked up %s, " "external X86_64_RELOC_GOT or X86_64_RELOC_GOT_LOAD\n" " : addr = %p\n", nm, addr)); @@ -845,7 +845,7 @@ relocateSection(ObjectCode* oc, int curSection) nm, (void *)value)); } else { - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); if (addr == NULL) { errorBelch("\nlookupSymbol failed in relocateSection (relocate external)\n" @@ -1345,7 +1345,7 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->nlist[i].n_type & N_EXT) { if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) - && lookupSymbol_(nm)) { + && lookupDependentSymbol(nm, oc)) { // weak definition, and we already have a definition IF_DEBUG(linker, debugBelch(" weak: %s\n", nm)); } @@ -1497,7 +1497,7 @@ ocResolve_MachO(ObjectCode* oc) * have the address. */ if(NULL == symbol->addr) { - symbol->addr = lookupSymbol_((char*)symbol->name); + symbol->addr = lookupDependentSymbol((char*)symbol->name, oc); if(NULL == symbol->addr) barf("Failed to lookup symbol: %s", symbol->name); } else { ===================================== rts/linker/PEi386.c ===================================== @@ -185,6 +185,7 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" #include "GetEnv.h" +#include "CheckUnload.h" #include "linker/PEi386.h" #include "linker/PEi386Types.h" #include "linker/SymbolExtras.h" @@ -1894,7 +1895,7 @@ ocResolve_PEi386 ( ObjectCode* oc ) } else { copyName ( getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1 ); - S = (size_t) lookupSymbol_( (char*)symbol ); + S = (size_t) lookupDependentSymbol( (char*)symbol, oc ); if ((void*)S == NULL) { errorBelch(" | %" PATH_FMT ": unknown symbol `%s'", oc->fileName, symbol); releaseOcInfo (oc); ===================================== rts/linker/elf_got.c ===================================== @@ -88,7 +88,7 @@ fillGot(ObjectCode * oc) { if( STT_NOTYPE == ELF_ST_TYPE(symbol->elf_sym->st_info) || STB_WEAK == ELF_ST_BIND(symbol->elf_sym->st_info)) { if(0x0 == symbol->addr) { - symbol->addr = lookupSymbol_(symbol->name); + symbol->addr = lookupDependentSymbol(symbol->name, oc); if(0x0 == symbol->addr) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; ===================================== rts/sm/Evac.c ===================================== @@ -28,6 +28,7 @@ #include "CNF.h" #include "Scav.h" #include "NonMoving.h" +#include "CheckUnload.h" // n_unloaded_objects and markObjectCode #if defined(THREADED_RTS) && !defined(PARALLEL_GC) #define evacuate(p) evacuate1(p) @@ -593,6 +594,11 @@ loop: if (!HEAP_ALLOCED_GC(q)) { if (!major_gc) return; + // Note [Object unloading] in CheckUnload.c + if (RTS_UNLIKELY(unload_mark_needed)) { + markObjectCode(q); + } + info = get_itbl(q); switch (info->type) { ===================================== rts/sm/GC.c ===================================== @@ -97,6 +97,13 @@ * See also: Note [STATIC_LINK fields] in Storage.h. */ +/* Hot GC globals + * ~~~~~~~~~~~~~~ + * The globals below are quite hot during GC but read-only, initialized during + * the beginning of collection. It is important that they reside in the same + * cache-line to minimize unnecessary cache misses. + */ + /* N is the oldest generation being collected, where the generations * are numbered starting at 0. A major GC (indicated by the major_gc * flag) is when we're collecting all generations. We only attempt to @@ -105,6 +112,7 @@ uint32_t N; bool major_gc; bool deadlock_detect_gc; +bool unload_mark_needed; /* Data used for allocation area sizing. */ @@ -297,6 +305,12 @@ GarbageCollect (uint32_t collect_gen, static_flag == STATIC_FLAG_A ? STATIC_FLAG_B : STATIC_FLAG_A; } + if (major_gc) { + unload_mark_needed = prepareUnloadCheck(); + } else { + unload_mark_needed = false; + } + #if defined(THREADED_RTS) work_stealing = RtsFlags.ParFlags.parGcLoadBalancingEnabled && N >= RtsFlags.ParFlags.parGcLoadBalancingGen; @@ -810,9 +824,12 @@ GarbageCollect (uint32_t collect_gen, resetNurseries(); - // mark the garbage collected CAFs as dead #if defined(DEBUG) - if (major_gc && !RtsFlags.GcFlags.useNonmoving) { gcCAFs(); } + // Mark the garbage collected CAFs as dead. Done in `nonmovingGcCafs()` when + // non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + gcCAFs(); + } #endif // Update the stable name hash table @@ -823,9 +840,14 @@ GarbageCollect (uint32_t collect_gen, // hs_free_stable_ptr(), both of which access the StablePtr table. stablePtrUnlock(); - // Must be after stablePtrUnlock(), because it might free stable ptrs. - if (major_gc) { - checkUnload (gct->scavenged_static_objects); + // Unload dynamically-loaded object code after a major GC. + // See Note [Object unloading] in CheckUnload.c for details. + // + // TODO: Similar to `nonmovingGcCafs` non-moving GC should have its own + // collector for these objects, but that's currently not implemented, so we + // simply don't unload object code when non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + checkUnload(); } #if defined(PROFILING) ===================================== rts/sm/GC.h ===================================== @@ -35,6 +35,7 @@ extern uint32_t N; extern bool major_gc; /* See Note [Deadlock detection under nonmoving collector]. */ extern bool deadlock_detect_gc; +extern bool unload_mark_needed; extern bdescr *mark_stack_bd; extern bdescr *mark_stack_top_bd; ===================================== testsuite/tests/ghci/T16525a/T16525a.script ===================================== @@ -1,6 +1,10 @@ :set -fobject-code :load A import Control.Concurrent -_ <- forkIO $ threadDelay 1000000 >> (print (map v1 value)) +_ <- forkIO $ threadDelay 500000 >> print (map v1 value) :l [] System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC ===================================== testsuite/tests/ghci/T16525a/T16525a.stdout ===================================== @@ -0,0 +1 @@ +["a;lskdfa;lszkfsd;alkfjas"] ===================================== testsuite/tests/ghci/T16525a/all.T ===================================== @@ -1,6 +1,3 @@ test('T16525a', - [extra_files(['A.hs', 'B.hs', ]), - when(compiler_debugged(), extra_run_opts('+RTS -DS -RTS')), - # We don't support unloading with the dynamic linker - when(ghc_dynamic(), skip), ], + [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525a.script']) ===================================== testsuite/tests/ghci/T16525b/A.hs ===================================== @@ -0,0 +1,6 @@ +module A (a) where + +import B + +a :: () -> IO Int +a x = b x ===================================== testsuite/tests/ghci/T16525b/B.hs ===================================== @@ -0,0 +1,5 @@ +module B (b) where + +{-# NOINLINE b #-} +b :: () -> IO Int +b () = return 999999999 ===================================== testsuite/tests/ghci/T16525b/T16525b.script ===================================== @@ -0,0 +1,22 @@ +:set -fobject-code +:load A +import Control.Concurrent +import Control.Monad +:{ +_ <- forkIO $ do + replicateM_ 3 (a () >>= print >> threadDelay 500000) + putStrLn "===== THREAD DONE =====" +:} +:l [] +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 ===================================== testsuite/tests/ghci/T16525b/T16525b.stdout ===================================== @@ -0,0 +1,4 @@ +999999999 +999999999 +999999999 +===== THREAD DONE ===== ===================================== testsuite/tests/ghci/T16525b/all.T ===================================== @@ -0,0 +1,2 @@ +# Tests unloading an object file which is in use in a thread +test('T16525b', [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525b.script']) ===================================== testsuite/tests/rts/linker/linker_error.c ===================================== @@ -57,7 +57,10 @@ int main (int argc, char *argv[]) r = resolveObjs(); if (!r) { debugBelch("resolveObjs failed\n"); + // Mark the object as unloadable: unloadObj(obj); + // Actually unload it: + performMajorGC(); continue; } errorBelch("loading succeeded"); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/180f58cf281e00bf5c9b7a514a799706535dc5b9...3bcb55221883ea41acf1286b580c782e9aac68d2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/180f58cf281e00bf5c9b7a514a799706535dc5b9...3bcb55221883ea41acf1286b580c782e9aac68d2 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 Tue Nov 24 02:41:58 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 23 Nov 2020 21:41:58 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] rts/linker: Move shared library loading logic into Elf.c Message-ID: <5fbc72f698783_36a73fd2f1fdd7f88285b@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: c463ca00 by Ben Gamari at 2020-11-23T21:41:51-05:00 rts/linker: Move shared library loading logic into Elf.c - - - - - 3 changed files: - rts/Linker.c - rts/linker/Elf.c - rts/linker/Elf.h Changes: ===================================== rts/Linker.c ===================================== @@ -64,7 +64,6 @@ # include "linker/Elf.h" # include // regex is already used by dlopen() so this is OK // to use here without requiring an additional lib -# include #elif defined(OBJFORMAT_PEi386) # include "linker/PEi386.h" # include @@ -171,8 +170,6 @@ Mutex linker_mutex; /* Generic wrapper function to try and Resolve and RunInit oc files */ int ocTryLoad( ObjectCode* oc ); -static void freeNativeCode_ELF (ObjectCode *nc); - /* Link objects into the lower 2Gb on x86_64 and AArch64. GHC assumes the * small memory model on this architecture (see gcc docs, * -mcmodel=small). @@ -1961,141 +1958,6 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc, size, kind )); } - -# if defined(OBJFORMAT_ELF) -static int loadNativeObjCb_(struct dl_phdr_info *info, - size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { - ObjectCode* nc = (ObjectCode*) data; - - // This logic mimicks _dl_addr_inside_object from glibc - // For reference: - // int - // internal_function - // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) - // { - // int n = l->l_phnum; - // const ElfW(Addr) reladdr = addr - l->l_addr; - // - // while (--n >= 0) - // if (l->l_phdr[n].p_type == PT_LOAD - // && reladdr - l->l_phdr[n].p_vaddr >= 0 - // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) - // return 1; - // return 0; - // } - - if ((void*) info->dlpi_addr == nc->l_addr) { - int n = info->dlpi_phnum; - while (--n >= 0) { - if (info->dlpi_phdr[n].p_type == PT_LOAD) { - NativeCodeRange* ncr = - stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); - ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); - ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); - - ncr->next = nc->nc_ranges; - nc->nc_ranges = ncr; - } - } - } - return 0; -} - -static void copyErrmsg(char** errmsg_dest, char* errmsg) { - if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; - *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); - strcpy(*errmsg_dest, errmsg); -} - -// need dl_mutex -static void freeNativeCode_ELF (ObjectCode *nc) { - dlclose(nc->dlopen_handle); - - NativeCodeRange *ncr = nc->nc_ranges; - while (ncr) { - NativeCodeRange* last_ncr = ncr; - ncr = ncr->next; - stgFree(last_ncr); - } -} - -static void * loadNativeObj_ELF (pathchar *path, char **errmsg) -{ - ObjectCode* nc; - void *hdl, *retval; - - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); - - retval = NULL; - ACQUIRE_LOCK(&dl_mutex); - - /* Loading the same object multiple times will lead to chaos - * as we will have two ObjectCodes but one underlying dlopen - * handle. Fail if this happens. - */ - if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { - copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); - goto dlopen_fail; - } - - nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, true, NULL, 0); - - foreignExportsLoadingObject(nc); - hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); - foreignExportsFinishedLoadingObject(); - if (hdl == NULL) { - /* dlopen failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlopen_fail; - } - - struct link_map *map; - if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { - /* dlinfo failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlinfo_fail; - } - - nc->l_addr = (void*) map->l_addr; - nc->dlopen_handle = hdl; - hdl = NULL; // pass handle ownership to nc - - dl_iterate_phdr(loadNativeObjCb_, nc); - if (!nc->nc_ranges) { - copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); - goto dl_iterate_phdr_fail; - } - - insertOCSectionIndices(nc); - - nc->next_loaded_object = loaded_objects; - loaded_objects = nc; - - retval = nc->dlopen_handle; - -#if defined(PROFILING) - // collect any new cost centres that were defined in the loaded object. - refreshProfilingCCSs(); -#endif - - goto success; - -dl_iterate_phdr_fail: - // already have dl_mutex - freeNativeCode_ELF(nc); -dlinfo_fail: - if (hdl) dlclose(hdl); -dlopen_fail: -success: - - RELEASE_LOCK(&dl_mutex); - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); - - return retval; -} - -# endif - #define UNUSED(x) (void)(x) void * loadNativeObj (pathchar *path, char **errmsg) ===================================== rts/linker/Elf.c ===================================== @@ -15,15 +15,18 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" +#include "CheckUnload.h" #include "linker/Elf.h" #include "linker/CacheFlush.h" #include "linker/M32Alloc.h" #include "linker/SymbolExtras.h" +#include "ForeignExports.h" #include "sm/OSMem.h" #include "GetEnv.h" #include "linker/util.h" #include "linker/elf_util.h" +#include #include #include #if defined(HAVE_SYS_STAT_H) @@ -1962,6 +1965,143 @@ int ocRunInit_ELF( ObjectCode *oc ) return 1; } +/* + * Shared object loading + */ + +static int loadNativeObjCb_(struct dl_phdr_info *info, + size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { + ObjectCode* nc = (ObjectCode*) data; + + // This logic mimicks _dl_addr_inside_object from glibc + // For reference: + // int + // internal_function + // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) + // { + // int n = l->l_phnum; + // const ElfW(Addr) reladdr = addr - l->l_addr; + // + // while (--n >= 0) + // if (l->l_phdr[n].p_type == PT_LOAD + // && reladdr - l->l_phdr[n].p_vaddr >= 0 + // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) + // return 1; + // return 0; + // } + + if ((void*) info->dlpi_addr == nc->l_addr) { + int n = info->dlpi_phnum; + while (--n >= 0) { + if (info->dlpi_phdr[n].p_type == PT_LOAD) { + NativeCodeRange* ncr = + stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); + ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); + ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); + + ncr->next = nc->nc_ranges; + nc->nc_ranges = ncr; + } + } + } + return 0; +} + +static void copyErrmsg(char** errmsg_dest, char* errmsg) { + if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; + *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); + strcpy(*errmsg_dest, errmsg); +} + +// need dl_mutex +void freeNativeCode_ELF (ObjectCode *nc) { + dlclose(nc->dlopen_handle); + + NativeCodeRange *ncr = nc->nc_ranges; + while (ncr) { + NativeCodeRange* last_ncr = ncr; + ncr = ncr->next; + stgFree(last_ncr); + } +} + +void * loadNativeObj_ELF (pathchar *path, char **errmsg) +{ + ObjectCode* nc; + void *hdl, *retval; + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); + + retval = NULL; + ACQUIRE_LOCK(&dl_mutex); + + /* Loading the same object multiple times will lead to chaos + * as we will have two ObjectCodes but one underlying dlopen + * handle. Fail if this happens. + */ + if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { + copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); + goto dlopen_fail; + } + + nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, true, NULL, 0); + + foreignExportsLoadingObject(nc); + hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); + foreignExportsFinishedLoadingObject(); + if (hdl == NULL) { + /* dlopen failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlopen_fail; + } + + struct link_map *map; + if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { + /* dlinfo failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlinfo_fail; + } + + nc->l_addr = (void*) map->l_addr; + nc->dlopen_handle = hdl; + hdl = NULL; // pass handle ownership to nc + + dl_iterate_phdr(loadNativeObjCb_, nc); + if (!nc->nc_ranges) { + copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); + goto dl_iterate_phdr_fail; + } + + insertOCSectionIndices(nc); + + nc->next_loaded_object = loaded_objects; + loaded_objects = nc; + + retval = nc->dlopen_handle; + +#if defined(PROFILING) + // collect any new cost centres that were defined in the loaded object. + refreshProfilingCCSs(); +#endif + + goto success; + +dl_iterate_phdr_fail: + // already have dl_mutex + freeNativeCode_ELF(nc); +dlinfo_fail: + if (hdl) dlclose(hdl); +dlopen_fail: +success: + + RELEASE_LOCK(&dl_mutex); + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); + + return retval; +} + + /* * PowerPC & X86_64 ELF specifics */ ===================================== rts/linker/Elf.h ===================================== @@ -14,5 +14,7 @@ int ocGetNames_ELF ( ObjectCode* oc ); int ocResolve_ELF ( ObjectCode* oc ); int ocRunInit_ELF ( ObjectCode* oc ); int ocAllocateExtras_ELF ( ObjectCode *oc ); +void freeNativeCode_ELF ( ObjectCode *nc ); +void *loadNativeObj_ELF ( pathchar *path, char **errmsg ); #include "EndPrivate.h" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c463ca00e278f0db179f60e75bebc5729ed80263 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c463ca00e278f0db179f60e75bebc5729ed80263 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 Tue Nov 24 03:50:05 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Mon, 23 Nov 2020 22:50:05 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 3 commits: Make the fast path work without roles Message-ID: <5fbc82edb9aee_36a73fd2f90f5f308295e9@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: f8237cf7 by Richard Eisenberg at 2020-11-23T22:08:58+00:00 Make the fast path work without roles - - - - - e5353131 by Richard Eisenberg at 2020-11-24T01:31:09+00:00 Use MCo - - - - - 62d06215 by Richard Eisenberg at 2020-11-24T01:37:58+00:00 Remove unused parameter - - - - - 4 changed files: - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Flatten.hs Changes: ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -70,8 +70,9 @@ module GHC.Core.Coercion ( isGReflCo, isReflCo, isReflCo_maybe, isGReflCo_maybe, isReflexiveCo, isReflexiveCo_maybe, isReflCoVar_maybe, isGReflMCo, mkGReflLeftMCo, mkGReflRightMCo, + mkCoherenceRightMCo, - coToMCo, mkTransMCo, mkTransMCoL, mkCastTyMCo, mkSymMCo, + coToMCo, mkTransMCo, mkTransMCoL, mkCastTyMCo, mkSymMCo, isReflMCo, -- ** Coercion variables mkCoVar, isCoVar, coVarName, setCoVarName, setCoVarUnique, @@ -352,6 +353,15 @@ mkGReflRightMCo :: Role -> Type -> MCoercionN -> Coercion mkGReflRightMCo r ty MRefl = mkReflCo r ty mkGReflRightMCo r ty (MCo co) = mkGReflRightCo r ty co +-- | Like 'mkCoherenceRightCo', but with an 'MCoercion' +mkCoherenceRightMCo :: Role -> Type -> MCoercionN -> Coercion -> Coercion +mkCoherenceRightMCo _ _ MRefl co2 = co2 +mkCoherenceRightMCo r ty (MCo co) co2 = mkCoherenceRightCo r ty co co2 + +isReflMCo :: MCoercion -> Bool +isReflMCo MRefl = True +isReflMCo _ = False + {- %************************************************************************ %* * @@ -2939,7 +2949,7 @@ simplifyArgsWorker :: [TyCoBinder] -> Kind -> [(Type, Coercion)] -- flattened type arguments, arg -- each comes with the coercion used to flatten it, -- with co :: flattened_type ~ original_type - -> ([Type], [Coercion], CoercionN) + -> ([Type], [Coercion], MCoercionN) -- Returns (xis, cos, res_co), where each co :: xi ~ arg, -- and res_co :: kind (f xis) ~ kind (f tys), where f is the function applied to the args -- Precondition: if f :: forall bndrs. inner_ki (where bndrs and inner_ki are passed in), @@ -2961,14 +2971,15 @@ simplifyArgsWorker orig_ki_binders orig_inner_ki orig_fvs -> Kind -- Unsubsted result kind of function (not a Pi-type) -> [Role] -- Roles at which to flatten these ... -> [(Type, Coercion)] -- flattened arguments, with their flattening coercions - -> ([Type], [Coercion], CoercionN) + -> ([Type], [Coercion], MCoercionN) go acc_xis acc_cos !lc binders inner_ki _ [] -- The !lc makes the function strict in the lifting context -- which means GHC can unbox that pair. A modest win. = (reverse acc_xis, reverse acc_cos, kind_co) where final_kind = mkPiTys binders inner_ki - kind_co = liftCoSubst Nominal lc final_kind + kind_co | noFreeVarsOfType final_kind = MRefl + | otherwise = MCo $ liftCoSubst Nominal lc final_kind go acc_xis acc_cos lc (binder:binders) inner_ki (role:roles) ((xi,co):args) = -- By Note [Flattening] in GHC.Tc.Solver.Flatten invariant (F2), @@ -3024,7 +3035,7 @@ simplifyArgsWorker orig_ki_binders orig_inner_ki orig_fvs (xis_out, cos_out, res_co_out) = go acc_xis acc_cos zapped_lc bndrs new_inner roles casted_args in - (xis_out, cos_out, res_co_out `mkTransCo` res_co) + (xis_out, cos_out, res_co_out `mkTransMCoL` res_co) go _ _ _ _ _ _ _ = panic "simplifyArgsWorker wandered into deeper water than usual" ===================================== compiler/GHC/Core/FamInstEnv.hs ===================================== @@ -1319,7 +1319,7 @@ topNormaliseType_maybe env ty tyFamStepper :: NormaliseStepper (Coercion, MCoercionN) tyFamStepper rec_nts tc tys -- Try to step a type/data family = case topReduceTyFamApp_maybe env tc tys of - Just (co, rhs, res_co) -> NS_Step rec_nts rhs (co, MCo res_co) + Just (co, rhs, res_co) -> NS_Step rec_nts rhs (co, res_co) _ -> NS_Done --------------- @@ -1365,14 +1365,14 @@ normalise_tc_app tc tys assemble_result :: Role -- r, ambient role in NormM monad -> Type -- nty, result type, possibly of changed kind -> Coercion -- orig_ty ~r nty, possibly heterogeneous - -> CoercionN -- typeKind(orig_ty) ~N typeKind(nty) + -> MCoercionN -- typeKind(orig_ty) ~N typeKind(nty) -> (Coercion, Type) -- (co :: orig_ty ~r nty_casted, nty_casted) -- where nty_casted has same kind as orig_ty assemble_result r nty orig_to_nty kind_co = ( final_co, nty_old_kind ) where - nty_old_kind = nty `mkCastTy` mkSymCo kind_co - final_co = mkCoherenceRightCo r nty (mkSymCo kind_co) orig_to_nty + nty_old_kind = nty `mkCastTyMCo` mkSymMCo kind_co + final_co = mkCoherenceRightMCo r nty (mkSymMCo kind_co) orig_to_nty --------------- -- | Try to simplify a type-family application, by *one* step @@ -1381,7 +1381,7 @@ normalise_tc_app tc tys -- res_co :: typeKind(F tys) ~ typeKind(rhs) -- Type families and data families; always Representational role topReduceTyFamApp_maybe :: FamInstEnvs -> TyCon -> [Type] - -> Maybe (Coercion, Type, Coercion) + -> Maybe (Coercion, Type, MCoercion) topReduceTyFamApp_maybe envs fam_tc arg_tys | isFamilyTyCon fam_tc -- type families and data families , Just (co, rhs) <- reduceTyFamApp_maybe envs role fam_tc ntys @@ -1394,7 +1394,7 @@ topReduceTyFamApp_maybe envs fam_tc arg_tys normalise_tc_args fam_tc arg_tys normalise_tc_args :: TyCon -> [Type] -- tc tys - -> NormM (Coercion, [Type], CoercionN) + -> NormM (Coercion, [Type], MCoercionN) -- (co, new_tys), where -- co :: tc tys ~ tc new_tys; might not be homogeneous -- res_co :: typeKind(tc tys) ~N typeKind(tc new_tys) @@ -1477,14 +1477,14 @@ normalise_type ty ; role <- getRole ; let nty = mkAppTys nfun nargs nco = mkAppCos fun_co args_cos - nty_casted = nty `mkCastTy` mkSymCo res_co - final_co = mkCoherenceRightCo role nty (mkSymCo res_co) nco + nty_casted = nty `mkCastTyMCo` mkSymMCo res_co + final_co = mkCoherenceRightMCo role nty (mkSymMCo res_co) nco ; return (final_co, nty_casted) } } normalise_args :: Kind -- of the function -> [Role] -- roles at which to normalise args -> [Type] -- args - -> NormM ([Coercion], [Type], Coercion) + -> NormM ([Coercion], [Type], MCoercion) -- returns (cos, xis, res_co), where each xi is the normalised -- version of the corresponding type, each co is orig_arg ~ xi, -- and the res_co :: kind(f orig_args) ~ kind(f xis) @@ -1494,7 +1494,7 @@ normalise_args :: Kind -- of the function normalise_args fun_ki roles args = do { normed_args <- zipWithM normalise1 roles args ; let (xis, cos, res_co) = simplifyArgsWorker ki_binders inner_ki fvs roles normed_args - ; return (map mkSymCo cos, xis, mkSymCo res_co) } + ; return (map mkSymCo cos, xis, mkSymMCo res_co) } where (ki_binders, inner_ki) = splitPiTys fun_ki fvs = tyCoVarsOfTypes args ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -200,8 +200,7 @@ canClass :: CtEvidence canClass ev cls tys pend_sc = -- all classes do *nominal* matching ASSERT2( ctEvRole ev == Nominal, ppr ev $$ ppr cls $$ ppr tys ) - do { (xis, cos, _kind_co) <- flattenArgsNom ev cls_tc tys - ; MASSERT( isTcReflCo _kind_co ) + do { (xis, cos) <- flattenArgsNom ev cls_tc tys ; let co = mkTcTyConAppCo Nominal cls_tc cos xi = mkClassPred cls xis mk_ct new_ev = CDictCan { cc_ev = new_ev ===================================== compiler/GHC/Tc/Solver/Flatten.hs ===================================== @@ -127,6 +127,7 @@ setEqRel new_eq_rel thing_inside if new_eq_rel == fe_eq_rel env then runFlatM thing_inside env else runFlatM thing_inside (env { fe_eq_rel = new_eq_rel }) +{-# INLINE setEqRel #-} -- | Make sure that flattening actually produces a coercion (in other -- words, make sure our flavour is not Derived) @@ -237,23 +238,24 @@ flattenKind loc flav ty ; return (ty', co) } -- See Note [Flattening] -flattenArgsNom :: CtEvidence -> TyCon -> [TcType] -> TcS ([Xi], [TcCoercion], TcCoercionN) +flattenArgsNom :: CtEvidence -> TyCon -> [TcType] -> TcS ([Xi], [TcCoercion]) -- Externally-callable, hence runFlatten -- Flatten a vector of types all at once; in fact they are -- always the arguments of type family or class, so -- ctEvFlavour ev = Nominal -- and we want to flatten all at nominal role -- The kind passed in is the kind of the type family or class, call it T --- The last coercion returned has type (tcTypeKind(T xis) ~N tcTypeKind(T tys)) +-- The kind of T args must be constant (i.e. not depend on the args) -- -- For Derived constraints the returned coercion may be undefined -- because flattening may use a Derived equality ([D] a ~ ty) flattenArgsNom ev tc tys = do { traceTcS "flatten_args {" (vcat (map ppr tys)) ; (tys', cos, kind_co) - <- runFlattenCtEv ev (flatten_args_tc tc (repeat Nominal) tys) + <- runFlattenCtEv ev (flatten_args_tc tc Nothing tys) + ; MASSERT( isReflMCo kind_co ) ; traceTcS "flatten }" (vcat (map ppr tys')) - ; return (tys', cos, kind_co) } + ; return (tys', cos) } -- | Flatten a type w.r.t. nominal equality. This is useful to rewrite -- a type w.r.t. any givens. It does not do type-family reduction. This @@ -381,14 +383,15 @@ we skip adding to the cache here. {-# INLINE flatten_args_tc #-} flatten_args_tc :: TyCon -- T - -> [Role] -- Role r + -> Maybe [Role] -- Nothing: ambient role is Nominal; all args are Nominal + -- Otherwise: no assumptions; use roles provided -> [Type] -- Arg types [t1,..,tn] -> FlatM ( [Xi] -- List of flattened args [x1,..,xn] -- 1-1 corresp with [t1,..,tn] , [Coercion] -- List of arg coercions [co1,..,con] -- 1-1 corresp with [t1,..,tn] -- coi :: xi ~r ti - , CoercionN) -- Result coercion, rco + , MCoercionN) -- Result coercion, rco -- rco : (T t1..tn) ~N (T (x1 |> co1) .. (xn |> con)) flatten_args_tc tc = flatten_args all_bndrs any_named_bndrs inner_ki emptyVarSet -- NB: TyCon kinds are always closed @@ -406,8 +409,9 @@ flatten_args_tc tc = flatten_args all_bndrs any_named_bndrs inner_ki emptyVarSet flatten_args :: [TyCoBinder] -> Bool -- Binders, and True iff any of them are -- named. -> Kind -> TcTyCoVarSet -- function kind; kind's free vars - -> [Role] -> [Type] -- these are in 1-to-1 correspondence - -> FlatM ([Xi], [Coercion], CoercionN) + -> Maybe [Role] -> [Type] -- these are in 1-to-1 correspondence + -- Nothing: use all Nominal + -> FlatM ([Xi], [Coercion], MCoercionN) -- Coercions :: Xi ~ Type, at roles given -- Third coercion :: tcTypeKind(fun xis) ~N tcTypeKind(fun tys) -- That is, the third coercion relates the kind of some function (whose kind is @@ -419,15 +423,12 @@ flatten_args orig_binders any_named_bndrs orig_inner_ki orig_fvs - orig_roles + orig_m_roles orig_tys - = if any_named_bndrs - then flatten_args_slow orig_binders - orig_inner_ki - orig_fvs - orig_roles - orig_tys - else flatten_args_fast orig_binders orig_inner_ki orig_roles orig_tys + = case (orig_m_roles, any_named_bndrs) of + (Nothing, False) -> flatten_args_fast orig_tys + _ -> flatten_args_slow orig_binders orig_inner_ki orig_fvs orig_roles orig_tys + where orig_roles = fromMaybe (repeat Nominal) orig_m_roles {-# INLINE flatten_args_fast #-} -- | fast path flatten_args, in which none of the binders are named and @@ -435,75 +436,30 @@ flatten_args orig_binders -- There are many bang patterns in here. It's been observed that they -- greatly improve performance of an optimized build. -- The T9872 test cases are good witnesses of this fact. -flatten_args_fast :: [TyCoBinder] - -> Kind - -> [Role] - -> [Type] - -> FlatM ([Xi], [Coercion], CoercionN) -flatten_args_fast orig_binders orig_inner_ki orig_roles orig_tys - = fmap finish (iterate orig_tys orig_roles orig_binders) +flatten_args_fast :: [Type] + -> FlatM ([Xi], [Coercion], MCoercionN) +flatten_args_fast orig_tys + = fmap finish (iterate orig_tys) where iterate :: [Type] - -> [Role] - -> [TyCoBinder] - -> FlatM ([Xi], [Coercion], [TyCoBinder]) - iterate (ty:tys) (role:roles) (_:binders) = do - (xi, co) <- go role ty - (xis, cos, binders) <- iterate tys roles binders - pure (xi : xis, co : cos, binders) - iterate [] _ binders = pure ([], [], binders) - iterate _ _ _ = pprPanic - "flatten_args wandered into deeper water than usual" (vcat []) - -- This debug information is commented out because leaving it in - -- causes a ~2% increase in allocations in T9872{a,c,d}. - {- - (vcat [ppr orig_binders, - ppr orig_inner_ki, - ppr (take 10 orig_roles), -- often infinite! - ppr orig_tys]) - -} - - {-# INLINE go #-} - go :: Role - -> Type - -> FlatM (Xi, Coercion) - go role ty - = case role of - -- In the slow path we bind the Xi and Coercion from the recursive - -- call and then use it such - -- - -- let kind_co = mkTcSymCo $ mkReflCo Nominal (tyBinderType binder) - -- casted_xi = xi `mkCastTy` kind_co - -- casted_co = xi |> kind_co ~r xi ; co - -- - -- but this isn't necessary: - -- mkTcSymCo (Refl a b) = Refl a b, - -- mkCastTy x (Refl _ _) = x - -- mkTcGReflLeftCo _ ty (Refl _ _) `mkTransCo` co = co - -- - -- Also, no need to check isAnonTyCoBinder or isNamedBinder, since - -- we've already established that they're all anonymous. - Nominal -> setEqRel NomEq $ flatten_one ty - Representational -> setEqRel ReprEq $ flatten_one ty - Phantom -> -- See Note [Phantoms in the flattener] - do { ty <- liftTcS $ zonkTcType ty - ; return (ty, mkReflCo Phantom ty) } - + -> FlatM ([Xi], [Coercion]) + iterate (ty:tys) = do + (xi, co) <- flatten_one ty + (xis, cos) <- iterate tys + pure (xi : xis, co : cos) + iterate [] = pure ([], []) {-# INLINE finish #-} - finish :: ([Xi], [Coercion], [TyCoBinder]) -> ([Xi], [Coercion], CoercionN) - finish (xis, cos, binders) = (xis, cos, kind_co) - where - final_kind = mkPiTys binders orig_inner_ki - kind_co = mkNomReflCo final_kind + finish :: ([Xi], [Coercion]) -> ([Xi], [Coercion], MCoercionN) + finish (xis, cos) = (xis, cos, MRefl) {-# INLINE flatten_args_slow #-} -- | Slow path, compared to flatten_args_fast, because this one must track -- a lifting context. flatten_args_slow :: [TyCoBinder] -> Kind -> TcTyCoVarSet -> [Role] -> [Type] - -> FlatM ([Xi], [Coercion], CoercionN) + -> FlatM ([Xi], [Coercion], MCoercionN) flatten_args_slow binders inner_ki fvs roles tys -- Arguments used dependently must be flattened with proper coercions, but -- we're not guaranteed to get a proper coercion when flattening with the @@ -671,7 +627,9 @@ flatten_app_ty_args fun_xi fun_co arg_tys flatten_ty_con_app :: TyCon -> [TcType] -> FlatM (Xi, Coercion) flatten_ty_con_app tc tys = do { role <- getRole - ; (xis, cos, kind_co) <- flatten_args_tc tc (tyConRolesX role tc) tys + ; let m_roles | Nominal <- role = Nothing + | otherwise = Just $ tyConRolesX role tc + ; (xis, cos, kind_co) <- flatten_args_tc tc m_roles tys ; let tyconapp_xi = mkTyConApp tc xis tyconapp_co = mkTyConAppCo role tc cos ; return (homogenise_result tyconapp_xi tyconapp_co role kind_co) } @@ -680,15 +638,12 @@ flatten_ty_con_app tc tys homogenise_result :: Xi -- a flattened type -> Coercion -- :: xi ~r original ty -> Role -- r - -> CoercionN -- kind_co :: tcTypeKind(xi) ~N tcTypeKind(ty) + -> MCoercionN -- kind_co :: tcTypeKind(xi) ~N tcTypeKind(ty) -> (Xi, Coercion) -- (xi |> kind_co, (xi |> kind_co) -- ~r original ty) -homogenise_result xi co r kind_co - -- the explicit pattern match here improves the performance of T9872a, b, c by - -- ~2% - | isGReflCo kind_co = (xi `mkCastTy` kind_co, co) - | otherwise = (xi `mkCastTy` kind_co - , (mkSymCo $ GRefl r xi (MCo kind_co)) `mkTransCo` co) +homogenise_result xi co _ MRefl = (xi, co) +homogenise_result xi co r mco@(MCo kind_co) + = (xi `mkCastTy` kind_co, (mkSymCo $ GRefl r xi mco) `mkTransCo` co) {-# INLINE homogenise_result #-} -- Flatten a vector (list of arguments). @@ -696,7 +651,7 @@ flatten_vector :: Kind -- of the function being applied to these arguments -> [Role] -- If we're flatten w.r.t. ReprEq, what roles do the -- args have? -> [Type] -- the args to flatten - -> FlatM ([Xi], [Coercion], CoercionN) + -> FlatM ([Xi], [Coercion], MCoercionN) flatten_vector ki roles tys = do { eq_rel <- getEqRel ; case eq_rel of @@ -704,17 +659,17 @@ flatten_vector ki roles tys any_named_bndrs inner_ki fvs - (repeat Nominal) + Nothing tys ReprEq -> flatten_args bndrs any_named_bndrs inner_ki fvs - roles + (Just roles) tys } where - (bndrs, inner_ki, any_named_bndrs) = split_pi_tys' ki + (bndrs, inner_ki, any_named_bndrs) = split_pi_tys' ki -- "RAE" fix fvs = tyCoVarsOfType ki {-# INLINE flatten_vector #-} @@ -840,10 +795,14 @@ flatten_exact_fam_app tc tys ; Nothing -> -- That didn't work. So reduce the arguments, in STEP 3. - do { (xis, cos, kind_co) <- flatten_args_tc tc (repeat Nominal) tys + do { eq_rel <- getEqRel + -- checking eq_rel == NomEq saves ~0.5% in T9872a + ; (xis, cos, kind_co) <- if eq_rel == NomEq + then flatten_args_tc tc Nothing tys + else setEqRel NomEq $ + flatten_args_tc tc Nothing tys -- kind_co :: tcTypeKind(F xis) ~N tcTypeKind(F tys) - ; eq_rel <- getEqRel ; let role = eqRelRole eq_rel args_co = mkTyConAppCo role tc cos -- args_co :: F xis ~r F tys View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2bbcc402adb211c78cf185e0cda194e6f8d87b1...62d06215790ee056fbca69e6724a096bec00f8b0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2bbcc402adb211c78cf185e0cda194e6f8d87b1...62d06215790ee056fbca69e6724a096bec00f8b0 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 Tue Nov 24 07:43:28 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 24 Nov 2020 02:43:28 -0500 Subject: [Git][ghc/ghc][master] rts: Flush eventlog buffers from flushEventLog Message-ID: <5fbcb9a0d8784_36a71600f92c838825@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 11 changed files: - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - rts/Capability.c - rts/Capability.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h Changes: ===================================== includes/RtsAPI.h ===================================== @@ -18,8 +18,6 @@ extern "C" { #include "HsFFI.h" #include "rts/Time.h" #include "rts/Types.h" -#include "rts/EventLogWriter.h" - /* * Running the scheduler @@ -60,6 +58,9 @@ typedef struct CapabilityPublic_ { StgRegTable r; } CapabilityPublic; +/* N.B. this needs the Capability declaration above. */ +#include "rts/EventLogWriter.h" + /* ---------------------------------------------------------------------------- RTS configuration settings, for passing to hs_init_ghc() ------------------------------------------------------------------------- */ ===================================== includes/rts/EventLogWriter.h ===================================== @@ -68,3 +68,8 @@ bool startEventLogging(const EventLogWriter *writer); * Stop event logging and destroy the current EventLogWriter. */ void endEventLogging(void); + +/* + * Flush the eventlog. cap can be NULL if one is not held. + */ +void flushEventLog(Capability **cap); ===================================== libraries/base/Debug/Trace.hs ===================================== @@ -37,6 +37,7 @@ module Debug.Trace ( -- $eventlog_tracing traceEvent, traceEventIO, + flushEventLog, -- * Execution phase markers -- $markers @@ -319,3 +320,11 @@ traceMarkerIO :: String -> IO () traceMarkerIO msg = GHC.Foreign.withCString utf8 msg $ \(Ptr p) -> IO $ \s -> case traceMarker# p s of s' -> (# s', () #) + +-- | Immediately flush the event log, if enabled. +-- +-- @since 4.15.0.0 +flushEventLog :: IO () +flushEventLog = c_flushEventLog nullPtr + +foreign import ccall "flushEventLog" c_flushEventLog :: Ptr () -> IO () ===================================== rts/Capability.c ===================================== @@ -23,6 +23,7 @@ #include "Schedule.h" #include "Sparks.h" #include "Trace.h" +#include "eventlog/EventLog.h" // for flushLocalEventsBuf #include "sm/GC.h" // for gcWorkerThread() #include "STM.h" #include "RtsUtils.h" @@ -982,6 +983,10 @@ yieldCapability debugTrace(DEBUG_nonmoving_gc, "Flushing update remembered set blocks..."); break; + case SYNC_FLUSH_EVENT_LOG: + flushLocalEventsBuf(cap); + break; + default: break; } ===================================== rts/Capability.h ===================================== @@ -27,6 +27,7 @@ #include "BeginPrivate.h" +/* N.B. This must be consistent with CapabilityPublic in RtsAPI.h */ struct Capability_ { // State required by the STG virtual machine when running Haskell // code. During STG execution, the BaseReg register always points @@ -267,7 +268,8 @@ typedef enum { SYNC_OTHER, SYNC_GC_SEQ, SYNC_GC_PAR, - SYNC_FLUSH_UPD_REM_SET + SYNC_FLUSH_UPD_REM_SET, + SYNC_FLUSH_EVENT_LOG } SyncType; // ===================================== rts/RtsSymbols.c ===================================== @@ -594,6 +594,7 @@ SymI_HasProto(__word_encodeFloat) \ SymI_HasProto(stg_atomicallyzh) \ SymI_HasProto(barf) \ + SymI_HasProto(flushEventLog) \ SymI_HasProto(deRefStablePtr) \ SymI_HasProto(debugBelch) \ SymI_HasProto(errorBelch) \ ===================================== rts/Schedule.c ===================================== @@ -2070,7 +2070,7 @@ forkProcess(HsStablePtr *entry stopTimer(); // See #4074 #if defined(TRACING) - flushEventLog(); // so that child won't inherit dirty file buffers + flushAllCapsEventsBufs(); // so that child won't inherit dirty file buffers #endif pid = fork(); ===================================== rts/Trace.c ===================================== @@ -118,10 +118,10 @@ void resetTracing (void) restartEventLogging(); } -void flushTrace (void) +void flushTrace () { if (eventlog_enabled) { - flushEventLog(); + flushEventLog(NULL); } } ===================================== rts/Trace.h ===================================== @@ -319,7 +319,6 @@ void traceConcSweepEnd(void); void traceConcUpdRemSetFlush(Capability *cap); void traceNonmovingHeapCensus(uint32_t log_blk_size, const struct NonmovingAllocCensus *census); - void flushTrace(void); #else /* !TRACING */ ===================================== rts/eventlog/EventLog.c ===================================== @@ -16,6 +16,7 @@ #include "RtsUtils.h" #include "Stats.h" #include "EventLog.h" +#include "Schedule.h" #include #include @@ -272,8 +273,8 @@ stopEventLogWriter(void) } } -void -flushEventLog(void) +static void +flushEventLogWriter(void) { if (event_log_writer != NULL && event_log_writer->flushEventLog != NULL) { @@ -1541,7 +1542,7 @@ void printAndClearEventBuf (EventsBuf *ebuf) "printAndClearEventLog: could not flush event log\n" ); resetEventsBuf(ebuf); - flushEventLog(); + flushEventLogWriter(); return; } @@ -1623,6 +1624,40 @@ void postEventType(EventsBuf *eb, EventType *et) postInt32(eb, EVENT_ET_END); } +void flushLocalEventsBuf(Capability *cap) +{ + EventsBuf *eb = &capEventBuf[cap->no]; + printAndClearEventBuf(eb); +} + +// Flush all capabilities' event buffers when we already hold all capabilities. +// Used during forkProcess. +void flushAllCapsEventsBufs() +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + + for (unsigned int i=0; i < n_capabilities; i++) { + flushLocalEventsBuf(capabilities[i]); + } + flushEventLogWriter(); +} + +void flushEventLog(Capability **cap USED_IF_THREADS) +{ + ACQUIRE_LOCK(&eventBufMutex); + printAndClearEventBuf(&eventBuf); + RELEASE_LOCK(&eventBufMutex); + +#if defined(THREADED_RTS) + Task *task = getMyTask(); + stopAllCapabilitiesWith(cap, task, SYNC_FLUSH_EVENT_LOG); + releaseAllCapabilities(n_capabilities, cap ? *cap : NULL, task); +#endif + flushEventLogWriter(); +} + #else enum EventLogStatus eventLogStatus(void) @@ -1636,4 +1671,6 @@ bool startEventLogging(const EventLogWriter *writer STG_UNUSED) { void endEventLogging(void) {} +void flushEventLog(Capability **cap STG_UNUSED) {} + #endif /* TRACING */ ===================================== rts/eventlog/EventLog.h ===================================== @@ -28,8 +28,10 @@ void initEventLogging(void); void restartEventLogging(void); void freeEventLogging(void); void abortEventLogging(void); // #4512 - after fork child needs to abort -void flushEventLog(void); // event log inherited from parent void moreCapEventBufs (uint32_t from, uint32_t to); +void flushLocalEventsBuf(Capability *cap); +void flushAllCapsEventsBufs(void); +void flushAllEventsBufs(Capability *cap); /* * Post a scheduler event to the capability's event buffer (an event @@ -180,6 +182,9 @@ void postTickyCounterSamples(StgEntCounter *p); #else /* !TRACING */ +INLINE_HEADER void flushLocalEventsBuf(Capability *cap STG_UNUSED) +{ /* nothing */ } + INLINE_HEADER void postSchedEvent (Capability *cap STG_UNUSED, EventTypeNum tag STG_UNUSED, StgThreadID id STG_UNUSED, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f88f43398217a5f4c2d326555e21fb1417a21db2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f88f43398217a5f4c2d326555e21fb1417a21db2 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 Tue Nov 24 07:44:04 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 24 Nov 2020 02:44:04 -0500 Subject: [Git][ghc/ghc][master] 3 commits: gitlab-ci: Run LLVM job on appropriately-labelled MRs Message-ID: <5fbcb9c45da38_36a73fd2f1fdd7f8842165@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 7 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToLlvm/Base.hs - libraries/ghc-boot/GHC/Data/ShortText.hs - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/elf_reloc_aarch64.c - testsuite/driver/testlib.py Changes: ===================================== .gitlab-ci.yml ===================================== @@ -659,22 +659,6 @@ validate-x86_64-linux-deb9-debug: when: always expire_in: 2 week -# Disabled to alleviate CI load -.validate-x86_64-linux-deb9-llvm: - extends: .build-x86_64-linux-deb9 - stage: full-build - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - -nightly-x86_64-linux-deb9-llvm: - <<: *nightly - extends: .build-x86_64-linux-deb9 - stage: full-build - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - validate-x86_64-linux-deb9-integer-simple: extends: .build-x86_64-linux-deb9 stage: full-build @@ -759,6 +743,23 @@ release-x86_64-linux-deb10-dwarf: TEST_ENV: "x86_64-linux-deb10-dwarf" BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz" +validate-x86_64-linux-deb10-llvm: + extends: .build-x86_64-linux-deb10 + stage: full-build + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/' + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + +nightly-x86_64-linux-deb10-llvm: + <<: *nightly + extends: .build-x86_64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + ################################# # x86_64-linux-ubuntu 20.04 ################################# ===================================== compiler/GHC/CmmToLlvm/Base.hs ===================================== @@ -476,13 +476,15 @@ ghcInternalFunctions :: LlvmM () ghcInternalFunctions = do platform <- getPlatform let w = llvmWord platform + cint = LMInt $ widthInBits $ cIntWidth platform + mk "memcmp" cint [i8Ptr, i8Ptr, w] mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w] mk "memmove" i8Ptr [i8Ptr, i8Ptr, w] mk "memset" i8Ptr [i8Ptr, w, w] mk "newSpark" w [i8Ptr, i8Ptr] where mk n ret args = do - let n' = llvmDefLabel $ fsLit n + let n' = fsLit n decl = LlvmFunctionDecl n' ExternallyVisible CC_Ccc ret FixedArgs (tysToParams args) Nothing renderLlvm $ ppLlvmFunctionDecl decl @@ -516,7 +518,10 @@ getGlobalPtr llvmLbl = do let mkGlbVar lbl ty = LMGlobalVar lbl (LMPointer ty) Private Nothing Nothing case m_ty of -- Directly reference if we have seen it already - Just ty -> return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global + Just ty -> do + if llvmLbl `elem` (map fsLit ["newSpark", "memmove", "memcpy", "memcmp", "memset"]) + then return $ mkGlbVar (llvmLbl) ty Global + else return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global -- Otherwise use a forward alias of it Nothing -> do saveAlias llvmLbl ===================================== libraries/ghc-boot/GHC/Data/ShortText.hs ===================================== @@ -1,6 +1,22 @@ -{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies #-} +{-# LANGUAGE BangPatterns, MagicHash, UnboxedTuples, GeneralizedNewtypeDeriving, DerivingStrategies, CPP #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} - +-- gross hack: we manuvered ourselves into a position where we can't boot GHC with a LLVM based GHC anymore. +-- LLVM based GHC's fail to compile memcmp ffi calls. These end up as memcmp$def in the llvm ir, however we +-- don't have any prototypes and subsequently the llvm toolchain chokes on them. Since 7fdcce6d, we use +-- ShortText for the package database. This however introduces this very module; which through inlining ends +-- up bringing memcmp_ByteArray from bytestring:Data.ByteString.Short.Internal into scope, which results in +-- the memcmp call we choke on. +-- +-- The solution thusly is to force late binding via the linker instead of inlining when comping with the +-- bootstrap compiler. This will produce a slower (slightly less optimised) stage1 compiler only. +-- +-- See issue 18857. hsyl20 deserves credit for coming up with the idea for the soltuion. +-- +-- This can be removed when we exit the boot compiler window. Thus once we drop GHC-9.2 as boot compiler, +-- we can drop this code as well. +#if GHC_STAGE < 1 +{-# OPTIONS_GHC -fignore-interface-pragmas #-} +#endif -- | -- An Unicode string for internal GHC use. Meant to replace String -- in places where being a lazy linked is not very useful and a more ===================================== rts/LinkerInternals.h ===================================== @@ -141,7 +141,7 @@ typedef struct _Segment { int n_sections; } Segment; -#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) +#if defined(powerpc_HOST_ARCH) || defined(x86_64_HOST_ARCH) || defined(aarch64_HOST_ARCH) #define NEED_SYMBOL_EXTRAS 1 #endif ===================================== rts/linker/Elf.c ===================================== @@ -781,7 +781,12 @@ ocGetNames_ELF ( ObjectCode* oc ) else if (!oc->imageMapped || size < getPageSize() / 3) { bool executable = kind == SECTIONKIND_CODE_OR_RODATA; m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32; - start = m32_alloc(allocator, size, 8); + // align on 16 bytes. The reason being that llvm will emit see + // paddq statements for x86_64 under optimisation and load from + // RODATA sections. Specifically .rodata.cst16. However we don't + // handle the cst part in any way what so ever, so 16 seems + // better than 8. + start = m32_alloc(allocator, size, 16); if (start == NULL) goto fail; memcpy(start, oc->image + offset, size); alloc = SECTION_M32; @@ -940,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1867,6 +1872,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1940,6 +1946,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== testsuite/driver/testlib.py ===================================== @@ -2216,6 +2216,13 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + + # filter out nix garbage, that just keeps on showing up as errors on darwin + s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2286,6 +2293,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f88f43398217a5f4c2d326555e21fb1417a21db2...2ed3e6c0f179c06828712832d1176519cdfa82a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f88f43398217a5f4c2d326555e21fb1417a21db2...2ed3e6c0f179c06828712832d1176519cdfa82a6 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 Tue Nov 24 08:15:12 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Tue, 24 Nov 2020 03:15:12 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fbcc110dc8de_36a71600f92c848011@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - cc6f5668 by David Eichmann at 2020-11-24T03:15:01-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - d6810102 by Andreas Klebinger at 2020-11-24T03:15:02-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - b4526737 by Tim Barnes at 2020-11-24T03:15:03-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/ByteCode/Types.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Runtime/Interpreter.hs - docs/users_guide/conf.py - includes/Rts.h - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Capability.c - rts/Capability.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/357bedc3672faf699a72954f0f2b000262dae033...b45267375d83d4172607547f8f82c355a51db0cf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/357bedc3672faf699a72954f0f2b000262dae033...b45267375d83d4172607547f8f82c355a51db0cf 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 Tue Nov 24 10:13:37 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 24 Nov 2020 05:13:37 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/heap-rep-decode-tweaks Message-ID: <5fbcdcd1a3d5e_36a73fd2ff413ea0871324@gitlab.mail> Matthew Pickering pushed new branch wip/heap-rep-decode-tweaks at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/heap-rep-decode-tweaks 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 Tue Nov 24 12:35:44 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 24 Nov 2020 07:35:44 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/opt_cmm_sink Message-ID: <5fbcfe207f219_36a73fd2f90f5f308917ad@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/opt_cmm_sink at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/opt_cmm_sink 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 Tue Nov 24 13:16:53 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Tue, 24 Nov 2020 08:16:53 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/amg/fieldselectors Message-ID: <5fbd07c5cf376_36a7643e30089548d@gitlab.mail> Adam Gundry pushed new branch wip/amg/fieldselectors at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/amg/fieldselectors 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 Tue Nov 24 14:10:36 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 09:10:36 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 78 commits: Bump the # of commits searched for perf baseline Message-ID: <5fbd145ca7376_36a73fd2ff413ea0905135@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 43273f21 by Richard Eisenberg at 2020-11-24T09:09:42-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - ff788365 by Richard Eisenberg at 2020-11-24T09:09:42-05:00 Start of work in simplifying flattening - - - - - 377155fb by Richard Eisenberg at 2020-11-24T09:09:42-05:00 Much work toward simplifying CFunEqCan - - - - - 233c586b by Richard Eisenberg at 2020-11-24T09:09:42-05:00 Canonicalized function equalities. Now, onto interactions. - - - - - 379340ec by Richard Eisenberg at 2020-11-24T09:09:42-05:00 CEqCan, and canonicalization for it - - - - - b1feaa06 by Richard Eisenberg at 2020-11-24T09:09:43-05:00 Main changes done. Now to delete code. - - - - - 46fb44c5 by Richard Eisenberg at 2020-11-24T09:09:43-05:00 Kill off CFunEqCan and CTyEqCan - - - - - 31bcd677 by Richard Eisenberg at 2020-11-24T09:09:43-05:00 It compiles. - - - - - 8f889853 by Richard Eisenberg at 2020-11-24T09:09:44-05:00 Some bugfixing - - - - - 165c9719 by Richard Eisenberg at 2020-11-24T09:09:44-05:00 Lots of bug fixing - - - - - 01f8d4c0 by Richard Eisenberg at 2020-11-24T09:09:44-05:00 Expand synonyms that mention families, obvs - - - - - b5efbc62 by Richard Eisenberg at 2020-11-24T09:09:44-05:00 Super skolems are really super. - - - - - 16cdeafb by Richard Eisenberg at 2020-11-24T09:09:45-05:00 Another bug bites the dust. - - - - - 9c1ebefa by Richard Eisenberg at 2020-11-24T09:09:45-05:00 Put variable on left only when it will unify - - - - - fe65da9d by Richard Eisenberg at 2020-11-24T09:09:45-05:00 Tiny little changes - - - - - d29be562 by Richard Eisenberg at 2020-11-24T09:09:45-05:00 Use built-in axioms for injectivity - - - - - 9c448311 by Richard Eisenberg at 2020-11-24T09:09:45-05:00 Stop loop in solver due to blocked hetero eqs - - - - - 6bb90248 by Richard Eisenberg at 2020-11-24T09:09:46-05:00 Note [Runaway Derived rewriting] - - - - - 7fc769fe by Richard Eisenberg at 2020-11-24T09:09:46-05:00 Still need to check tyvar/funeq orientation - - - - - 293440ae by Richard Eisenberg at 2020-11-24T09:09:46-05:00 More bugfixing - - - - - 2e649833 by Richard Eisenberg at 2020-11-24T09:09:46-05:00 Orient FunEq/FunEq correctly wrt occurs-check - - - - - 40dbbe30 by Richard Eisenberg at 2020-11-24T09:09:47-05:00 Fix import - - - - - 9b33e7e5 by Richard Eisenberg at 2020-11-24T09:09:47-05:00 Note [Type variable cycles in Givens] - - - - - 22673fae by Richard Eisenberg at 2020-11-24T09:09:47-05:00 Handle obscure corner case in canonicalize - - - - - 56376e8c by Richard Eisenberg at 2020-11-24T09:09:47-05:00 Handle (=>) specially in pure unifier - - - - - 8689aa3e by Richard Eisenberg at 2020-11-24T09:09:47-05:00 Start deleting stuff. Hooray! - - - - - 07f1446b by Richard Eisenberg at 2020-11-24T09:09:48-05:00 Fix test output - - - - - 555fda71 by Richard Eisenberg at 2020-11-24T09:09:48-05:00 Delete delete delete !! - - - - - 58e4e20f by Richard Eisenberg at 2020-11-24T09:09:48-05:00 More deleting. Checkpoint before removing FlattenMode - - - - - e0085e42 by Richard Eisenberg at 2020-11-24T09:09:48-05:00 Remove FlattenMode - - - - - 4ed3a230 by Richard Eisenberg at 2020-11-24T09:09:49-05:00 Stopped bumping ctLocDepth in runFlatten - - - - - 5f6e46be by Richard Eisenberg at 2020-11-24T09:09:49-05:00 Finished deleting. - - - - - e7f68557 by Richard Eisenberg at 2020-11-24T09:09:49-05:00 A few error message wibbles - - - - - df970440 by Richard Eisenberg at 2020-11-24T09:09:49-05:00 Some small changes, mostly comments. - - - - - 65472b85 by Richard Eisenberg at 2020-11-24T09:09:50-05:00 Fix #18875 by breaking type variable cycles. - - - - - 25e503c3 by Richard Eisenberg at 2020-11-24T09:09:50-05:00 Actually add test files - - - - - 0f542bc8 by Richard Eisenberg at 2020-11-24T09:09:50-05:00 Add Detail (7) to the Note - - - - - 676a61a0 by Richard Eisenberg at 2020-11-24T09:09:50-05:00 A few error wibbles - - - - - 6fd1d9ae by Richard Eisenberg at 2020-11-24T09:09:51-05:00 Don't simplify extra-constraint holes - - - - - 3a269ebb by Richard Eisenberg at 2020-11-24T09:09:51-05:00 Subtleties in Note [Instance and Given overlap] - - - - - 522039f5 by Richard Eisenberg at 2020-11-24T09:09:51-05:00 Update Note [TyVar/TyVar orientation] - - - - - 87063ef7 by Richard Eisenberg at 2020-11-24T09:09:51-05:00 Actually add tests - - - - - ed3f9494 by Richard Eisenberg at 2020-11-24T09:09:52-05:00 Do mightMatchLater correctlier. - - - - - 726ef325 by Richard Eisenberg at 2020-11-24T09:09:52-05:00 Simplify getNoGivenEqs - - - - - d3cbe4cb by Richard Eisenberg at 2020-11-24T09:09:52-05:00 Simplify code a bit - - - - - cc5ba866 by Richard Eisenberg at 2020-11-24T09:09:53-05:00 Introduce 3-way for ic_given_eqs - - - - - 8fa02f7e by Richard Eisenberg at 2020-11-24T09:09:53-05:00 test LocalGivenEqs - - - - - 8df67685 by Richard Eisenberg at 2020-11-24T09:09:53-05:00 Update commentary about HasGivenEqs - - - - - dd1e840b by Richard Eisenberg at 2020-11-24T09:09:53-05:00 Update notes. - - - - - eb332ec5 by Richard Eisenberg at 2020-11-24T09:09:54-05:00 More documentation around LocalGivenEqs - - - - - dc76ece9 by Richard Eisenberg at 2020-11-24T09:09:54-05:00 Rename the flat-cache. Document it, too. - - - - - d75bb209 by Richard Eisenberg at 2020-11-24T09:09:54-05:00 Make EqualCtList into a newtype with NonEmpty - - - - - fb3dc4ab by Richard Eisenberg at 2020-11-24T09:09:54-05:00 Remove Note [No FunEq improvement for Givens] - - - - - 410f1115 by Richard Eisenberg at 2020-11-24T09:09:55-05:00 Fix compilation errors from rebasing - - - - - 5550167d by Richard Eisenberg at 2020-11-24T09:09:55-05:00 Use DTyConEnv for TcAppMap instead of UDFM - - - - - 455d7841 by Richard Eisenberg at 2020-11-24T09:09:55-05:00 Remove mention of CFunEqCan from rebasing - - - - - cc4b8a83 by Richard Eisenberg at 2020-11-24T09:09:55-05:00 Fix error output - - - - - d814d351 by Richard Eisenberg at 2020-11-24T09:09:56-05:00 Reimplement flatten_exact_fam_app Hopefully will be faster? - - - - - cedd34a1 by Richard Eisenberg at 2020-11-24T09:09:56-05:00 Improve performance - - - - - 6aab20bf by Richard Eisenberg at 2020-11-24T09:09:56-05:00 Don't fail eagerly on runaway Derived instances - - - - - 47ca6411 by Richard Eisenberg at 2020-11-24T09:09:56-05:00 Improve some comments - - - - - 5cee98a3 by Richard Eisenberg at 2020-11-24T09:09:57-05:00 Checkpoint before adding filterTM - - - - - 71fa8a4c by Richard Eisenberg at 2020-11-24T09:09:57-05:00 remove stale givens from famapp-cache - - - - - 18bee4b6 by Richard Eisenberg at 2020-11-24T09:09:57-05:00 Remove unused parameter - - - - - 5bf18684 by Richard Eisenberg at 2020-11-24T09:09:57-05:00 Address points from Hécate. - - - - - 758f674f by Richard Eisenberg at 2020-11-24T09:09:58-05:00 Reviews on GitLab - - - - - f94ad669 by Richard Eisenberg at 2020-11-24T09:09:58-05:00 Use tcSplitTyConApp_maybe in can_eq_nc' - - - - - e3be013e by Richard Eisenberg at 2020-11-24T09:09:58-05:00 Try removing (2b). Let's see what the testsuite says - - - - - 1f1bc99b by Richard Eisenberg at 2020-11-24T09:09:59-05:00 Really remove (2b) - - - - - f068d2d4 by Richard Eisenberg at 2020-11-24T09:09:59-05:00 More reactions to reviews - - - - - 68ad1a0a by Richard Eisenberg at 2020-11-24T09:09:59-05:00 Revisit [Prevent unification with type families] - - - - - 61957259 by Richard Eisenberg at 2020-11-24T09:09:59-05:00 Don't flatten during instance lookup - - - - - 1bdd8642 by Richard Eisenberg at 2020-11-24T09:10:00-05:00 Comments, etc., from Friday - - - - - 5bf08b61 by Richard Eisenberg at 2020-11-24T09:10:00-05:00 Make the fast path work without roles - - - - - c73a7e6d by Richard Eisenberg at 2020-11-24T09:10:00-05:00 Use MCo - - - - - 4112199a by Richard Eisenberg at 2020-11-24T09:10:00-05:00 Remove unused parameter - - - - - ebd6e660 by Richard Eisenberg at 2020-11-24T09:10:01-05:00 Add test case - - - - - a18f2ddd by Richard Eisenberg at 2020-11-24T09:10:01-05:00 s/flatten/rewrite` - - - - - 30 changed files: - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Map.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62d06215790ee056fbca69e6724a096bec00f8b0...a18f2dddfbb68800c8ce2fa18488d2d2e5eca983 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62d06215790ee056fbca69e6724a096bec00f8b0...a18f2dddfbb68800c8ce2fa18488d2d2e5eca983 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 Tue Nov 24 15:05:40 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 10:05:40 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 3 commits: inline finish Message-ID: <5fbd2144674be_36a73fd2ff413ea0925419@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 47433e63 by Richard Eisenberg at 2020-11-24T14:32:10+00:00 inline finish - - - - - 5300222f by Richard Eisenberg at 2020-11-24T14:49:55+00:00 Use a flag on `finish` - - - - - 6079d4e0 by Richard Eisenberg at 2020-11-24T15:05:29+00:00 Don't avoid adding inerts to cache - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Rewrite.hs Changes: ===================================== compiler/GHC/Tc/Solver/Rewrite.hs ===================================== @@ -781,10 +781,9 @@ rewrite_exact_fam_app tc tys -- STEP 1/2. Try to reduce without reducing arguments first. ; result1 <- try_to_reduce tc tys ; case result1 of - -- Don't use `finish`; + -- Don't use the cache; -- See Note [rewrite_exact_fam_app performance] - { Just (co, xi) -> do { (xi2, co2) <- bumpDepth $ rewrite_one xi - ; return (xi2, co2 `mkTcTransCo` co) } + { Just (co, xi) -> finish False (xi, co) ; Nothing -> -- That didn't work. So reduce the arguments, in STEP 3. @@ -817,7 +816,10 @@ rewrite_exact_fam_app tc tys | fr `eqCanRewriteFR` (flavour, eq_rel) -> do { traceRewriteM "rewrite family application with inert" (ppr tc <+> ppr xis $$ ppr xi) - ; finish (homogenise xi downgraded_co) } + ; finish True (homogenise xi downgraded_co) } + -- this will sometimes duplicate an inert in the cache, + -- but avoiding doing so had no impact on performance, and + -- it seems easier not to weed out that special case where inert_role = eqRelRole inert_eq_rel role = eqRelRole eq_rel @@ -829,7 +831,7 @@ rewrite_exact_fam_app tc tys -- inert didn't work. Try to reduce again, in STEP 5/6. do { result3 <- try_to_reduce tc xis ; case result3 of - Just (co, xi) -> finish (homogenise xi co) + Just (co, xi) -> finish True (homogenise xi co) Nothing -> -- we have made no progress at all: STEP 7. return (homogenise reduced (mkTcReflCo role reduced)) where @@ -837,20 +839,23 @@ rewrite_exact_fam_app tc tys where -- call this if the above attempts made progress. -- This recursively rewrites the result and then adds to the cache - finish :: (Xi, Coercion) -> RewriteM (Xi, Coercion) - finish (xi, co) = do { -- rewrite the result: FINISH 1 - (fully, fully_co) <- bumpDepth $ rewrite_one xi - ; let final_co = fully_co `mkTcTransCo` co - ; eq_rel <- getEqRel - ; flavour <- getFlavour - - -- extend the cache: FINISH 2 - ; when (eq_rel == NomEq && flavour /= Derived) $ - -- the cache only wants Nominal eqs - -- and Wanteds can rewrite Deriveds; the cache - -- has only Givens - liftTcS $ extendFamAppCache tc tys (final_co, fully) - ; return (fully, final_co) } + finish :: Bool -- add to the cache? + -> (Xi, Coercion) -> RewriteM (Xi, Coercion) + finish use_cache (xi, co) + = do { -- rewrite the result: FINISH 1 + (fully, fully_co) <- bumpDepth $ rewrite_one xi + ; let final_co = fully_co `mkTcTransCo` co + ; eq_rel <- getEqRel + ; flavour <- getFlavour + + -- extend the cache: FINISH 2 + ; when (use_cache && eq_rel == NomEq && flavour /= Derived) $ + -- the cache only wants Nominal eqs + -- and Wanteds can rewrite Deriveds; the cache + -- has only Givens + liftTcS $ extendFamAppCache tc tys (final_co, fully) + ; return (fully, final_co) } + {-# INLINE finish #-} -- Returned coercion is output ~r input, where r is the role in the RewriteM monad -- See Note [How to normalise a family application] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a18f2dddfbb68800c8ce2fa18488d2d2e5eca983...6079d4e093d5c41a0f1bfb637578fa1977eb8d3b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a18f2dddfbb68800c8ce2fa18488d2d2e5eca983...6079d4e093d5c41a0f1bfb637578fa1977eb8d3b 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 Tue Nov 24 15:26:40 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Tue, 24 Nov 2020 10:26:40 -0500 Subject: [Git][ghc/ghc][wip/T18891] Wibbles Message-ID: <5fbd2630e267e_36a73fd2ff413ea09302eb@gitlab.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: 66356469 by Simon Peyton Jones at 2020-11-24T15:26:02+00:00 Wibbles - - - - - 9 changed files: - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/dependent/should_fail/T13780a.hs - testsuite/tests/th/T9692.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -865,7 +865,7 @@ tcDataFamInstHeader -- e.g. data instance D [a] :: * -> * where ... -- Here the "header" is the bit before the "where" tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity - hs_ctxt hs_pats m_ksig hs_cons new_or_data + hs_ctxt hs_pats m_ksig _hs_cons new_or_data = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (scoped_tvs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ @@ -884,8 +884,9 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity -- Add constraints from the result signature ; res_kind <- tc_kind_sig m_ksig - -- Add constraints from the data constructors - ; kcConDecls new_or_data res_kind hs_cons + -- Do not add constraints from the data constructors + -- See Note [Kind inference for data family instances] +-- ; kcConDecls new_or_data res_kind hs_cons -- Check that the result kind of the TyCon applied to its args -- is compatible with the explicit signature (or Type, if there @@ -1049,6 +1050,73 @@ however, so this Note aims to describe these subtleties: themselves. Heavy sigh. But not truly hard; that's what tcbVisibilities does. +Note [Kind inference for data family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this GADT-style data type declaration, where I have used +fresh variables in the data constructor's type, to stress that c,d are +quite distinct from a,b. + data T a b where + MkT :: forall c d. c d -> T c d + +Following Note [Inferring kinds for type declarations] in GHC.Tc.TyCl, +to infer T's kind, we initially give T :: kappa, a monomorpic kind, +gather constraints from the header and data constructors, and conclude + T :: (kappa1 -> type) -> kappa1 -> Type +Then we generalise, giving + T :: forall k. (k->Type) -> k -> Type + +Now what about a data /instance/ decl + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p Int where ... + +No doubt here! The poly-kinded T is instantiate with k=Type, so the +header really looks like + data instance T @Type (p :: Type->Type) Int where ... + +But what about this? + data instance T p q where + MkT :: forall r. r Int -> T r Int + +Remember: we already /fully know/ T's kind -- that came from the +family declaration, and is not influenced by the data instances. + +So what kind do 'p' and 'q' have? No clues from the header, but from +the data constructor we can clearly see that (r :: Type->Type). Does +that mean that the the /entire data instance/ is instantiated at Type, +like this? + data instance T @Type (p :: Type->Type) (q :: Type) where + ... + +Not at all! This is a /GADT/-style decl, so the kind argument might +be instantiated by the GADT, thus: + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall (r :: Type -> Type). + r Int -> T @Type r Int + +SHORT SUMMARY: in a data instance decl, it's not clear whether kind +constraints arising from the data constructors should be considered +local to the (GADT) data /constructor/ or should apply to the entire +data instance. + +DESIGN CHOICE: in data/newtype family instance declarations, we ignore +the /data constructor/ declarations altogether, looking only at the +data instance /header/. + +Observations: +* This choice is simple to describe, as well as simple to implment. + For a data/newtype instance decl, the instance kinds are influenced + /only/ by the header. + +* We could treat Haskell-98 style data-instance decls differently, by + taking the data constructors into account, since there are no GADT + issues. + +* Ditto newtypes, since again you can't have newtype GADTs. + +But for now at least, we keep the simplest choice. See #18891 and !4419 +for more discussion of this issue.a + -} ===================================== testsuite/tests/dependent/should_fail/T13780a.hs ===================================== @@ -1,9 +1,11 @@ {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE DataKinds, PolyKinds #-} module T13780a where -data family Sing (a :: k) +data family Sing (c :: k) + +data Foo b = b ~ Bool => MkFoo -data Foo a = a ~ Bool => MkFoo data instance Sing (z :: Foo a) = (z ~ MkFoo) => SMkFoo ===================================== testsuite/tests/th/T9692.hs ===================================== @@ -12,7 +12,7 @@ class C a where data F a (b :: k) :: Type instance C Int where - data F Int x = FInt x + data F Int (x :: Type) = FInt x $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs ===================================== @@ -4,6 +4,7 @@ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} module UnliftedNewtypesUnassociatedFamily where @@ -20,7 +21,14 @@ newtype instance DFT ('TupleRep '[ 'IntRep, 'WordRep]) data instance DFT 'LiftedRep = MkDFT4 | MkDFT5 data family DF :: TYPE (r :: RuntimeRep) -newtype instance DF = MkDF1 Int# -newtype instance DF = MkDF2 Word# -newtype instance DF = MkDF3 (# Int#, Word# #) + +newtype instance DF :: TYPE 'IntRep where + MkDF1 :: Int# -> DF + +newtype instance DF :: TYPE 'WordRep where + MkDF2 :: Word# -> DF + +newtype instance DF :: TYPE ('TupleRep '[ 'IntRep, 'WordRep ]) where + MkDF3 :: (# Int#, Word# #) -> DF + data instance DF = MkDF4 | MkDF5 ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr ===================================== @@ -1,11 +1,5 @@ -UnliftedNewtypesFamilyKindFail2.hs:12:20: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the newtype instance declaration for ‘F’ - -UnliftedNewtypesFamilyKindFail2.hs:12:31: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the type ‘(F 5)’ - In the definition of data constructor ‘MkF’ +UnliftedNewtypesFamilyKindFail2.hs:12:20: error: + • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ + • In the first argument of ‘F’, namely ‘5’ + In the newtype instance declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesInstanceFail.stderr ===================================== @@ -5,10 +5,3 @@ UnliftedNewtypesInstanceFail.hs:13:3: error: but ‘Bar Bool’ has kind ‘TYPE 'IntRep’ • In the newtype instance declaration for ‘Bar’ In the instance declaration for ‘Foo Bool’ - -UnliftedNewtypesInstanceFail.hs:14:17: error: - • Couldn't match kind ‘'WordRep’ with ‘'IntRep’ - Expected kind ‘TYPE 'IntRep’, but ‘Word#’ has kind ‘TYPE 'WordRep’ - • In the type ‘Word#’ - In the definition of data constructor ‘BarBoolC’ - In the newtype instance declaration for ‘Bar’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} + +module UnliftedNewtypesUnassociatedFamily where + +import GHC.Int (Int(I#)) +import GHC.Word (Word(W#)) +import GHC.Exts (Int#,Word#) +import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep)) + +data family DF :: TYPE (r :: RuntimeRep) + +-- All these fail: see #18891 and !4419 +-- See Note [Kind inference for data family instances] +-- in GHC.Tc.TyCl.Instance +newtype instance DF = MkDF1a Int# +newtype instance DF = MkDF2a Word# +newtype instance DF = MkDF3a (# Int#, Word# #) ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr ===================================== @@ -0,0 +1,18 @@ + +UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error: + • Expecting a lifted type, but ‘Int#’ is unlifted + • In the type ‘Int#’ + In the definition of data constructor ‘MkDF1a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error: + • Expecting a lifted type, but ‘Word#’ is unlifted + • In the type ‘Word#’ + In the definition of data constructor ‘MkDF2a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error: + • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted + • In the type ‘(# Int#, Word# #)’ + In the definition of data constructor ‘MkDF3a’ + In the newtype instance declaration for ‘DF’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKind', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, ['']) test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, ['']) +test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, ['']) test('T13834', normal, compile_fail, ['']) test('T17077', normal, compile_fail, ['']) test('T16512a', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/66356469127cf1b67b00ee3a1dbaf382776cdbb1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/66356469127cf1b67b00ee3a1dbaf382776cdbb1 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 Tue Nov 24 15:58:38 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Tue, 24 Nov 2020 10:58:38 -0500 Subject: [Git][ghc/ghc][wip/heap-rep-decode-tweaks] 2 commits: Remove special case for GHC.ByteCode.Instr Message-ID: <5fbd2dae75e26_36a73fd2ff413ea0934197@gitlab.mail> Matthew Pickering pushed to branch wip/heap-rep-decode-tweaks at Glasgow Haskell Compiler / GHC Commits: 778af89a by Matthew Pickering at 2020-11-24T15:57:14+00:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - 4b844a5c by Matthew Pickering at 2020-11-24T15:58:23+00:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 1 changed file: - libraries/ghc-heap/GHC/Exts/Heap.hs Changes: ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -29,6 +29,7 @@ module GHC.Exts.Heap ( , PrimType(..) , HasHeapRep(getClosureData) , getClosureDataFromHeapRep + , getClosureDataFromHeapRepPrim -- * Info Table types , StgInfoTable(..) @@ -152,26 +153,34 @@ getClosureDataFromHeapObject x = do STACK -> pure $ UnsupportedClosure infoTable _ -> getClosureDataFromHeapRep heapRep infoTablePtr ptrList + -- | Convert an unpacked heap object, to a `GenClosure b`. The inputs to this -- function can be generated from a heap object using `unpackClosure#`. -getClosureDataFromHeapRep - :: ByteArray# +getClosureDataFromHeapRep :: ByteArray# -> Ptr StgInfoTable -> [b] -> IO (GenClosure b) +getClosureDataFromHeapRep heapRep infoTablePtr pts = do + itbl <- peekItbl infoTablePtr + getClosureDataFromHeapRepPrim (dataConNames infoTablePtr) itbl heapRep pts + +getClosureDataFromHeapRepPrim + :: IO (String, String, String) + -- ^ A continuation used to decode the constructor description field, + -- in ghc-debug this code can lead to segfaults because dataConNames + -- will dereference a random part of memory. + -> StgInfoTable + -- ^ The `StgInfoTable` of the closure, extracted from the heap + -- representation. + -> ByteArray# -- ^ Heap representation of the closure as returned by `unpackClosure#`. -- This includes all of the object including the header, info table -- pointer, pointer data, and non-pointer data. The ByteArray# may be -- pinned or unpinned. - -> Ptr StgInfoTable - -- ^ Pointer to the `StgInfoTable` of the closure, extracted from the heap - -- representation. The info table must not be movable by GC i.e. must be in - -- pinned or off-heap memory. -> [b] -- ^ Pointers in the payload of the closure, extracted from the heap -- representation as returned by `collect_pointers()` in `Heap.c`. The type -- `b` is some representation of a pointer e.g. `Any` or `Ptr Any`. -> IO (GenClosure b) -- ^ Heap representation of the closure. -getClosureDataFromHeapRep heapRep infoTablePtr pts = do - itbl <- peekItbl infoTablePtr +getClosureDataFromHeapRepPrim getConDesc itbl heapRep pts = do let -- heapRep as a list of words. rawHeapWords :: [Word] rawHeapWords = [W# (indexWordArray# heapRep i) | I# i <- [0.. end] ] @@ -189,10 +198,8 @@ getClosureDataFromHeapRep heapRep infoTablePtr pts = do npts = drop (closureTypeHeaderSize (tipe itbl) + length pts) rawHeapWords case tipe itbl of t | t >= CONSTR && t <= CONSTR_NOCAF -> do - (p, m, n) <- dataConNames infoTablePtr - if m == "GHC.ByteCode.Instr" && n == "BreakInfo" - then pure $ UnsupportedClosure itbl - else pure $ ConstrClosure itbl pts npts p m n + (p, m, n) <- getConDesc + pure $ ConstrClosure itbl pts npts p m n t | t >= THUNK && t <= THUNK_STATIC -> do pure $ ThunkClosure itbl pts npts View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51e3ecc54142ea04965bf7e2b66622eb118f7ab6...4b844a5c89889fb4f3f21825f50d6281519c84ea -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51e3ecc54142ea04965bf7e2b66622eb118f7ab6...4b844a5c89889fb4f3f21825f50d6281519c84ea 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 Tue Nov 24 16:04:29 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Tue, 24 Nov 2020 11:04:29 -0500 Subject: [Git][ghc/ghc][wip/T18599] Imlement Outputable for new syntax Message-ID: <5fbd2f0d170a4_36a71172f34c937272@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: b4b3f656 by Shayne Fletcher at 2020-11-24T11:04:16-05:00 Imlement Outputable for new syntax - - - - - 1 changed file: - compiler/GHC/Hs/Expr.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -241,14 +241,8 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} --- New for RecordDotSyntax - --- e.g. "foo.bar.baz = 42" is --- ProjUpdate { --- pb_fIELDS=["foo","bar","baz"] --- , pb_exp=42 --- , pb_func=\a -> setField@"foo" a .... 42 --- } +-- New for RecordDotSyntax. + data ProjUpdate' p arg = ProjUpdate { pb_fIELDS :: [Located FastString] @@ -261,6 +255,12 @@ type LHsProjUpdate p arg = Located (ProjUpdate p arg) type RecUpdProj p = ProjUpdate' p (LHsExpr p) type LHsRecUpdProj p = Located (RecUpdProj p) +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate {pb_fIELDS = flds, pb_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -480,55 +480,48 @@ data HsExpr p -- not the family tycon - -- | Record field selection. - -- Expressions of these cases arise only when the RecordDotSyntax - -- langauge extensions is enabled. - - -- e.g. z.x = GetField { - -- gf_ext=noExtField, gf_expr=z, gf_fIELD=x, gf_getField = getField @"x" z - -- }. - | GetField - { gf_ext :: XGetField p - , gf_expr :: LHsExpr p - , gf_fIELD :: Located FastString - , gf_getField :: LHsExpr p -- Equivalent 'getField' term. - } + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_fIELD :: Located FastString + , gf_getField :: LHsExpr p -- Equivalent 'getField' term. + } - -- Record update. + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, - -- 'GHC.Parser.Annotation.AnnDot','GHC.Parser.Annotation.AnnDotdot', - -- 'GHC.Parser.Annotation.AnnClose' @'}'@ - - -- Expressions of these cases arise only when the RecordDotSyntax - -- langauge extensions is enabled. - - -- e.g. a{foo.bar.baz=1, quux} = RecordDotUpd { - -- rdupd_ext=noExtField, rdupd_expr=a, rdupd_updates=[...], rdupd_setField=setField@"quux" (setField@"foo"...a... 1) quux - -- }, + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } - | RecordDotUpd - { rdupd_ext :: XRecordDotUpd p - , rdupd_expr :: LHsExpr p - , rdupd_upds :: [LHsRecUpdProj p] - , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. - } + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. - -- | Record field selector. - -- Expressions of these cases arise only when the RecordDotSyntax - -- langauge extensions is enabled. - - -- e.g. (.x) = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x], proj_projection = \z -> z.x - -- }, - -- (.x.y) = Projection { - -- proj_ext=noExtField, proj_fIELDS=[.x, .y], proj_projection = (\z -> z.y) . (\z -> z.x) - -- } - | Projection - { proj_ext :: XProjection p - , proj_fIELDS :: [Located FastString] - , proj_projection :: LHsExpr p -- Equivalent 'getField' term. - } + | Projection { + proj_ext :: XProjection p + , proj_fIELDS :: [Located FastString] + , proj_projection :: LHsExpr p -- Equivalent 'getField' term. + } -- | Expression with an explicit type signature. @e :: type@ -- @@ -1282,14 +1275,13 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) -ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field, gf_getField = _}) +ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field }) = ppr fexp <> dot <> ppr field -ppr_expr (Projection { proj_fIELDS = _, proj_projection = _}) - = undefined {- TODO: implement this -} +ppr_expr (Projection { proj_fIELDS = flds }) = parens (hcat (punctuate dot (map ppr flds))) -ppr_expr (RecordDotUpd { rdupd_expr = _, rdupd_upds = _, rdupd_setField =_ }) - = undefined {- TODO: implement this -} +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4b3f656e5a1fad25f68b7bc50a6091dd210d73b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b4b3f656e5a1fad25f68b7bc50a6091dd210d73b 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 Tue Nov 24 16:16:18 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 11:16:18 -0500 Subject: [Git][ghc/ghc][wip/facebook/ghc-8.8-unloading] 13 commits: Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)" Message-ID: <5fbd31d227dba_36a71172f34c937446@gitlab.mail> Ben Gamari pushed to branch wip/facebook/ghc-8.8-unloading at Glasgow Haskell Compiler / GHC Commits: 2ce2a5b4 by Pepe Iborra at 2020-11-24T01:17:25+00:00 Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)" This reverts commit 1c18d3b41f897f34a93669edaebe6069f319f9e2. - - - - - 711fffed by Ömer Sinan Ağacan at 2020-11-24T01:17:25+00:00 rts: Properly free the RTSSummaryStats structure `stat_exit` always allocates a `RTSSummaryStats` but only sometimes frees it, which casues leaks. With this patch we unconditionally free the structure, fixing the leak. Fixes #16584 - - - - - 237180d2 by pepeiborra at 2020-11-24T01:17:25+00:00 Define __FACEBOOK_HASKELL__ Summary: Adds a new __FACEBOOK_HASKELL__ CPP definition for use in conditional compilation. This is needed because fbghc makes api changes in the ghc package, which can break downstream consumers like ghcide Test Plan: ## Doesn't break anything ``` $ tp2_use_local ghc $ buck build common/hs/... haxl/... tools/build/... sigma/haxl/... ``` ## Can be used for conditional compilation $FBCODE/experimental/pepeiborra/Hellofacebook.hs: ```haskell {-# LANGUAGE CPP #-} module Hellofacebook where main :: IO () main = #ifdef __FACEBOOK_HASKELL__ putStrLn "Hello Facebook" #else putStrLn "Hello dummy" #endif ``` $FBCODE/experimental/pepeiborra/TARGETS: ``` load("@fbcode_macros//build_defs:haskell_binary.bzl", "haskell_binary") haskell_binary( name = "hellofacebook", srcs = [ "Hellofacebook.hs", ], main = "Hellofacebook" ) ``` Test ``` $ buck run //experimental/pepeiborra:hellofacebook Building: finished in 0.4 sec (100%) 41/41 jobs, 0 updated Total time: 0.4 sec Hello Facebook ``` Reviewers: josefs, rayshih, watashi Reviewed By: watashi Subscribers: smarlow Differential Revision: https://phabricator.intern.facebook.com/D22901280 Tasks: T70949920 Tags: haskell, bootcamp, GHC Signature: 22901280:1596477273:1c220ebed71b59079ab022af9b50223d99257be8 - - - - - eecf9f27 by Pepe Iborra at 2020-11-24T01:17:25+00:00 Revert "Add a RTS option -xp to load PIC object anywhere in address space" This reverts commit cb3f710d952c0a2bad539f76c2ab6d07ba894bea. - - - - - 552714a2 by Pepe Iborra at 2020-11-24T01:17:25+00:00 Revert "Revert "Add a RTS option -xp to load PIC object anywhere in address space"" This reverts commit 82a716431cc680392e332bc2b1a1fd0d7faa4cd8. - - - - - 54527eff by Pepe Iborra at 2020-11-24T01:17:25+00:00 Revert "Revert "Allocate bss section within proper range of other sections"" This reverts commit 9cbf6f2baf793e361d41b9c36497c5601ff22253. - - - - - a94ffd1b by Ben Gamari at 2020-11-24T01:17:25+00:00 Revert "Reimplement fix related to load/unload native object" This reverts commit 8edf564362e37c9740a351f1d71f2fa5e042f7b1. - - - - - a226fc88 by Ben Gamari at 2020-11-24T01:17:25+00:00 Revert "Apply upstream patch 3842: Linker: Object unloading" This reverts commit e508c92828c7e009b6f7df16cd7be2147c4a9026. - - - - - 91907765 by Ben Gamari at 2020-11-24T01:18:39+00:00 Revert "Add loadNativeObj and unloadNativeObj" This reverts commit b6482d18f78fc52de3321c03ab20cb84f0253016. - - - - - 8bc40df0 by Ben Gamari at 2020-11-24T01:18:43+00:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. (cherry picked from commit c492134912e5270180881b7345ee86dc32756bdd) (cherry picked from commit ed57c3a9eb9286faa222f98e484a9ef3432b2025) - - - - - 91950b3b by Ben Gamari at 2020-11-24T01:18:43+00:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. (cherry picked from commit 40dc91069d15bfc1d81f1722b39e06cac8fdddd1) (cherry picked from commit 65be3832f3aa48bbde896ee846c18fcba1f16b42) - - - - - c043710a by Ömer Sinan Ağacan at 2020-11-24T01:18:43+00:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) (cherry picked from commit a4153029347c48be38bace114438b72475e2c40f) - - - - - 0ac69171 by Ray Shih at 2020-11-24T01:18:43+00:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. (cherry picked from commit 2782487f5f6ad9df4dc8725226a47f07fec77f9f) - - - - - 30 changed files: - compiler/deSugar/DsForeign.hs - compiler/ghci/Linker.hs - compiler/main/DriverPipeline.hs - docs/users_guide/8.8.1-notes.rst - includes/Rts.h - includes/ghc.mk - + includes/rts/ForeignExports.h - includes/rts/storage/GC.h - rts/CheckUnload.c - rts/CheckUnload.h - + rts/ForeignExports.c - + rts/ForeignExports.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/RtsSymbols.c - rts/Stats.c - rts/linker/Elf.c - rts/linker/Elf.h - rts/linker/MachO.c - rts/linker/MachO.h - rts/linker/PEi386.c - rts/linker/PEi386.h - rts/linker/SymbolExtras.c - rts/linker/SymbolExtras.h - rts/rts.cabal.in - rts/sm/Evac.c - rts/sm/GC.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4d6a8d55db4a28274d080351352baaaf41027d40...0ac691710c8131767b940f0e36b171312dd1ba9e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4d6a8d55db4a28274d080351352baaaf41027d40...0ac691710c8131767b940f0e36b171312dd1ba9e 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 Tue Nov 24 16:22:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 11:22:12 -0500 Subject: [Git][ghc/ghc][wip/facebook/ghc-8.8-unloading] 5 commits: Revert "Add loadNativeObj and unloadNativeObj" Message-ID: <5fbd3334e53b2_36a73fd2f1d86400937622@gitlab.mail> Ben Gamari pushed to branch wip/facebook/ghc-8.8-unloading at Glasgow Haskell Compiler / GHC Commits: b8a23380 by Ben Gamari at 2020-11-24T16:21:44+00:00 Revert "Add loadNativeObj and unloadNativeObj" This reverts commit b6482d18f78fc52de3321c03ab20cb84f0253016. - - - - - fe92ef34 by Ben Gamari at 2020-11-24T16:21:48+00:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. (cherry picked from commit c492134912e5270180881b7345ee86dc32756bdd) (cherry picked from commit ed57c3a9eb9286faa222f98e484a9ef3432b2025) - - - - - d79732be by Ben Gamari at 2020-11-24T16:21:48+00:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. (cherry picked from commit 40dc91069d15bfc1d81f1722b39e06cac8fdddd1) (cherry picked from commit 65be3832f3aa48bbde896ee846c18fcba1f16b42) - - - - - 8ded6f17 by Ömer Sinan Ağacan at 2020-11-24T16:21:48+00:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) (cherry picked from commit a4153029347c48be38bace114438b72475e2c40f) - - - - - 958aba5a by Ray Shih at 2020-11-24T16:21:48+00:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. (cherry picked from commit 2782487f5f6ad9df4dc8725226a47f07fec77f9f) - - - - - 30 changed files: - compiler/deSugar/DsForeign.hs - compiler/ghci/Linker.hs - includes/Rts.h - + includes/rts/ForeignExports.h - includes/rts/storage/GC.h - rts/CheckUnload.c - rts/CheckUnload.h - + rts/ForeignExports.c - + rts/ForeignExports.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/RtsSymbols.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/rts.cabal.in - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - rts/sm/Storage.c - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ac691710c8131767b940f0e36b171312dd1ba9e...958aba5ae6b579646c3c8055b1c9d3c17c3bbb03 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0ac691710c8131767b940f0e36b171312dd1ba9e...958aba5ae6b579646c3c8055b1c9d3c17c3bbb03 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 Tue Nov 24 17:03:18 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 12:03:18 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-9.0] 257 commits: Bignum: add support for negative shifts (fix #18499) Message-ID: <5fbd3cd68b2d9_36a71600f92c94186b@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-9.0 at Glasgow Haskell Compiler / GHC Commits: 32496789 by Sylvain Henry at 2020-08-11T17:43:13+02:00 Bignum: add support for negative shifts (fix #18499) shiftR/shiftL support negative arguments despite Haskell 2010 report saying otherwise. We explicitly test for negative values which is bad (it gets in the way of constant folding, etc.). Anyway, for consistency we fix Bits instancesof Integer/Natural. - - - - - b4cccab3 by Sylvain Henry at 2020-08-11T17:48:05+02:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - 817f94f5 by Sylvain Henry at 2020-08-11T17:48:22+02:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - eab2511e by Sylvain Henry at 2020-08-12T11:43:42+02:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3745bdb6 by Sylvain Henry at 2020-08-12T11:43:42+02:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 7cf007cc by David Binder at 2020-08-13T18:22:38-04:00 Fix dead link to haskell prime discussion - - - - - 205f168c by BinderDavid at 2020-08-13T18:22:38-04:00 Replace broken links to old haskell-prime site by working links to gitlab instance. [skip ci] - - - - - 29794212 by Daniel Gröber at 2020-08-13T18:22:38-04:00 Remove length field from FastString - - - - - f8804cd8 by Daniel Gröber at 2020-08-13T18:22:38-04:00 Use ShortByteString for FastString There are multiple reasons we want this: - Fewer allocations: ByteString has 3 fields, ShortByteString just has one. - ByteString memory is pinned: - This can cause fragmentation issues (see for example #13110) but also - makes using FastStrings in compact regions impossible. Metric Decrease: T5837 T12150 T12234 T12425 - - - - - 5acdf506 by Daniel Gröber at 2020-08-13T18:22:38-04:00 Pass specialised utf8DecodeChar# to utf8DecodeLazy# for performance Currently we're passing a indexWord8OffAddr# type function to utf8DecodeLazy# which then passes it on to utf8DecodeChar#. By passing one of utf8DecodeCharAddr# or utf8DecodeCharByteArray# instead we benefit from the inlining and specialization already done for those. - - - - - a9b46ec3 by Daniel Gröber at 2020-08-13T18:22:38-04:00 Encoding: Add comment about tricky ForeignPtr lifetime - - - - - fcb9e94d by Daniel Gröber at 2020-08-13T18:22:38-04:00 Use IO constructor instead of `stToIO . ST` - - - - - 44b28e97 by Daniel Gröber at 2020-08-13T18:22:38-04:00 Encoding: Remove redundant use of withForeignPtr - - - - - f0fe989d by Daniel Gröber at 2020-08-13T18:22:38-04:00 Encoding: Reformat utf8EncodeShortByteString to be more consistent - - - - - 59cd5cd4 by Daniel Gröber at 2020-08-13T18:22:38-04:00 FastString: Reintroduce character count cache Metric Increase: ManyConstructors Metric Decrease: T4029 - - - - - 0f66e49e by Ben Gamari at 2020-08-13T18:22:38-04:00 get-win32-tarballs: Fix detection of missing tarballs This fixes the error message given by configure when the user attempts to configure without first download the win32 tarballs. - - - - - 3ecac53c by Andreas Klebinger at 2020-08-13T18:22:39-04:00 Enable BangPatterns, ScopedTypeVariables for ghc and hadrian by default. This is only for their respective codebases. - - - - - dbf77b79 by Sylvain Henry at 2020-08-13T18:22:39-04:00 Remove unused "ncg" flag This flag has been removed in 066b369de2c6f7da03c88206288dca29ab061b31 in 2011. - - - - - 4e22de2a by Sylvain Henry at 2020-08-13T18:22:39-04:00 Don't panic if the NCG isn't built (it is always built) - - - - - e27698ce by Sylvain Henry at 2020-08-13T18:22:39-04:00 Remove unused sGhcWithNativeCodeGen - - - - - 666acbd4 by Sylvain Henry at 2020-08-13T18:22:39-04:00 Correctly test active backend Previously we used a platform settings to detect if the native code generator was used. This was wrong. We need to use the `DynFlags.hscTarget` field instead. - - - - - ce5408c0 by Sylvain Henry at 2020-08-13T18:22:39-04:00 Replace ghcWithNativeCodeGen with a proper Backend datatype * Represent backends with a `Backend` datatype in GHC.Driver.Backend * Don't detect the default backend to use for the target platform at compile time in Hadrian/make but at runtime. It makes "Settings" simpler and it is a step toward making GHC multi-target. * The latter change also fixes hadrian which has not been updated to take into account that the NCG now supports AIX and PPC64 (cf df26b95559fd467abc0a3a4151127c95cb5011b9 and d3c1dda60d0ec07fc7f593bfd83ec9457dfa7984) * Also we don't treat iOS specifically anymore (cf cb4878ffd18a3c70f98bdbb413cd3c4d1f054e1f) - - - - - 9751d499 by Tamar Christina at 2020-08-13T18:22:39-04:00 winio: restore console cp on exit (cherry picked from commit cdd0ff16f20ce920c74f9128a1067cbe1bd378c2) - - - - - 5438dcec by Tamar Christina at 2020-08-13T18:22:39-04:00 winio: change memory allocation strategy and fix double free errors. (cherry picked from commit c1f4f81d3a439cd1a8128e4ab11c7caac7cc0ad8) - - - - - 5544d17a by Stefan Schulze Frielinghaus at 2020-08-13T18:22:39-04:00 Require SMP support in order to build a threaded stage1 Fixes 18266 (cherry picked from commit fc0f6fbcd95f2dc69a8efabbee2d8a485c34cc47) - - - - - e66e281d by Matthias Andreas Benkard at 2020-08-13T18:22:39-04:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. (cherry picked from commit a7c4439a407ad85b76aab9301fda61e7c10183ff) - - - - - 986063cf by Ben Gamari at 2020-08-13T18:22:39-04:00 rts/win32: Exit with EXIT_HEAPOVERFLOW if memory commit fails Since switching to the two-step allocator, the `outofmem` test fails via `osCommitMemory` failing to commit. However, this was previously exiting with `EXIT_FAILURE`, rather than `EXIT_HEAPOVERFLOW`. I think the latter is a more reasonable exit code for this case and matches the behavior on POSIX platforms. (cherry picked from commit da7269a4472856ba701d956a247599f721e9915e) - - - - - b2f8c6a7 by Ben Gamari at 2020-08-13T18:22:39-04:00 testsuite: Update win32 output for parseTree (cherry picked from commit f153a1d0a3351ad4d94cef4cef8e63bab5b47008) - - - - - 83a0649c by Ben Gamari at 2020-08-13T18:22:39-04:00 testsuite: Normalise WinIO error message differences Previously the old Windows IO manager threw different errors than WinIO. We now canonicalise these to the WinIO errors. (cherry picked from commit e91672f0b7185bbafbe8ed1f2ae2cb775111f950) - - - - - 97ac5b2a by Ben Gamari at 2020-08-13T18:22:39-04:00 gitlab-ci: Kill ssh-agent after pushing test metrics Otherwise the Windows builds hang forever waiting for the process to terminate. (cherry picked from commit 9cbfe0868418a531da0872b0c477a15aa67f8861) - - - - - 8f1154d3 by Tamar Christina at 2020-08-13T18:22:39-04:00 winio: remove dead argument to stg_newIOPortzh (cherry picked from commit 8236925fc8cc2e6e3fed61a0676fa65270a4a538) - - - - - 39c6fbae by Tamar Christina at 2020-08-13T18:22:39-04:00 winio: fix detection of tty terminals (cherry picked from commit ce0a1d678fbc8efa5fd384fd0227b7b3dc97cadd) - - - - - b784c75a by Tamar Christina at 2020-08-13T18:22:40-04:00 winio: update codeowners (cherry picked from commit 52685cf7c077c51e3719e3c4dd5ca8257a99c4ea) - - - - - 8388567e by Ben Gamari at 2020-08-13T18:22:40-04:00 Drop 32-bit Windows support As noted in #18487, we have reached the end of this road. (cherry picked from commit aa054d32a8ff69c334293a0d6c9d11b83a236a96) - - - - - 353521ab by Simon Peyton Jones at 2020-08-13T18:22:40-04:00 Eta-expand the Simplifier monad This patch eta-expands the Simplifier's monad, using the method explained in GHC.Core.Unify Note [The one-shot state monad trick]. It's part of the exta-expansion programme in #18202. It's a tiny patch, but is worth a 1-2% reduction in bytes-allocated by the compiler. Here's the list, based on the compiler-performance tests in perf/compiler: Reduction in bytes allocated T10858(normal) -0.7% T12425(optasm) -1.3% T13056(optasm) -1.8% T14683(normal) -1.1% T15164(normal) -1.3% T15630(normal) -1.4% T17516(normal) -2.3% T18282(normal) -1.6% T18304(normal) -0.8% T1969(normal) -0.6% T4801(normal) -0.8% T5321FD(normal) -0.7% T5321Fun(normal) -0.5% T5642(normal) -0.9% T6048(optasm) -1.1% T9020(optasm) -2.7% T9233(normal) -0.7% T9675(optasm) -0.5% T9961(normal) -2.9% WWRec(normal) -1.2% Metric Decrease: T12425 T9020 T9961 (cherry picked from commit 3d345c9680ab3d766ef43dd8389ccc1eaeca066c) - - - - - c0a3283a by Ben Gamari at 2020-08-13T18:22:40-04:00 gitlab-ci: Ensure that Hadrian jobs don't download artifacts Previously the Hadrian jobs had the default dependencies, meaning that they would download artifacts from all jobs of earlier stages. This is unneccessary. (cherry picked from commit 57aca6bba1c000f8542ce94e8b724b0334ff96d4) - - - - - e14ee26b by Ben Gamari at 2020-08-13T18:22:40-04:00 gitlab-ci: Bump bootstrap compiler to 8.8.4 Hopefully this will make the Windows jobs a bit more reliable. (cherry picked from commit 0a815cea9fa11ce6ef22aec3525dd7a0df541daf) - - - - - cf9a6c17 by Simon Peyton Jones at 2020-08-13T18:22:40-04:00 This patch addresses the exponential blow-up in the simplifier. Specifically: #13253 exponential inlining #10421 ditto #18140 strict constructors #18282 another nested-function call case This patch makes one really significant changes: change the way that mkDupableCont handles StrictArg. The details are explained in GHC.Core.Opt.Simplify Note [Duplicating StrictArg]. Specific changes * In mkDupableCont, when making auxiliary bindings for the other arguments of a call, add extra plumbing so that we don't forget the demand on them. Otherwise we haev to wait for another round of strictness analysis. But actually all the info is to hand. This change affects: - Make the strictness list in ArgInfo be [Demand] instead of [Bool], and rename it to ai_dmds. - Add as_dmd to ValArg - Simplify.makeTrivial takes a Demand - mkDupableContWithDmds takes a [Demand] There are a number of other small changes 1. For Ids that are used at most once in each branch of a case, make the occurrence analyser record the total number of syntactic occurrences. Previously we recorded just OneBranch or MultipleBranches. I thought this was going to be useful, but I ended up barely using it; see Note [Note [Suppress exponential blowup] in GHC.Core.Opt.Simplify.Utils Actual changes: * See the occ_n_br field of OneOcc. * postInlineUnconditionally 2. I found a small perf buglet in SetLevels; see the new function GHC.Core.Opt.SetLevels.hasFreeJoin 3. Remove the sc_cci field of StrictArg. I found I could get its information from the sc_fun field instead. Less to get wrong! 4. In ArgInfo, arrange that ai_dmds and ai_discs have a simpler invariant: they line up with the value arguments beyond ai_args This allowed a bit of nice refactoring; see isStrictArgInfo, lazyArgcontext, strictArgContext There is virtually no difference in nofib. (The runtime numbers are bogus -- I tried a few manually.) Program Size Allocs Runtime Elapsed TotalMem -------------------------------------------------------------------------------- fft +0.0% -2.0% -48.3% -49.4% 0.0% multiplier +0.0% -2.2% -50.3% -50.9% 0.0% -------------------------------------------------------------------------------- Min -0.4% -2.2% -59.2% -60.4% 0.0% Max +0.0% +0.1% +3.3% +4.9% 0.0% Geometric Mean +0.0% -0.0% -33.2% -34.3% -0.0% Test T18282 is an existing example of these deeply-nested strict calls. We get a big decrease in compile time (-85%) because so much less inlining takes place. Metric Decrease: T18282 (cherry picked from commit 0bd60059b0edfee9e8f66c6817257bbb946656cd) - - - - - 6ba13945 by Sergei Trofimovich at 2020-08-13T18:22:40-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> (cherry picked from commit 39c89862161bf488a6aca9372cbb67690f436ce7) - - - - - 59226e20 by Felix Wiemuth at 2020-08-13T18:22:40-04:00 Fix typo (cherry picked from commit b9a880fce484d0a87bb794b9d2d8a73e54819011) - - - - - 9166d4d6 by Simon Peyton Jones at 2020-08-13T18:22:40-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 (cherry picked from commit bbc5191640761ca9773abc898c077363b7beb4e7) - - - - - 505a9d68 by John Ericson at 2020-08-13T18:22:40-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. (cherry picked from commit 6c68a84254d70280e2dc73485f361787a3503850) - - - - - bd365c1d by Simon Peyton Jones at 2020-08-13T18:22:40-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d (cherry picked from commit 9f71f69714255165d0fdc2790a588487ff9439dc) - - - - - 6653e139 by Sylvain Henry at 2020-08-13T18:22:40-04:00 Fix minimal imports dump for boot files (fix #18497) (cherry picked from commit 7c274cd530cc42a26028050b75d56b3437e06ec1) - - - - - 2c86713b by Leon Schoorl at 2020-08-13T18:22:41-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 (cherry picked from commit f2d1accf67cb6e1dab6b2c78fef4b64526c31a4a) - - - - - 36d8cd6f by Niklas Hambüchen at 2020-08-13T18:22:41-04:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. (cherry picked from commit 947206f478d4eef641dfc58cb4c13471a23260c3) - - - - - 01534bf9 by Krzysztof Gogolewski at 2020-08-13T18:22:48-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. (cherry picked from commit 5e12cd1733b581f48a5873b12971b6974778eabb) - - - - - 20a45d0c by Ben Gamari at 2020-08-13T18:22:48-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. (cherry picked from commit 2bff2f87e43985e02bdde8c6fa39279df86cb617) - - - - - 2911d640 by Ben Gamari at 2020-08-13T18:22:48-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. (cherry picked from commit 53ce0db5a06598c88c6b8cb32043b878e7083dd4) - - - - - cb3e202a by Ryan Scott at 2020-08-13T18:22:48-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. (cherry picked from commit fbcb886d503dd7aaebc4c40e59615068b3fd0bd7) - - - - - bd506bd6 by Vladislav Zavialov at 2020-08-13T18:22:48-04:00 Improve NegativeLiterals (#18022, GHC Proposal #344) Before this patch, NegativeLiterals used to parse x-1 as x (-1). This may not be what the user expects, and now it is fixed: x-1 is parsed as (-) x 1. We achieve this by the following requirement: * When lexing a negative literal, it must not be preceded by a 'closing token'. This also applies to unboxed literals, e.g. -1#. See GHC Proposal #229 for the definition of a closing token. A nice consequence of this change is that -XNegativeLiterals becomes a subset of -XLexicalNegation. In other words, enabling both of those extensions has the same effect as enabling -XLexicalNegation alone. (cherry picked from commit aee45d9ea8c6cf4ebad4d5c732748923c7865cbe) - - - - - bc186461 by Takenobu Tani at 2020-08-13T18:22:48-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] (cherry picked from commit 9570c21295a2b4a1d1e40939869124f0b9b9bf91) - - - - - 77653d5c by Ben Gamari at 2020-08-13T18:22:48-04:00 cmm: Clean up Notes a bit (cherry picked from commit 5f03606319f745b10e9918c76a47426b293f0bf9) - - - - - 47de152f by Ben Gamari at 2020-08-13T18:22:48-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. (cherry picked from commit 6402c1240d5bd768b8fe8b4368413932bedbe107) - - - - - e64ac078 by Ben Gamari at 2020-08-13T18:22:48-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. (cherry picked from commit 15b36de030ecdd60897bc7a6a02bdeabd0825be4) - - - - - 24c230ce by Ben Gamari at 2020-08-13T18:22:48-04:00 testsuite: Add test for #18527 (cherry picked from commit 3847ae0ccf67bddf73304a39f5320c3ba285aa48) - - - - - ee2ed876 by Ben Gamari at 2020-08-13T18:22:48-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. (cherry picked from commit dd51d53be42114c105b5ab15fcbdb387526b1c17) - - - - - b4c33250 by Alan Zimmerman at 2020-08-13T18:22:48-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. (cherry picked from commit e4f1b73ad9f292a6bbeb21fee44b0ba1a7f3c33b) - - - - - cb39cfdc by Ben Gamari at 2020-08-13T18:22:48-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. (cherry picked from commit 8a665db6174eaedbbae925c0ccb4c22b3f29bcaf) - - - - - b221b571 by Alex Biehl at 2020-08-13T18:22:48-04:00 Hardcode RTS includes to cope with unregistered builds (cherry picked from commit ef2ae81a394df573510b12b7e11bba0c931249d8) - - - - - c15fb71b by Ben Gamari at 2020-08-13T18:22:48-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". (cherry picked from commit f1088b3f31ceddf918a319c97557fb1f08a9a387) - - - - - 3bda53ad by Ben Gamari at 2020-08-13T20:44:39-04:00 testsuite: Allow baseline commit to be set explicitly (cherry picked from commit bbde6ea0ce80a154735f1302251d073a56606c20) - - - - - ce32390c by Ben Gamari at 2020-08-15T12:19:32-04:00 gitlab-ci: Use MR base commit as performance baseline (cherry picked from commit 4b91e5edf64363eff7d087731c2806464033447c) Metric Decrease: T13056 T18304 T1969 T9233 - - - - - 57fd3ff0 by Ben Gamari at 2020-08-16T12:18:11-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. (cherry picked from commit 2f0bae734e2dc8737fbbb8465de7ded89c1121b6) - - - - - 0af2db18 by Ben Gamari at 2020-08-16T12:18:19-04:00 testsuite: Add test for #18291 (cherry picked from commit 6c7785f8e17a43a2578366134f74fd1989077b73) - - - - - 614ac76d by Ben Gamari at 2020-08-17T15:14:35-04:00 Clean up TBDs in changelog (cherry picked from commit 4f334120c8e9cc4aefcbf11d99f169f648af9fde) - - - - - 1a54d708 by Ben Gamari at 2020-08-17T15:14:35-04:00 Bump bytestring submodule - - - - - 20e19811 by Ben Gamari at 2020-08-17T15:14:35-04:00 Bump binary submodule - - - - - 8c7e8e1c by Ben Gamari at 2020-08-17T20:09:30+00:00 Bump Cabal submodule - - - - - 1f6824a1 by Ben Gamari at 2020-08-21T11:35:00-04:00 Accept spurious performance shift Metric Decrease: T13035 - - - - - 5ccf44c6 by Krzysztof Gogolewski at 2020-08-24T21:35:48-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. (cherry picked from commit 364258e0ad25bc95e69745554f5ca831ce80baf8) - - - - - 29e9d2d1 by Vladislav Zavialov at 2020-08-29T16:54:45+02:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. (cherry picked from commit fddddbf47d6ba2b1b3b6ec89bd40c8fa020e6606) - - - - - bf8bb9e7 by Sylvain Henry at 2020-08-31T13:49:08-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - a3e90763 by Sylvain Henry at 2020-09-01T10:22:24+02:00 Fix documentation and fix "check" bignum backend (#18604) (cherry-picked from 0a3723876c6c79a0a407d50f4baa2818a13f232e) - - - - - d5c3a027 by Sylvain Henry at 2020-09-01T10:22:46+02:00 Bignum: add BigNat compat functions (#18613) (cherry-picked from a8a2568b7b64e5b9fca5b12df7da759de4db39ae) - - - - - a6809cf8 by Ben Gamari at 2020-09-02T15:27:27-04:00 users-guide: A few release notes fixes - - - - - 2dbdb7b9 by GHC GitLab CI at 2020-09-03T19:55:38-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). (cherry picked from commit 34e0fa963f35a77093fc7111a80c557fc6bd614f) - - - - - 4e8f05fa by Ben Gamari at 2020-09-06T15:27:00-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. (cherry picked from commit be2cc0ad2109894d2f576c73e3f037b6b79a6bdc) - - - - - 104b0ccd by Ben Gamari at 2020-09-07T03:18:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - cee137dc by Ben Gamari at 2020-09-07T03:18:32-04:00 gitlab-ci: Use hadrian builds for Window release artifacts - - - - - c2030f00 by Ben Gamari at 2020-09-07T16:16:05-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. (cherry picked from commit aa4b744d51aa6bdb46064f981ea8e001627921d6) - - - - - 6dbd1054 by Sylvain Henry at 2020-09-07T16:20:38-04:00 Remove outdated note - - - - - c23275f4 by Sylvain Henry at 2020-09-07T16:20:38-04:00 Bignum: add missing compat import/export functions - - - - - 214b2b69 by Ben Gamari at 2020-09-07T20:28:21-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) (cherry picked from commit 9374737005c9fa36a870111f100fe27f9a0efd8e) - - - - - b093074e by Ben Gamari at 2020-09-07T20:28:26-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) (cherry picked from commit c10ff55fddf8c6708d679e91f3253dc642b91565) - - - - - 3e55edd9 by Ben Gamari at 2020-09-08T09:46:42-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. (cherry picked from commit 15dca84793d5ec4ff922726477923e40caa075eb) - - - - - 12d9742c by Zubin Duggal at 2020-09-16T14:38:15-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` Backport of !4037 - - - - - 59862b4a by Ben Gamari at 2020-09-17T19:46:29-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory (cherry picked from commit 9c6c1ebc9ab2f18d711a8793c7f0ec36e989d687) - - - - - e8f5e16a by Ryan Scott at 2020-09-17T19:46:29-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. (cherry picked from commit 4f83e9ad76b1e7c67a440ea89f22f6fc03921b5d) - - - - - eae6f239 by Ryan Scott at 2020-09-17T19:46:29-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. (cherry picked from commit 502605f7ae9907a6b0b9823e8f055ae390c57b1d) - - - - - 8dcbbeec by Ben Gamari at 2020-09-17T19:46:29-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. (cherry picked from commit 708e374a8bf108999c11b6cf59c7d27677ed24a8) - - - - - df6d0218 by Ben Gamari at 2020-09-17T19:46:29-04:00 testsuite: Add test for #18118 (cherry picked from commit 2cdb72a569f6049a390626bca0dd6e362045ed65) - - - - - 675c0cce by Ben Gamari at 2020-09-17T19:46:29-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. (cherry picked from commit 77b1ebf6dd34df8068a07865d92301ff298cf5ca) - - - - - 7e315b15 by Ben Gamari at 2020-09-17T19:46:29-04:00 llvm-targets: Add i686 targets Addresses #18422. (cherry picked from commit 12dadd04a09c23c91d7da6f5b17ef78688d93fe7) - - - - - 264afed3 by Krzysztof Gogolewski at 2020-09-17T19:46:29-04:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. (cherry picked from commit 8b86509270227dbc61f0700c7d9261a4c7672361) - - - - - 2c2ed25b by Krzysztof Gogolewski at 2020-09-17T19:46:29-04:00 Move pprTyTcApp' inside pprTyTcApp No semantic change (cherry picked from commit d8f61182c3bdd1b6121c83be632b4941b907de88) - - - - - 8d0a75c6 by Takenobu Tani at 2020-09-17T19:46:29-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. (cherry picked from commit 84ec8daa016d07ae42f0f0f48575dd7d907d5f9d) - - - - - aac5417a by Ben Gamari at 2020-09-17T19:46:29-04:00 configure: Fix whitespace (cherry picked from commit 1213fd87564ab092aa914d8633df4de07fe04905) - - - - - b83682c7 by Ben Gamari at 2020-09-17T19:46:29-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. (cherry picked from commit 566ac68de70e5b580c96e8ab8b3b02ad0f1acd42) - - - - - cb8610b8 by Ben Gamari at 2020-09-17T19:46:29-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. (cherry picked from commit 72036e1c03385aa4f5ed70179ab4b154beed81cb) - - - - - ab244fc9 by Ben Gamari at 2020-09-17T19:46:29-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. (cherry picked from commit 4597752ad3c031e17fe3cceb20c61e4d5b58c52f) - - - - - ad6cef78 by Ben Gamari at 2020-09-17T19:46:29-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. (cherry picked from commit 5b12bb7c98529374ff8e932d0c36104d1a0fe509) - - - - - cc3e00cb by Ben Gamari at 2020-09-17T19:46:29-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. (cherry picked from commit c4fd8947f4104e7b6d6bf3d320a63a361191bde1) - - - - - 702bd58c by Ben Gamari at 2020-09-17T19:46:29-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. (cherry picked from commit c2fefaf37ae134aefc4136bae7e5976f991d76f4) - - - - - 5b0fb69f by Ryan Scott at 2020-09-17T19:46:29-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. (cherry picked from commit 5e883375409efc2336da6295c7d81bd10b542210) - - - - - 7d00408b by Ryan Scott at 2020-09-17T19:46:29-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. (cherry picked from commit bc487caf830ce6cd2c03845b29416c6706185fbc) - - - - - 8edda01f by Krzysztof Gogolewski at 2020-09-17T19:46:29-04:00 Make sure we can read past perf notes See #18656. (cherry picked from commit b8a9cff2ce651c085c84980d3e709db2ecda8c3f) - - - - - af32a4cb by Ben Gamari at 2020-09-17T19:46:29-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. (cherry picked from commit 35ea92708e17c90e476167163ae24747a3f5508e) - - - - - efc41fcc by HaskellMouse at 2020-09-17T19:46:29-04:00 Added explicit fixity to (~). Solves #18252 (cherry picked from commit 3c94c81629ac9159775b8b70baf2c635f0331708) - - - - - 3309d2a2 by Ben Gamari at 2020-09-17T19:46:29-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. (cherry picked from commit a64e94f98ca18e53ecc13f736d50b9cb2d156b05) - - - - - 4e00ee7b by Ben Gamari at 2020-09-17T19:46:29-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts (cherry picked from commit d4bc9f0de7992f60bce403731019829f6248cc2c) - - - - - 4ffa7d40 by Ben Gamari at 2020-09-18T08:31:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. (cherry picked from commit 09b91e8b95eb16fe72aef8405896fd6caf789f61) - - - - - e5f6188b by Zubin Duggal at 2020-09-18T08:32:37-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - d16223fd by Alan Zimmerman at 2020-09-18T08:38:16-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) (cherry picked from commit 701463ec9998c679b03dcc848912a7ce9da9a66a) - - - - - 23f34f7b by Alan Zimmerman at 2020-09-18T08:38:29-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features (cherry picked from commit 0f4d29cac3826392ceb26ea219fce6e8a7505107) - - - - - f91ea170 by Alan Zimmerman at 2020-09-20T19:25:22+01:00 API Annotations: Fix annotation for strictness This adds the correct location for a ! or ~. It is a reconstruction of 3ccc80ee6120db7ead579c6e9fc5c2164f3bf575, some of which got mangled in the backport process. - - - - - fbdc93e7 by Ben Gamari at 2020-09-21T15:27:17-04:00 Bump Win32 submodule - - - - - 17740c20 by Ben Gamari at 2020-09-21T15:27:17-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. (cherry picked from commit a89c2fbab9bcf7d769e9d27262ab29f93342f114) Modified to use happy-1.19 - - - - - d4d44edb by Ben Gamari at 2020-09-22T17:05:52-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). (cherry picked from commit 2f7ef2fb3234cdfb89b3da1298fc9c1b7381e418) - - - - - b1c4116d by Simon Jakobi at 2020-09-24T13:09:09-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. (cherry picked from commit a90d13091ff82e954432bedd0bb20845c666eddb) - - - - - 29fc00bc by Wander Hillen at 2020-09-24T13:11:02-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. (cherry picked from commit e195dae6d959e2a9b1a22a2ca78db5955e1d7dea) - - - - - 7f418acf by Ryan Scott at 2020-09-24T13:14:46-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. (cherry picked from commit 3ea8ac774efd9ee25156f444eacf49893d48a6c9) - - - - - 4c37274a by Ben Gamari at 2020-09-25T17:39:53-04:00 Bump Cabal, haskeline, directory, process submodules To accomodate Win32 2.10.0.0. - - - - - 12957a0b by Ben Gamari at 2020-09-25T17:39:53-04:00 Disable -Wdeprecations for deepseq Use to use of Data.Semigroup.Option for NFData instance. - - - - - 6c98a930 by Sylvain Henry at 2020-09-28T08:37:29+02:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 74f3f581 by Sylvain Henry at 2020-09-28T08:37:29+02:00 Bignum: implement extended GCD (#18427) - - - - - ebcc0968 by Sylvain Henry at 2020-09-28T09:56:49+02:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - edfa896e by Arnaud Spiwack at 2020-09-29T11:41:25-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. (cherry picked from commit 2707c4eae4cf99e6da2709e128f560d91e468357) - - - - - a64ea9d0 by Krzysztof Gogolewski at 2020-09-29T11:41:25-04:00 Disallow linear types in FFI (#18472) (cherry picked from commit 160fba4aa306c0649c72a6dcd7c98d9782a0e74b) - - - - - f8d8c343 by Krzysztof Gogolewski at 2020-09-29T11:41:25-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH (cherry picked from commit 83407ffc7acc00cc025b9f6ed063add9ab9f9bcc) - - - - - 90fe5cff by Krzysztof Gogolewski at 2020-09-29T11:41:25-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. (cherry picked from commit e124f2a7d9a5932a4c2383fd3f9dd772b2059885) - - - - - 93df442a by Krzysztof Gogolewski at 2020-09-30T01:05:27+03:00 Linear types: fix kind inference when checking datacons (cherry picked from b31a3360e2ef12f3ec7eaf66b3600247c1eb36c3) - - - - - 7c7bd94d by Vladislav Zavialov at 2020-09-30T01:06:07+03:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. (cherry-picked from 5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - d5e13ceb by Vladislav Zavialov at 2020-10-02T01:39:25+03:00 Fix pretty-printing of the mult-polymorphic arrow (cherry-picked from a8018c17747342444c67eeec21a506c89c1110e8) - - - - - 89a00150 by Sylvain Henry at 2020-10-05T10:32:31+02:00 Bignum: add integerNegate RULE - - - - - 175d7141 by Sylvain Henry at 2020-10-05T10:32:38+02:00 Bignum: implement integerRecipMod (#18427) - - - - - 5d414fdc by Sylvain Henry at 2020-10-05T10:32:43+02:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - b936c542 by MaxGabriel at 2020-10-12T14:19:41+02:00 Document -Wderiving-typeable Tracking: #18641 (cherry picked from commit 73d2521688bd1da4b6bd1202e5325a00cb410a44) - - - - - c073a4ab by Hécate at 2020-10-12T14:20:47+02:00 Remove the list of loaded modules from the ghci prompt (cherry picked from commit 086ef01813069fad84cafe81cab37527d41c8568) - - - - - aff164bc by Benjamin Maurer at 2020-10-12T14:21:51+02:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. (cherry picked from commit 74c797f6b72c4d01f5e0092dfac1461f3f3dd7a2) - - - - - 44779899 by Krzysztof Gogolewski at 2020-10-12T14:22:35+02:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. (cherry picked from commit e48cab2a57f2342891f985bcb44817e17e985275) - - - - - ba446875 by Krzysztof Gogolewski at 2020-10-12T14:23:25+02:00 Fix linear types in TH splices (#18465) (cherry picked from commit 802b5e6fdd6dfc58396a9dca1903dc5a1d6634ca) - - - - - b10154d6 by Icelandjack at 2020-10-12T14:25:47+02:00 Replaced MkT1 with T1 in type signatures. (cherry picked from commit b81350bb925f8cb309355ee46238dbc11b796faf) - - - - - baa55369 by Krzysztof Gogolewski at 2020-10-12T14:26:12+02:00 Linear types: fix quantification in GADTs (#18790) (cherry picked from commit 22f218b729a751bc5e5965624a716fc542f502a5) - - - - - 146cff70 by Alan Zimmerman at 2020-10-12T14:27:02+02:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 (cherry picked from commit d6dff830754a97220eacf032c32cd54b18654917) - - - - - 8c370e11 by Alan Zimmerman at 2020-10-12T14:27:30+02:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. (cherry picked from commit 36787bba78ae5acbb857c84b85b8feb7c83e54a5) - - - - - 15c4eb1f by Krzysztof Gogolewski at 2020-10-12T14:28:15+02:00 Linear types: fix roles in GADTs (#18799) (cherry picked from commit 8fafb304cacae69f8dbbdcf22ab858a5b28b6818) - - - - - a740aa0b by Sylvain Henry at 2020-10-12T15:10:13+02:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - d09e7e41 by Sylvain Henry at 2020-10-12T15:10:30+02:00 Bignum: fix bigNatCompareWord# bug (#18813) (cherry picked from commit 74ee1237bf243dd7d8b758a53695575c364c3088) - - - - - 7e257575 by Simon Peyton Jones at 2020-10-13T23:35:26+02:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. (cherry picked from commit c7182a5c67fe8b5bd256cb8eb805562636853ea2) - - - - - 9060a9dd by Ben Gamari at 2020-10-13T23:36:56+02:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. (cherry picked from commit 9657f6f34a1a00008a0db935dbf25733cb483cd4) - - - - - fb5eb8ab by Simon Peyton Jones at 2020-10-13T23:37:29+02:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. (cherry picked from commit bfdccac6acce84e15292a454d12f4e0d87ef6f10) - - - - - 64ab97bf by Krzysztof Gogolewski at 2020-10-13T23:39:06+02:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. (cherry picked from commit fd302e938ebf48c73d9f715d67ce8cd990f972ff) - - - - - b1a2c5e4 by Tamar Christina at 2020-10-16T10:21:20-04:00 winio: add release note - - - - - 51b09fe4 by Alan Zimmerman at 2020-10-21T23:53:56-04:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule (cherry picked from commit ea736839d85594c95490dcf02d3325c2bbc68f33) - - - - - 5a2400c6 by Viktor Dukhovni at 2020-10-23T20:51:00-04:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 7644d85c by Moritz Angermann at 2020-10-30T10:59:36-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) (cherry picked from commit 89a753308deb2c7ed012e875e220b1d39e1798d8) Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - 3d7f5ec8 by Alan Zimmerman at 2020-11-01T11:45:02-05:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' (cherry picked from commit c15b5f25ad54164c951e797ecbd10d0df1cf4ba6) - - - - - bba8f79c by Sylvain Henry at 2020-11-09T11:10:17-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. (cherry picked from commit bff74de713dac3e62c3bb6f1946e0649549f2215) - - - - - ed1699b2 by Tamar Christina at 2020-11-09T11:11:52-05:00 winio: Fix unused variables warnings (cherry picked from commit cb1f755c6fb77f140aee11fdc7b4da04dd5dcd02) - - - - - 0736b4e3 by Simon Peyton Jones at 2020-11-09T11:13:57-05:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion (cherry picked from commit 0b3d23afcad8bc14f2ba69b8dbe05c314e6e7b29) - - - - - 6c1cf280 by Tamar Christina at 2020-11-09T11:17:24-05:00 winio: simplify logic remove optimization step. (cherry picked from commit 412018c1214a19649e0ccfff73e80a0622635dd5) - - - - - e49c8923 by David Beacham at 2020-11-09T14:15:13-05:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog (cherry picked from commit 9ad51bc9d2ad9168abad271f715ce73d3562218a) - - - - - fb544de7 by Sylvain Henry at 2020-11-09T14:15:15-05:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a (cherry picked from commit 17d2f0a886f9f56ea408d2dd8b7f054021da19a4) - - - - - fa671e75 by Vladislav Zavialov at 2020-11-09T14:15:15-05:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. (cherry picked from commit bf2411a3c198cb2df93a9e0aa0c3b8297f47058d) - - - - - e5f73b99 by Ben Gamari at 2020-11-09T14:15:15-05:00 Bump win32-tarballs version to 0.3 This should fix #18774. (cherry picked from commit e5c7c9c8578de1248826c21ebd08e475d094a552) - - - - - 063d174f by Ben Gamari at 2020-11-09T14:15:15-05:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. (cherry picked from commit a848d52748c09a27ed5bef0fb039c51656bebdf1) - - - - - da266403 by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fixed bytestring reading interface. (cherry picked from commit 0fd3d360cab977e00fb6d90d0519962227b029bb) - - - - - c4fa35fa by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fixed more data error. (cherry picked from commit dfaef1cae7a4a0cb8783933274dae7f39d7165a0) - - - - - 556c2356 by Tamar Christina at 2020-11-09T14:15:15-05:00 winio: fix array splat (cherry picked from commit 6f0243ae5b359124936a8ff3dd0a287df3d7aca2) - - - - - c3a8c0bf by Tamar Christina at 2020-11-09T14:15:16-05:00 winio: fixed timeouts non-threaded. (cherry picked from commit c832f7e2a9314cfd61257cb161b1795b612d12b5) - - - - - e615aa85 by Andreas Klebinger at 2020-11-09T14:15:16-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) - - - - - 25a24e5d by Alan Zimmerman at 2020-11-09T14:15:16-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 (cherry picked from commit 616bec0dee67ae4841c4e60e9406cc9c63358223) - - - - - 2b3af303 by Ben Gamari at 2020-11-09T14:15:16-05:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. (cherry picked from commit 6434c2e35122886ad28a861cb857fa47bcc7e82d) - - - - - 06e7aed0 by Ben Gamari at 2020-11-09T14:15:16-05:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows (cherry picked from commit d76224c29a78ab962d86b9a1a92cde73e41b6479) - - - - - 918157d5 by Ben Gamari at 2020-11-09T19:17:08-05:00 testsuite: Update output for T18888_datakinds - - - - - 7fcca77f by Ben Gamari at 2020-11-09T19:17:13-05:00 testsuite: Update output for T12427a - - - - - c94c56d5 by Sylvain Henry at 2020-11-10T11:04:03-05:00 Export SPEC from GHC.Exts (#13681) (cherry picked from commit 4c407f6e71f096835f8671e2d3ea6bda38074314) - - - - - d4483f7b by Ben Gamari at 2020-11-14T06:49:57-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. (cherry picked from commit 6d21ecee535782f01dba9947a49e282afee25724) - - - - - 08d75467 by Ben Gamari at 2020-11-24T12:03:00-05:00 SMP.h: Add C11-style atomic operations - - - - - 9f6d3341 by Ben Gamari at 2020-11-24T12:03:00-05:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - 8b5e7dc7 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 67c0f410 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - 829a72cd by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/Task: Make comments proper Notes - - - - - c19ee6d5 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - 5ed8139a by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 3c35c588 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/ClosureMaros: Use relaxed atomics - - - - - 83e759a7 by Ben Gamari at 2020-11-24T12:03:01-05:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - 7d846a79 by Ben Gamari at 2020-11-24T12:03:01-05:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - 37886925 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 5541b8ea by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 12c8702a by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Annotate benign race in waitForCapability - - - - - 3eb46f2e by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Clarify locking behavior of releaseCapability_ - - - - - e052a812 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Add assertions for task ownership of capabilities - - - - - 2b1da3d8 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 053d3c5b by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Mitigate races in capability interruption logic - - - - - 7ebad34c by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - 67716ed3 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 5615aac8 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 677988d5 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 7ce38423 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Eliminate data races on pending_sync - - - - - 05f59c23 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - 6417288c by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Avoid data races in message handling - - - - - dba1771b by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - 1727bc57 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/ThreadPaused: Avoid data races - - - - - 3e36d9ee by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Schedule: Eliminate data races in run queue management - - - - - 7b856fcd by Ben Gamari at 2020-11-24T12:03:03-05:00 rts: Eliminate shutdown data race on task counters - - - - - 04a19bfc by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 1f5dded6 by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/Messages: Annotate benign race - - - - - 852eb2cc by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/RaiseAsync: Synchronize what_next read - - - - - d9b6eb31 by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - 1bcc9cd0 by Ben Gamari at 2020-11-24T12:03:03-05:00 Disable flawed assertion - - - - - 2e76a631 by Ben Gamari at 2020-11-24T12:03:03-05:00 Document schedulePushWork race - - - - - 718a46db by Ben Gamari at 2020-11-24T12:03:03-05:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - 588a950b by Ben Gamari at 2020-11-24T12:03:03-05:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 853ef5e1 by Ben Gamari at 2020-11-24T12:03:03-05:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 5bcda8ba by GHC GitLab CI at 2020-11-24T12:03:03-05:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - e78d90e3 by GHC GitLab CI at 2020-11-24T12:03:03-05:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - a99f05ef by Ben Gamari at 2020-11-24T12:03:03-05:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - 02d2e42b by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - fba38edf by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 0215ff52 by Ben Gamari at 2020-11-24T12:03:04-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - e191eb78 by Ben Gamari at 2020-11-24T12:03:04-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - a31bccca by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - 7aba9e54 by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 23a30a3b by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/BlockAlloc: Use relaxed operations - - - - - 4139b672 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - 33b7b375 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 725dfd75 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Storage: Use atomics - - - - - 240bb1b4 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Updates: Use proper atomic operations - - - - - b7b0f3ae by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - 20787589 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/GC: Use atomics - - - - - b15db127 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - 49c8049e by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Storage: Accept races on heap size counters - - - - - 89864d46 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - 31669bd3 by GHC GitLab CI at 2020-11-24T12:03:04-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 7e968942 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - acef7fd3 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Use relaxed ordering on spinlock counters - - - - - 53920304 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 0ca2beeb by Ben Gamari at 2020-11-24T12:03:05-05:00 Strengthen ordering in releaseGCThreads - - - - - 7d3d0f13 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - c29b1a83 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 55b252f2 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - d9e82a56 by GHC GitLab CI at 2020-11-24T12:03:05-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - d9ed5a62 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 219f6496 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - cf99c5e5 by Ben Gamari at 2020-11-24T12:03:05-05:00 Mitigate data races in event manager startup/shutdown - - - - - d7655654 by Ben Gamari at 2020-11-24T12:03:05-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - 389c92df by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Accept benign races in Proftimer - - - - - b4ced846 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 9116b39a by Ben Gamari at 2020-11-24T12:03:05-05:00 Fix #17289 - - - - - 75b8c066 by Ben Gamari at 2020-11-24T12:03:05-05:00 suppress #17289 (ticker) race - - - - - dcea5aef by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - 16d3ea21 by Ben Gamari at 2020-11-24T12:03:06-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - da69341b by Ben Gamari at 2020-11-24T12:03:06-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - f65a5c9e by Ben Gamari at 2020-11-24T12:03:06-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 543ad4f3 by Ben Gamari at 2020-11-24T12:03:06-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/test-metrics.sh - CODEOWNERS - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Utils.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Cond.hs - compiler/GHC/Core/Class.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/OccurAnal.hs - compiler/GHC/Core/Opt/Driver.hs → compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Env.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2288ddd4f953c1c692f523b5418ac0ce59cf43d0...543ad4f3f8320c17be0029078a1cbe832f5b6f56 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2288ddd4f953c1c692f523b5418ac0ce59cf43d0...543ad4f3f8320c17be0029078a1cbe832f5b6f56 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 Tue Nov 24 17:06:50 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 12:06:50 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-8.10] 100 commits: [macOS] improved runpath handling Message-ID: <5fbd3daa22447_36a71172f34c942158@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: 43f97049 by Moritz Angermann at 2020-10-14T13:51:31-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) (cherry picked from commit 4ff93292243888545da452ea4d4c1987f2343591) Signed-off-by: Moritz Angermann <moritz.angermann at iohk.io> - - - - - da1b5345 by Ben Gamari at 2020-10-16T01:10:54+02:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. (cherry picked from commit 708e374a8bf108999c11b6cf59c7d27677ed24a8) - - - - - f3bc882d by Ben Gamari at 2020-10-16T01:13:02+02:00 testsuite: Add test for #18118 (cherry picked from commit 2cdb72a569f6049a390626bca0dd6e362045ed65) Conflicts: testsuite/tests/typecheck/should_compile/all.T - - - - - 7e6c6340 by Moritz Angermann at 2020-10-16T01:14:57+02:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 (cherry picked from commit 6189cc04ca6c3d79126744e988b487f75ccef9e2) - - - - - 1ac0a2aa by Ben Gamari at 2020-10-16T01:16:06+02:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. (cherry picked from commit ea1cbb8f2ac9e077ed19530911c3a35c5f46ee8a) - - - - - 1fdadd41 by Ben Gamari at 2020-10-16T01:16:38+02:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. (cherry picked from commit ce42e187ebfc81174ed477f247f023ae094c9b24) - - - - - ec6b31f0 by Ben Gamari at 2020-10-16T01:17:08+02:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. (cherry picked from commit 0799b3de3e3462224bddc0e4b6a3156d04a06361) - - - - - 7367ae91 by Ben Gamari at 2020-10-16T01:17:33+02:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. (cherry picked from commit 057db94ce038970b14df1599fe83097c284b9c1f) - - - - - 5b5dde18 by Benjamin Maurer at 2020-10-16T01:19:50+02:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. (cherry picked from commit 74c797f6b72c4d01f5e0092dfac1461f3f3dd7a2) - - - - - 8cb4fe24 by Krzysztof Gogolewski at 2020-10-16T01:20:55+02:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. (cherry picked from commit 587c3c514f05f97082952d613695f1186ff3174e) - - - - - 5a4d0c3d by Krzysztof Gogolewski at 2020-10-16T01:21:41+02:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. (cherry picked from commit fd302e938ebf48c73d9f715d67ce8cd990f972ff) - - - - - 658362c6 by Tamar Christina at 2020-10-19T23:16:22-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. (cherry picked from commit fd984d68e5ec4b04bc79395c099434e653eb1060) - - - - - f60607cf by Ben Gamari at 2020-10-21T22:01:58-04:00 rts: Add __mingw_vsnwprintf to RtsSymbols - - - - - 929e09ed by toonn at 2020-10-22T22:12:43-04:00 Fix typos in 8.10.2 changelog Replace an "as well" missing "as" with "and" in 4.1 Highlights. Add missing apostrophe in "user's guide", insert space in "work around" and dash in "cost-center" in 4.2.2 Runtime system. - - - - - cc085aef by Ben Gamari at 2020-10-31T22:31:33-04:00 Bump Cabal submodule to 3.2.1.0 - - - - - f96d6cd7 by Ben Gamari at 2020-11-14T06:47:14-05:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. (cherry picked from commit ee5dcdf95a7c408e9c339aacebf89a007a735f8f) - - - - - 36c1027d by Ben Gamari at 2020-11-14T06:47:14-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. (cherry picked from commit 6d21ecee535782f01dba9947a49e282afee25724) - - - - - 410b43a2 by Andreas Klebinger at 2020-11-18T16:22:35-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. (cherry picked from commit bb100805337adc666867da300ee5b0b11c18fe00) (cherry picked from commit fda3e50b559f6f25347f9ad7239e5003e27937b0) - - - - - ed57c3a9 by Ben Gamari at 2020-11-18T21:39:41-05:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. (cherry picked from commit c492134912e5270180881b7345ee86dc32756bdd) - - - - - 65be3832 by Ben Gamari at 2020-11-18T21:39:53-05:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. (cherry picked from commit 40dc91069d15bfc1d81f1722b39e06cac8fdddd1) - - - - - 3571cc41 by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 macOS: Load frameworks without stating them first. macOS Big Sur makes the following change to how frameworks are shipped with the OS: > New in macOS Big Sur 11 beta, the system ships with a built-in > dynamic linker cache of all system-provided libraries. As part of > this change, copies of dynamic libraries are no longer present on > the filesystem. Code that attempts to check for dynamic library > presence by looking for a file at a path or enumerating a directory > will fail. Instead, check for library presence by attempting to > dlopen() the path, which will correctly check for the library in the > cache. (62986286) https://developer.apple.com/documentation/macos-release-notes/macos-big-sur-11-beta-release-notes/ Therefore, the previous method of checking whether a library exists before attempting to load it makes GHC.Runtime.Linker.loadFramework fail to find frameworks installed at /System/Library/Frameworks. GHC.Runtime.Linker.loadFramework now opportunistically loads the framework libraries without checking for their existence first, failing only if all attempts to load a given framework from any of the various possible locations fail. - - - - - 57b5f130 by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 loadFramework: Output the errors collected in all loading attempts. With the recent change away from first finding and then loading a framework, loadFramework had no way of communicating the real reason why loadDLL failed if it was any reason other than the framework missing from the file system. It now collects all loading attempt errors into a list and concatenates them into a string to return to the caller. - - - - - 07c5acae by Matthias Andreas Benkard at 2020-11-19T15:36:22-05:00 Document loadFramework changes. (#18446) Adds commentary on the rationale for the changes made in merge request !3689. - - - - - d84ae4d7 by Ben Gamari at 2020-11-24T12:05:59-05:00 SMP.h: Add C11-style atomic operations - - - - - d3c57867 by Ben Gamari at 2020-11-24T12:05:59-05:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - 623090ff by Ben Gamari at 2020-11-24T12:05:59-05:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - e2b937de by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - 9b5e63e8 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Task: Make comments proper Notes - - - - - b151680d by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - 1be2beab by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 9cef76a2 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/ClosureMaros: Use relaxed atomics - - - - - 62df95f5 by Ben Gamari at 2020-11-24T12:06:00-05:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - 8b544487 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 17b82ff6 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - f30971d6 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Annotate benign race in waitForCapability - - - - - 2a70c253 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 9047b483 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Add assertions for task ownership of capabilities - - - - - ca946de2 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 3336b9ad by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Mitigate races in capability interruption logic - - - - - 5e7cf74f by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - b6baf633 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - ad72d7a7 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Schedule: Use relaxed operations for sched_state - - - - - ac23a4b1 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 0f992176 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Eliminate data races on pending_sync - - - - - 968e57e8 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - f57d054c by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Avoid data races in message handling - - - - - c087685e by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - 406fb545 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/ThreadPaused: Avoid data races - - - - - 2f24325d by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Schedule: Eliminate data races in run queue management - - - - - d2dad2eb by Ben Gamari at 2020-11-24T12:06:00-05:00 rts: Eliminate shutdown data race on task counters - - - - - bee14332 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - df937d52 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Messages: Annotate benign race - - - - - d91a6199 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/RaiseAsync: Synchronize what_next read - - - - - 39b37c11 by Ben Gamari at 2020-11-24T12:06:00-05:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - 22876a69 by Ben Gamari at 2020-11-24T12:06:00-05:00 Disable flawed assertion - - - - - d83f867e by Ben Gamari at 2020-11-24T12:06:00-05:00 Document schedulePushWork race - - - - - c02ed4be by Ben Gamari at 2020-11-24T12:06:01-05:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - cdb3e4d1 by Ben Gamari at 2020-11-24T12:06:01-05:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 54ec6dd6 by Ben Gamari at 2020-11-24T12:06:01-05:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 16574964 by GHC GitLab CI at 2020-11-24T12:06:01-05:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - 08f636bc by GHC GitLab CI at 2020-11-24T12:06:01-05:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - c6195ca1 by Ben Gamari at 2020-11-24T12:06:01-05:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - 6f8204c9 by Ben Gamari at 2020-11-24T12:06:01-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - 3f64dc6d by Ben Gamari at 2020-11-24T12:06:01-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 75cf9779 by Ben Gamari at 2020-11-24T12:06:01-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 0616ef30 by Ben Gamari at 2020-11-24T12:06:01-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 1a72b5b7 by Ben Gamari at 2020-11-24T12:06:01-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - b78d9e19 by Ben Gamari at 2020-11-24T12:06:33-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 454fc268 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/BlockAlloc: Use relaxed operations - - - - - 5b5f95cd by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - a491b2bd by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 9385616f by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/Storage: Use atomics - - - - - bea6352f by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/Updates: Use proper atomic operations - - - - - b61d42f1 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - e6fb1a23 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/GC: Use atomics - - - - - a9612385 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - 3dd8d329 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/Storage: Accept races on heap size counters - - - - - 78c415cb by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - bf7f5836 by GHC GitLab CI at 2020-11-24T12:06:39-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - fe2f4f8e by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - b3094027 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Use relaxed ordering on spinlock counters - - - - - 8ed2b04b by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 03c0358e by Ben Gamari at 2020-11-24T12:06:39-05:00 Strengthen ordering in releaseGCThreads - - - - - 859ae214 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d9b2e381 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 43e44655 by Ben Gamari at 2020-11-24T12:06:39-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - 90ed4082 by GHC GitLab CI at 2020-11-24T12:06:40-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - e355d4ab by Ben Gamari at 2020-11-24T12:06:40-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 190fc07d by Ben Gamari at 2020-11-24T12:06:40-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - ca323a84 by Ben Gamari at 2020-11-24T12:06:40-05:00 Mitigate data races in event manager startup/shutdown - - - - - 111a1dc0 by Ben Gamari at 2020-11-24T12:06:40-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - d2067aed by Ben Gamari at 2020-11-24T12:06:40-05:00 rts: Accept benign races in Proftimer - - - - - 8082c3e8 by Ben Gamari at 2020-11-24T12:06:40-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 533ac721 by Ben Gamari at 2020-11-24T12:06:40-05:00 Fix #17289 - - - - - 0c90b600 by Ben Gamari at 2020-11-24T12:06:40-05:00 suppress #17289 (ticker) race - - - - - 952b9069 by Ben Gamari at 2020-11-24T12:06:40-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - c7979d7e by Ben Gamari at 2020-11-24T12:06:40-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 220bb050 by Ben Gamari at 2020-11-24T12:06:40-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 7b7d68bb by Ben Gamari at 2020-11-24T12:06:40-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 0b4a532a by Ben Gamari at 2020-11-24T12:06:40-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/deSugar/DsForeign.hs - compiler/ghci/Linker.hs - compiler/main/DriverPipeline.hs - compiler/main/DynFlags.hs - compiler/main/Settings.hs - compiler/main/SysTools.hs - compiler/main/SysTools/Settings.hs - compiler/main/SysTools/Tasks.hs - compiler/main/ToolSettings.hs - compiler/nativeGen/X86/CodeGen.hs - compiler/nativeGen/X86/Cond.hs - compiler/nativeGen/X86/Instr.hs - compiler/typecheck/TcSigs.hs - configure.ac - docs/users_guide/8.10.2-notes.rst - docs/users_guide/phases.rst - hadrian/cfg/system.config.in - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Oracles/Setting.hs - hadrian/src/Rules/Generate.hs - hadrian/src/Settings.hs - + hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/Rts.h - includes/ghc.mk - + includes/rts/ForeignExports.h - includes/rts/OSThreads.h - includes/rts/SpinLock.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f619ea8faae670bd2afb5545ad8b4a004eced3c7...0b4a532a1ce8a02afa5f9eb3672ca86f0ea36c6f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f619ea8faae670bd2afb5545ad8b4a004eced3c7...0b4a532a1ce8a02afa5f9eb3672ca86f0ea36c6f 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 Tue Nov 24 17:11:24 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 12:11:24 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] Fix and enable object unloading in GHCi Message-ID: <5fbd3ebc5cb20_36a73fd2f1fdd7f89430d0@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 67a1c9c1 by Ömer Sinan Ağacan at 2020-11-24T12:11:10-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 25 changed files: - compiler/ghci/Linker.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/linker_error.c Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1134,14 +1134,15 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do where unloadObjs :: Linkable -> IO () unloadObjs lnk + -- The RTS's PEi386 linker currently doesn't support unloading. + | isWindowsHost = return () + | dynamicGhc = return () -- We don't do any cleanup when linking objects with the -- dynamic linker. Doing so introduces extra complexity for -- not much benefit. - -- Code unloading currently disabled due to instability. - -- See #16841. - | False -- otherwise + | otherwise = mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk] -- The components of a BCO linkable may contain -- dot-o files. Which is very confusing. @@ -1149,7 +1150,6 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do -- But the BCO parts can be unlinked just by -- letting go of them (plus of course depopulating -- the symbol table which is done in the main body) - | otherwise = return () -- see #16841 {- ********************************************************************** ===================================== rts/CheckUnload.c ===================================== @@ -17,43 +17,99 @@ #include "CheckUnload.h" #include "sm/Storage.h" #include "sm/GCThread.h" +#include "sm/HeapUtils.h" // -// Code that we unload may be referenced from: -// - info pointers in heap objects and stack frames -// - pointers to static objects from the heap -// - StablePtrs to static objects -// - pointers to cost centres from the cost centre tree +// Note [Object unloading] +// ~~~~~~~~~~~~~~~~~~~~~~~ // -// We can find live static objects after a major GC, so we don't have -// to look at every closure pointer in the heap. However, we do have -// to look at every info pointer. So this is like a heap census -// traversal: we look at the header of every object, but not its -// contents. +// Overview of object unloading: // -// On the assumption that there aren't many different info pointers in -// a typical heap, we insert addresses into a hash table. The -// first time we see an address, we check it against the pending -// unloadable objects and if it lies within any of them, we mark that -// object as referenced so that it won't get unloaded in this round. +// - In a major GC, for every static object we mark the object's object code and +// its dependencies as 'live'. This is done by `markObjectCode`, called by +// `evacuate`. // - -// Note [Speeding up checkUnload] -// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -// In certain circumstances, there may be a lot of unloaded ObjectCode structs -// chained in `unloaded_objects` (such as when users `:load` a module in a very -// big repo in GHCi). To speed up checking whether an address lies within any of -// these objects, we populate the addresses of their mapped sections in -// an array sorted by their `start` address and do binary search for our address -// on that array. Note that this works because the sections are mapped to mutual -// exclusive memory regions, so we can simply find the largest lower bound among -// the `start` addresses of the sections and then check if our address is inside -// that section. In particular, we store the start address and end address of -// each mapped section in a OCSectionIndex, arrange them all on a contiguous -// memory range and then sort by start address. We then put this array in an -// OCSectionIndices struct to be passed into `checkAddress` to do binary search -// on. +// - Marking object code is done using a global "section index table" +// (global_s_indices below). When we load an object code we add its section +// indices to the table. `markObjectCode` does binary search on this table to +// find object code for the marked object, and mark it and its dependencies. +// +// Dependency of an object code is simply other object code that the object +// code refers to in its code. We know these dependencies by the relocations +// present in the referent. This is recorded by lookupSymbolDependent. +// +// - global_s_indices is updated as we load and unload objects. When we load an +// object code we add its section indices to the table, we remove those +// indices when we unload. +// +// The table is sorted and old indices are removed in `checkUnload`, instead +// on every load/unload, to avoid quadratic behavior when we load a list of +// objects. +// +// - After a major GC `checkUnload` unloads objects that are (1) explicitly +// asked for unloading (via `unloadObj`) and (2) are not marked during GC. +// +// Note that, crucially, we don't unload an object code even if it's not +// reachable from the heap, unless it's explicitly asked for unloading (via +// `unloadObj`). This is a feature and not a but! Two use cases: +// +// - The user might request a symbol from a loaded object at any point with +// lookupSymbol (e.g. GHCi might do this). +// +// - Sometimes we load objects that are not Haskell objects. +// +// To avoid unloading objects that are unreachable but are not asked for +// unloading we maintain a "root set" of object code, `loaded_objects` below. +// `loadObj` adds the loaded objects (and its dependencies) to the list. +// `unloadObj` removes. After a major GC, `checkUnload` first marks the root set +// (`loaded_objects`) to avoid unloading objects that are not asked for +// unloading. +// +// Two other lists `objects` and `old_objects` are similar to large object lists +// in GC. Before a major GC we move `objects` to `old_objects`, and move marked +// objects back to `objects` during evacuation and when marking roots in +// `checkUnload`. Any objects in `old_objects` after that is unloaded. +// +// TODO: We currently don't unload objects when non-moving GC is enabled. The +// implementation would be similar to `nonmovingGcCafs`: +// +// - Maintain a "snapshot": +// +// - Copy `loaded_objects` as the root set of the snapshot +// +// - Stash `objects` to `old_objects` as the snapshot. We don't need a new +// list for this as `old_objects` won't be used by any other code when +// non-moving GC is enabled. +// +// - Copy `global_s_indices` table to be able to mark objects while mutators +// call `loadObj_` and `unloadObj_` concurrently. +// +// - Don't mark object code in `evacuate`, marking will be done in the +// non-moving collector. // +// - After preparation, bump the object code mark bit (`object_code_mark_bit` +// below) and mark static objects using a version of `markObjectCode` that +// basically does the same thing but: +// +// - Needs to update `objects` list in a thread-safe way, as mutators will be +// concurrently calling `loadObj_` and add new stuff to `objects`. +// (alternatively we could have a new list for non-moving GC's objects list, +// and then merge it to the global list in the pause before moving to +// concurrent sweep phase) +// +// - Needs to use the copied `global_s_indices` +// +// - After marking anything left in `old_objects` are unreachable objects within +// the snapshot, unload those. The unload loop will be the same as in +// `checkUnload`. This step needs to happen in the final sync (before sweep +// begins) to avoid races when updating `global_s_indices`. +// +// - NOTE: We don't need write barriers in loadObj/unloadObj as we don't +// introduce a dependency from an already-loaded object to a newly loaded +// object and we don't delete existing dependencies. +// + +uint8_t object_code_mark_bit = 0; typedef struct { W_ start; @@ -62,20 +118,85 @@ typedef struct { } OCSectionIndex; typedef struct { + int capacity; // Doubled on resize int n_sections; + bool sorted; // Invalidated on insertion. Sorted in checkUnload. + bool unloaded; // Whether we removed anything from the table in + // removeOCSectionIndices. If this is set we "compact" the + // table (remove unused entries) in `sortOCSectionIndices. OCSectionIndex *indices; } OCSectionIndices; -static OCSectionIndices *createOCSectionIndices(int n_sections) +// List of currently live objects. Moved to `old_objects` before unload check. +// Marked objects moved back to this list in `markObjectLive`. Remaining objects +// are freed at the end of `checkUnload`. +// +// Double-linked list to be able to remove marked objects. List formed with +// `next` and `prev` fields of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *objects = NULL; + +// `objects` list is moved here before unload check. Marked objects are moved +// back to `objects`. Remaining objects are freed. +static ObjectCode *old_objects = NULL; + +// Number of objects that we want to unload. When this value is 0 we skip static +// object marking during GC and `checkUnload`. +// +// Not static: we use this value to skip static object marking in evacuate when +// this is 0. +// +// Incremented in `unloadObj_`, decremented as we unload objects in +// `checkUnload`. +int n_unloaded_objects = 0; + +// List of objects that we don't want to unload (i.e. we haven't called +// unloadObj on these yet). Used as root set for unload check in checkUnload. +// Objects are added with loadObj_ and removed with unloadObj_. +// +// List formed with `next_loaded_object` field of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *loaded_objects; + +// Section index table for currently loaded objects. New indices are added by +// `loadObj_`, indices of unloaded objects are removed in `checkUnload`. Used to +// map static closures to their ObjectCode. +static OCSectionIndices *global_s_indices = NULL; + +static OCSectionIndices *createOCSectionIndices(void) { - OCSectionIndices *s_indices; - s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); - s_indices->n_sections = n_sections; - s_indices->indices = stgMallocBytes(n_sections*sizeof(OCSectionIndex), + // TODO (osa): Maybe initialize as empty (without allocation) and allocate + // on first insertion? + OCSectionIndices *s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); + int capacity = 1024; + s_indices->capacity = capacity; + s_indices->n_sections = 0; + s_indices->sorted = true; + s_indices->unloaded = false; + s_indices->indices = stgMallocBytes(capacity * sizeof(OCSectionIndex), "OCSectionIndices::indices"); return s_indices; } +static void freeOCSectionIndices(OCSectionIndices *s_indices) +{ + free(s_indices->indices); + free(s_indices); +} + +void initUnloadCheck() +{ + global_s_indices = createOCSectionIndices(); +} + +void exitUnloadCheck() +{ + freeOCSectionIndices(global_s_indices); + global_s_indices = NULL; +} + static int cmpSectionIndex(const void* indexa, const void *indexb) { W_ s1 = ((OCSectionIndex*)indexa)->start; @@ -88,44 +209,124 @@ static int cmpSectionIndex(const void* indexa, const void *indexb) return 0; } -static OCSectionIndices* buildOCSectionIndices(ObjectCode *ocs) +static void reserveOCSectionIndices(OCSectionIndices *s_indices, int len) { - int cnt_sections = 0; - ObjectCode *oc; - for (oc = ocs; oc; oc = oc->next) { - cnt_sections += oc->n_sections; + int current_capacity = s_indices->capacity; + int current_len = s_indices->n_sections; + if (current_capacity - current_len >= len) { + return; + } + + // Round up to nearest power of 2 + int new_capacity = 1 << (int)ceil(log2(current_len + len)); + + OCSectionIndex *old_indices = s_indices->indices; + OCSectionIndex *new_indices = stgMallocBytes(new_capacity * sizeof(OCSectionIndex), + "reserveOCSectionIndices"); + + for (int i = 0; i < current_len; ++i) { + new_indices[i] = old_indices[i]; } - OCSectionIndices* s_indices = createOCSectionIndices(cnt_sections); - int s_i = 0, i; - for (oc = ocs; oc; oc = oc->next) { - for (i = 0; i < oc->n_sections; i++) { - if (oc->sections[i].kind != SECTIONKIND_OTHER) { - s_indices->indices[s_i].start = (W_)oc->sections[i].start; - s_indices->indices[s_i].end = (W_)oc->sections[i].start - + oc->sections[i].size; - s_indices->indices[s_i].oc = oc; - s_i++; + + s_indices->capacity = new_capacity; + s_indices->indices = new_indices; + + free(old_indices); +} + +// Insert object section indices of a single ObjectCode. Invalidates 'sorted' +// state. +void insertOCSectionIndices(ObjectCode *oc) +{ + reserveOCSectionIndices(global_s_indices, oc->n_sections); + global_s_indices->sorted = false; + + int s_i = global_s_indices->n_sections; + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + global_s_indices->indices[s_i].start = (W_)oc->sections[i].start; + global_s_indices->indices[s_i].end = (W_)oc->sections[i].start + + oc->sections[i].size; + global_s_indices->indices[s_i].oc = oc; + s_i++; + } + } + + global_s_indices->n_sections = s_i; + + // Add object to 'objects' list + if (objects != NULL) { + objects->prev = oc; + } + oc->next = objects; + objects = oc; +} + +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr); + +static void removeOCSectionIndices(OCSectionIndices *s_indices, ObjectCode *oc) +{ + // To avoid quadratic behavior in checkUnload we set `oc` fields of indices + // of unloaded objects NULL here. Removing unused entries is done in + // `sortOCSectionIndices`. + + s_indices->unloaded = true; + + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + int section_idx = findSectionIdx(s_indices, oc->sections[i].start); + if (section_idx != -1) { + s_indices->indices[section_idx].oc = NULL; } } } - s_indices->n_sections = s_i; +} + +static void sortOCSectionIndices(OCSectionIndices *s_indices) { + if (s_indices->sorted) { + return; + } + qsort(s_indices->indices, s_indices->n_sections, sizeof(OCSectionIndex), cmpSectionIndex); - return s_indices; + + s_indices->sorted = true; } -static void freeOCSectionIndices(OCSectionIndices *section_indices) -{ - free(section_indices->indices); - free(section_indices); +static void removeRemovedOCSections(OCSectionIndices *s_indices) { + if (!s_indices->unloaded) { + return; + } + + int next_free_idx = 0; + for (int i = 0; i < s_indices->n_sections; ++i) { + if (s_indices->indices[i].oc == NULL) { + // free entry, skip + } else if (i == next_free_idx) { + ++next_free_idx; + } else { + s_indices->indices[next_free_idx] = s_indices->indices[i]; + ++next_free_idx; + } + } + + s_indices->n_sections = next_free_idx; + s_indices->unloaded = true; } -static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { +// Returns -1 if not found +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr) { + ASSERT(s_indices->sorted); + W_ w_addr = (W_)addr; - if (s_indices->n_sections <= 0) return NULL; - if (w_addr < s_indices->indices[0].start) return NULL; + if (s_indices->n_sections <= 0) { + return -1; + } + if (w_addr < s_indices->indices[0].start) { + return -1; + } int left = 0, right = s_indices->n_sections; while (left + 1 < right) { @@ -139,330 +340,125 @@ static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { } ASSERT(w_addr >= s_indices->indices[left].start); if (w_addr < s_indices->indices[left].end) { - return s_indices->indices[left].oc; + return left; } - return NULL; + return -1; } -static void checkAddress (HashTable *addrs, const void *addr, - OCSectionIndices *s_indices) -{ - ObjectCode *oc; - - if (!lookupHashTable(addrs, (W_)addr)) { - insertHashTable(addrs, (W_)addr, addr); +static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { + int oc_idx = findSectionIdx(s_indices, addr); - oc = findOC(s_indices, addr); - if (oc != NULL) { - oc->referenced = 1; - return; - } + if (oc_idx == -1) { + return NULL; } + + return s_indices->indices[oc_idx].oc; } -static void searchStackChunk (HashTable *addrs, StgPtr sp, StgPtr stack_end, - OCSectionIndices *s_indices) -{ - StgPtr p; - const StgRetInfoTable *info; +static bool markObjectLive(void *data STG_UNUSED, StgWord key, const void *value STG_UNUSED) { + ObjectCode *oc = (ObjectCode*)key; + if (oc->mark == object_code_mark_bit) { + return true; // for hash table iteration + } + + oc->mark = object_code_mark_bit; + // Remove from 'old_objects' list + if (oc->prev != NULL) { + // TODO(osa): Maybe 'prev' should be a pointer to the referencing + // *field* ? (instead of referencing *object*) + oc->prev->next = oc->next; + } else { + old_objects = oc->next; + } + if (oc->next != NULL) { + oc->next->prev = oc->prev; + } - p = sp; - while (p < stack_end) { - info = get_ret_itbl((StgClosure *)p); + // Add it to 'objects' list + oc->prev = NULL; + oc->next = objects; + if (objects != NULL) { + objects->prev = oc; + } + objects = oc; - switch (info->i.type) { - case RET_SMALL: - case RET_BIG: - checkAddress(addrs, (const void*)info, s_indices); - break; + // Mark its dependencies + iterHashTable(oc->dependencies, NULL, markObjectLive); - default: - break; - } + return true; // for hash table iteration +} + +void markObjectCode(const void *addr) +{ + if (global_s_indices == NULL) { + return; + } - p += stack_frame_sizeW((StgClosure*)p); + // This should be checked at the call site + ASSERT(!HEAP_ALLOCED(addr)); + + ObjectCode *oc = findOC(global_s_indices, addr); + if (oc != NULL) { + // Mark the object code and its dependencies + markObjectLive(NULL, (W_)oc, NULL); } } - -static void searchHeapBlocks (HashTable *addrs, bdescr *bd, - OCSectionIndices *s_indices) +// Returns whether or not the GC that follows needs to mark code for potential +// unloading. +bool prepareUnloadCheck() { - StgPtr p; - const StgInfoTable *info; - uint32_t size; - bool prim; + if (global_s_indices == NULL) { + return false; + } - for (; bd != NULL; bd = bd->link) { + removeRemovedOCSections(global_s_indices); + sortOCSectionIndices(global_s_indices); - if (bd->flags & BF_PINNED) { - // Assume that objects in PINNED blocks cannot refer to - continue; - } + ASSERT(old_objects == NULL); - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); - prim = false; - - switch (info->type) { - - case THUNK: - size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case FUN: - case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR: - case CONSTR_NOCAF: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case BLACKHOLE: - case BLOCKING_QUEUE: - prim = true; - size = sizeW_fromITBL(info); - break; - - case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. - prim = true; - size = BLACKHOLE_sizeW(); - break; - - case BCO: - prim = true; - size = bco_sizeW((StgBCO *)p); - break; - - case MVAR_CLEAN: - case MVAR_DIRTY: - case TVAR: - case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = true; - size = sizeW_fromITBL(info); - break; - - case AP: - prim = true; - size = ap_sizeW((StgAP *)p); - break; - - case PAP: - prim = true; - size = pap_sizeW((StgPAP *)p); - break; - - case AP_STACK: - { - StgAP_STACK *ap = (StgAP_STACK *)p; - prim = true; - size = ap_stack_sizeW(ap); - searchStackChunk(addrs, (StgPtr)ap->payload, - (StgPtr)ap->payload + ap->size, s_indices); - break; - } + object_code_mark_bit = ~object_code_mark_bit; + old_objects = objects; + objects = NULL; + return true; +} - case ARR_WORDS: - prim = true; - size = arr_words_sizeW((StgArrBytes*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN_CLEAN: - case MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = true; - size = sizeofW(StgTSO); - break; - - case STACK: { - StgStack *stack = (StgStack*)p; - prim = true; - searchStackChunk(addrs, stack->sp, - stack->stack + stack->stack_size, s_indices); - size = stack_sizeW(stack); - break; - } +void checkUnload() +{ + if (global_s_indices == NULL) { + return; + } - case TREC_CHUNK: - prim = true; - size = sizeofW(StgTRecChunk); - break; + // At this point we've marked all dynamically loaded static objects + // (including their dependencies) during GC, but not the root set of object + // code (loaded_objects). Mark the roots first, then unload any unmarked + // objects. - default: - barf("searchHeapBlocks, unknown object: %d", info->type); - } + OCSectionIndices *s_indices = global_s_indices; + ASSERT(s_indices->sorted); - if (!prim) { - checkAddress(addrs,info, s_indices); - } - - p += size; - } + // Mark roots + for (ObjectCode *oc = loaded_objects; oc != NULL; oc = oc->next_loaded_object) { + markObjectLive(NULL, (W_)oc, NULL); } -} -#if defined(PROFILING) -// -// Do not unload the object if the CCS tree refers to a CCS or CC which -// originates in the object. -// -static void searchCostCentres (HashTable *addrs, CostCentreStack *ccs, - OCSectionIndices* s_indices) -{ - IndexTable *i; + // Free unmarked objects + ObjectCode *next = NULL; + for (ObjectCode *oc = old_objects; oc != NULL; oc = next) { + next = oc->next; - checkAddress(addrs, ccs, s_indices); - checkAddress(addrs, ccs->cc, s_indices); - for (i = ccs->indexTable; i != NULL; i = i->next) { - if (!i->back_edge) { - searchCostCentres(addrs, i->ccs, s_indices); - } + removeOCSectionIndices(s_indices, oc); + + // Symbols should be removed by unloadObj_. + // NB (osa): If this assertion doesn't hold then freeObjectCode below + // will corrupt symhash as keys of that table live in ObjectCodes. If + // you see a segfault in a hash table operation in linker (in non-debug + // RTS) then it's probably becuse this assertion did not hold. + ASSERT(oc->symbols == NULL); + + freeObjectCode(oc); + n_unloaded_objects -= 1; } -} -#endif -// -// Check whether we can unload any object code. This is called at the -// appropriate point during a GC, where all the heap data is nice and -// packed together and we have a linked list of the static objects. -// -// The check involves a complete heap traversal, but you only pay for -// this (a) when you have called unloadObj(), and (b) at a major GC, -// which is much more expensive than the traversal we're doing here. -// -void checkUnload (StgClosure *static_objects) -{ - uint32_t g, n; - HashTable *addrs; - StgClosure* p; - const StgInfoTable *info; - ObjectCode *oc, *prev, *next; - gen_workspace *ws; - StgClosure* link; - - if (unloaded_objects == NULL) return; - - ACQUIRE_LOCK(&linker_unloaded_mutex); - - OCSectionIndices *s_indices = buildOCSectionIndices(unloaded_objects); - // Mark every unloadable object as unreferenced initially - for (oc = unloaded_objects; oc; oc = oc->next) { - IF_DEBUG(linker, debugBelch("Checking whether to unload %" PATH_FMT "\n", - oc->fileName)); - oc->referenced = false; - } - - addrs = allocHashTable(); - - for (p = static_objects; p != END_OF_STATIC_OBJECT_LIST; p = link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - info = get_itbl(p); - checkAddress(addrs, info, s_indices); - link = *STATIC_LINK(info, p); - } - - // CAFs on revertible_caf_list are not on static_objects - for (p = (StgClosure*)revertible_caf_list; - p != END_OF_CAF_LIST; - p = ((StgIndStatic *)p)->static_link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - } - - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - searchHeapBlocks (addrs, generations[g].blocks, s_indices); - searchHeapBlocks (addrs, generations[g].large_objects, s_indices); - - for (n = 0; n < n_capabilities; n++) { - ws = &gc_threads[n]->gens[g]; - searchHeapBlocks(addrs, ws->todo_bd, s_indices); - searchHeapBlocks(addrs, ws->part_list, s_indices); - searchHeapBlocks(addrs, ws->scavd_list, s_indices); - } - } - -#if defined(PROFILING) - /* Traverse the cost centre tree, calling checkAddress on each CCS/CC */ - searchCostCentres(addrs, CCS_MAIN, s_indices); - - /* Also check each cost centre in the CC_LIST */ - CostCentre *cc; - for (cc = CC_LIST; cc != NULL; cc = cc->link) { - checkAddress(addrs, cc, s_indices); - } -#endif /* PROFILING */ - - freeOCSectionIndices(s_indices); - // Look through the unloadable objects, and any object that is still - // marked as unreferenced can be physically unloaded, because we - // have no references to it. - prev = NULL; - for (oc = unloaded_objects; oc; oc = next) { - next = oc->next; - if (oc->referenced == 0) { - if (prev == NULL) { - unloaded_objects = oc->next; - } else { - prev->next = oc->next; - } - IF_DEBUG(linker, debugBelch("Unloading object file %" PATH_FMT "\n", - oc->fileName)); - freeObjectCode(oc); - } else { - IF_DEBUG(linker, debugBelch("Object file still in use: %" - PATH_FMT "\n", oc->fileName)); - prev = oc; - } - } - - freeHashTable(addrs, NULL); - - RELEASE_LOCK(&linker_unloaded_mutex); + old_objects = NULL; } ===================================== rts/CheckUnload.h ===================================== @@ -12,6 +12,34 @@ #include "BeginPrivate.h" -void checkUnload (StgClosure *static_objects); +#include "LinkerInternals.h" + +// Currently live objects +extern ObjectCode *objects; + +// Root set for object collection +extern ObjectCode *loaded_objects; + +// Mark bit for live objects +extern uint8_t object_code_mark_bit; + +// Number of object code currently marked for unloading. See the definition in +// CheckUnload.c for details. +extern int n_unloaded_objects; + +void initUnloadCheck(void); +void exitUnloadCheck(void); + +// Call before major GC to prepare section index table for marking +bool prepareUnloadCheck(void); + +// Mark object code of a static closure address as 'live' +void markObjectCode(const void *addr); + +// Call after major GC to unload unused and unmarked object code +void checkUnload(void); + +// Call on loaded object code +void insertOCSectionIndices(ObjectCode *oc); #include "EndPrivate.h" ===================================== rts/Hash.c ===================================== @@ -400,6 +400,27 @@ mapHashTable(HashTable *table, void *data, MapHashFn fn) } } +void +iterHashTable(HashTable *table, void *data, IterHashFn fn) +{ + /* The last bucket with something in it is table->max + table->split - 1 */ + long segment = (table->max + table->split - 1) / HSEGSIZE; + long index = (table->max + table->split - 1) % HSEGSIZE; + + while (segment >= 0) { + while (index >= 0) { + for (HashList *hl = table->dir[segment][index]; hl != NULL; hl = hl->next) { + if (!fn(data, hl->key, hl->data)) { + return; + } + } + index--; + } + segment--; + index = HSEGSIZE - 1; + } +} + /* ----------------------------------------------------------------------------- * When we initialize a hash table, we set up the first segment as well, * initializing all of the first segment's hash buckets to NULL. @@ -444,12 +465,6 @@ allocStrHashTable(void) return allocHashTable_(hashStr, compareStr); } -void -exitHashTable(void) -{ - /* nothing to do */ -} - int keyCountHashTable (HashTable *table) { return table->kcount; ===================================== rts/Hash.h ===================================== @@ -33,8 +33,11 @@ int keyCountHashTable (HashTable *table); int keysHashTable(HashTable *table, StgWord keys[], int szKeys); typedef void (*MapHashFn)(void *data, StgWord key, const void *value); +// Return true -> continue; false -> stop +typedef bool (*IterHashFn)(void *data, StgWord key, const void *value); void mapHashTable(HashTable *table, void *data, MapHashFn fn); +void iterHashTable(HashTable *table, void *data, IterHashFn); /* Hash table access where the keys are C strings (the strings are * assumed to be allocated by the caller, and mustn't be deallocated @@ -62,6 +65,32 @@ int hashStr(const HashTable *table, StgWord key); */ void freeHashTable ( HashTable *table, void (*freeDataFun)(void *) ); -void exitHashTable ( void ); +INLINE_HEADER void freeStrHashTable ( HashTable *table, void (*freeDataFun)(void *) ) +{ + freeHashTable((HashTable*)table, freeDataFun); +} + +/* + * Hash set API + * + * A hash set is bascially a hash table where values are NULL. + */ + +typedef struct hashtable HashSet; + +INLINE_HEADER HashSet *allocHashSet ( void ) +{ + return (HashSet*)allocHashTable(); +} + +INLINE_HEADER void freeHashSet ( HashSet *set ) +{ + freeHashTable((HashTable*)set, NULL); +} + +INLINE_HEADER void insertHashSet ( HashSet *set, StgWord key ) +{ + insertHashTable((HashTable*)set, key, NULL); +} #include "EndPrivate.h" ===================================== rts/Linker.c ===================================== @@ -32,6 +32,7 @@ #include "linker/CacheFlush.h" #include "linker/SymbolExtras.h" #include "PathUtils.h" +#include "CheckUnload.h" // createOCSectionIndices #if !defined(mingw32_HOST_OS) #include "posix/Signals.h" @@ -161,23 +162,9 @@ */ /*Str*/HashTable *symhash; -/* List of currently loaded objects */ -ObjectCode *objects = NULL; /* initially empty */ - -/* List of objects that have been unloaded via unloadObj(), but are waiting - to be actually freed via checkUnload() */ -ObjectCode *unloaded_objects = NULL; /* initially empty */ - #if defined(THREADED_RTS) -/* This protects all the Linker's global state except unloaded_objects */ +/* This protects all the Linker's global state */ Mutex linker_mutex; -/* - * This protects unloaded_objects. We have a separate mutex for this, because - * the GC needs to access unloaded_objects in checkUnload, while the linker only - * needs to access unloaded_objects in unloadObj(), so this allows most linker - * operations proceed concurrently with the GC. - */ -Mutex linker_unloaded_mutex; #endif /* Generic wrapper function to try and Resolve and RunInit oc files */ @@ -447,12 +434,10 @@ initLinker_ (int retain_cafs) linker_init_done = 1; } - objects = NULL; - unloaded_objects = NULL; + initUnloadCheck(); #if defined(THREADED_RTS) initMutex(&linker_mutex); - initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -538,6 +523,7 @@ exitLinker( void ) { #endif if (linker_init_done == 1) { freeHashTable(symhash, free); + exitUnloadCheck(); } #if defined(THREADED_RTS) closeMutex(&linker_mutex); @@ -864,18 +850,24 @@ HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data) } /* ----------------------------------------------------------------------------- - * lookup a symbol in the hash table + * Lookup a symbol in the hash table + * + * When 'dependent' is not NULL, adds it as a dependent to the owner of the + * symbol. */ #if defined(OBJFORMAT_PEi386) -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + (void)dependent; // TODO + ASSERT_LOCK_HELD(&linker_mutex); return lookupSymbol_PEi386(lbl); } #else -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + ASSERT_LOCK_HELD(&linker_mutex); IF_DEBUG(linker, debugBelch("lookupSymbol: looking up '%s'\n", lbl)); ASSERT(symhash != NULL); @@ -900,10 +892,18 @@ SymbolAddr* lookupSymbol_ (SymbolName* lbl) return internal_dlsym(lbl + 1); # else - ASSERT(2+2 == 5); + ASSERT(false); return NULL; # endif } else { + if (dependent) { + // Add dependent as symbol's owner's dependency + ObjectCode *owner = pinfo->owner; + if (owner) { + // TODO: what does it mean for a symbol to not have an owner? + insertHashSet(dependent->dependencies, (W_)owner); + } + } return loadSymbol(lbl, pinfo); } } @@ -942,7 +942,7 @@ SymbolAddr* loadSymbol(SymbolName *lbl, RtsSymbolInfo *pinfo) { SymbolAddr* lookupSymbol( SymbolName* lbl ) { ACQUIRE_LOCK(&linker_mutex); - SymbolAddr* r = lookupSymbol_(lbl); + SymbolAddr* r = lookupDependentSymbol(lbl, NULL); if (!r) { errorBelch("^^ Could not load '%s', dependency unresolved. " "See top entry above.\n", lbl); @@ -1342,6 +1342,8 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->fileName); stgFree(oc->archiveMemberName); + freeHashSet(oc->dependencies); + stgFree(oc); } @@ -1403,6 +1405,10 @@ mkOc( pathchar *path, char *image, int imageSize, /* chain it onto the list of objects */ oc->next = NULL; + oc->prev = NULL; + oc->next_loaded_object = NULL; + oc->mark = object_code_mark_bit; + oc->dependencies = allocHashSet(); #if RTS_LINKER_USE_MMAP oc->rw_m32 = m32_allocator_new(false); @@ -1421,9 +1427,9 @@ mkOc( pathchar *path, char *image, int imageSize, HsInt isAlreadyLoaded( pathchar *path ) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path) + && o->status != OBJECT_UNLOADED) { return 1; /* already loaded */ } } @@ -1557,21 +1563,16 @@ preloadObjectFile (pathchar *path) */ static HsInt loadObj_ (pathchar *path) { - ObjectCode* oc; - IF_DEBUG(linker, debugBelch("loadObj: %" PATH_FMT "\n", path)); - - /* debugBelch("loadObj %s\n", path ); */ - - /* Check that we haven't already loaded this object. - Ignore requests to load multiple times */ + // Check that we haven't already loaded this object. + // Ignore requests to load multiple times if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); - return 1; /* success */ + return 1; // success } - oc = preloadObjectFile(path); + ObjectCode *oc = preloadObjectFile(path); if (oc == NULL) return 0; if (! loadOc(oc)) { @@ -1582,8 +1583,10 @@ static HsInt loadObj_ (pathchar *path) return 0; } - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); + + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; return 1; } @@ -1778,15 +1781,15 @@ int ocTryLoad (ObjectCode* oc) { */ static HsInt resolveObjs_ (void) { - ObjectCode *oc; - int r; - IF_DEBUG(linker, debugBelch("resolveObjs: start\n")); - for (oc = objects; oc; oc = oc->next) { - r = ocTryLoad(oc); + for (ObjectCode *oc = objects; oc; oc = oc->next) { + int r = ocTryLoad(oc); if (!r) { + errorBelch("Could not load Object Code %" PATH_FMT ".\n", OC_INFORMATIVE_FILENAME(oc)); + IF_DEBUG(linker, printLoadedObjects()); + fflush(stderr); return r; } } @@ -1813,45 +1816,35 @@ HsInt resolveObjs (void) */ static HsInt unloadObj_ (pathchar *path, bool just_purge) { - ObjectCode *oc, *prev, *next; - HsBool unloadedAnyObj = HS_BOOL_FALSE; - ASSERT(symhash != NULL); ASSERT(objects != NULL); IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); - prev = NULL; - for (oc = objects; oc; oc = next) { - next = oc->next; // oc might be freed - - if (!pathcmp(oc->fileName,path)) { + bool unloadedAnyObj = false; + ObjectCode *prev = NULL; + // NOTE (osa): There may be more than one object with the same file name + // (happens when loading archive files) so we don't stop after unloading one + for (ObjectCode *oc = loaded_objects; oc; oc = oc->next_loaded_object) { + if (pathcmp(oc->fileName,path) == 0) { + oc->status = OBJECT_UNLOADED; - // these are both idempotent, so in just_purge mode we can - // later call unloadObj() to really unload the object. + // These are both idempotent, so in just_purge mode we can later + // call unloadObj() to really unload the object. removeOcSymbols(oc); freeOcStablePtrs(oc); + unloadedAnyObj = true; + if (!just_purge) { + n_unloaded_objects += 1; + // Remove object code from root set if (prev == NULL) { - objects = oc->next; + loaded_objects = oc->next_loaded_object; } else { - prev->next = oc->next; + prev->next_loaded_object = oc->next_loaded_object; } - ACQUIRE_LOCK(&linker_unloaded_mutex); - oc->next = unloaded_objects; - unloaded_objects = oc; - oc->status = OBJECT_UNLOADED; - RELEASE_LOCK(&linker_unloaded_mutex); - // We do not own oc any more; it can be released at any time by - // the GC in checkUnload(). - } else { - prev = oc; } - - /* This could be a member of an archive so continue - * unloading other members. */ - unloadedAnyObj = HS_BOOL_TRUE; } else { prev = oc; } @@ -1859,8 +1852,7 @@ static HsInt unloadObj_ (pathchar *path, bool just_purge) if (unloadedAnyObj) { return 1; - } - else { + } else { errorBelch("unloadObj: can't find `%" PATH_FMT "' to unload", path); return 0; } @@ -1884,13 +1876,7 @@ HsInt purgeObj (pathchar *path) static OStatus getObjectLoadStatus_ (pathchar *path) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } - } - for (o = unloaded_objects; o; o = o->next) { + for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { return o->status; } ===================================== rts/LinkerInternals.h ===================================== @@ -191,9 +191,6 @@ typedef struct _ObjectCode { /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; - /* flag used when deciding whether to unload an object file */ - int referenced; - /* record by how much image has been deliberately misaligned after allocation, so that we can use realloc */ int misalignment; @@ -205,8 +202,37 @@ typedef struct _ObjectCode { int n_segments; Segment *segments; - /* Allow a chain of these things */ - struct _ObjectCode * next; + // + // Garbage collection fields + // + + // Next object in `objects` list + struct _ObjectCode *next; + + // Previous object in `objects` list + struct _ObjectCode *prev; + + // Next object in `loaded_objects` list + struct _ObjectCode *next_loaded_object; + + // Mark bit + uint8_t mark; + + // Set of dependencies (ObjectCode*) of the object file. Traverse + // dependencies using `iterHashTable`. + // + // New entries are added as we resolve symbols in an object file, in + // `lookupDependentSymbol`. When an object file uses multiple symbols from + // another object file we add the dependent multiple times, so we use a + // `HashTable` here rather than a list/array to avoid copies. + // + // Used when unloading object files. See Note [Object unloading] in + // CheckUnload.c. + HashSet *dependencies; + + // + // End of garbage collection fields + // /* SANITY CHECK ONLY: a list of the only memory regions which may safely be prodded during relocation. Any attempt to prod @@ -250,12 +276,8 @@ typedef struct _ObjectCode { (OC)->fileName \ ) -extern ObjectCode *objects; -extern ObjectCode *unloaded_objects; - #if defined(THREADED_RTS) extern Mutex linker_mutex; -extern Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -306,8 +328,9 @@ int ghciInsertSymbolTable( HsBool weak, ObjectCode *owner); -/* lock-free version of lookupSymbol */ -SymbolAddr* lookupSymbol_ (SymbolName* lbl); +/* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a + * dependent to the owner of the symbol. */ +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent); extern /*Str*/HashTable *symhash; ===================================== rts/RtsStartup.c ===================================== @@ -512,9 +512,6 @@ hs_exit_(bool wait_foreign) shutdownAsyncIO(wait_foreign); #endif - /* free hash table storage */ - exitHashTable(); - // Finally, free all our storage. However, we only free the heap // memory if we have waited for foreign calls to complete; // otherwise a foreign call in progress may still be referencing ===================================== rts/linker/Elf.c ===================================== @@ -1099,7 +1099,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) { S = (Elf_Addr)symbol->addr; } else { - S_tmp = lookupSymbol_( symbol->name ); + S_tmp = lookupDependentSymbol( symbol->name, oc ); S = (Elf_Addr)S_tmp; } if (!S) { @@ -1519,7 +1519,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } else { /* No, so look up the name in our global table. */ symbol = strtab + sym.st_name; - S_tmp = lookupSymbol_( symbol ); + S_tmp = lookupDependentSymbol( symbol, oc ); S = (Elf_Addr)S_tmp; } if (!S) { ===================================== rts/linker/LoadArchive.c ===================================== @@ -5,6 +5,7 @@ #include "sm/OSMem.h" #include "RtsUtils.h" #include "LinkerInternals.h" +#include "CheckUnload.h" // loaded_objects, insertOCSectionIndices #include "linker/M32Alloc.h" /* Platform specific headers */ @@ -241,7 +242,6 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, static HsInt loadArchive_ (pathchar *path) { - ObjectCode* oc = NULL; char *image = NULL; HsInt retcode = 0; int memberSize; @@ -520,8 +520,8 @@ static HsInt loadArchive_ (pathchar *path) sprintf(archiveMemberName, "%" PATH_FMT "(%.*s)", path, (int)thisFileNameSize, fileName); - oc = mkOc(path, image, memberSize, false, archiveMemberName - , misalignment); + ObjectCode *oc = mkOc(path, image, memberSize, false, archiveMemberName, + misalignment); #if defined(OBJFORMAT_MACHO) ocInit_MachO( oc ); #endif @@ -536,8 +536,9 @@ static HsInt loadArchive_ (pathchar *path) fclose(f); return 0; } else { - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); // also adds the object to `objects` list + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; } } else if (isGnuIndex) { ===================================== rts/linker/MachO.c ===================================== @@ -242,7 +242,7 @@ resolveImports( addr = (SymbolAddr*) (symbol->nlist->n_value); IF_DEBUG(linker, debugBelch("resolveImports: undefined external %s has value %p\n", symbol->name, addr)); } else { - addr = lookupSymbol_(symbol->name); + addr = lookupDependentSymbol(symbol->name, oc); IF_DEBUG(linker, debugBelch("resolveImports: looking up %s, %p\n", symbol->name, addr)); } @@ -564,12 +564,12 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { /* external symbols should be able to be - * looked up via the lookupSymbol_ function. + * looked up via the lookupDependentSymbol function. * Either through the global symbol hashmap * or asking the system, if not found * in the symbol hashmap */ - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -609,7 +609,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -784,7 +784,7 @@ relocateSection(ObjectCode* oc, int curSection) // symtab, or it is undefined, meaning dlsym must be used // to resolve it. - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); IF_DEBUG(linker, debugBelch("relocateSection: looked up %s, " "external X86_64_RELOC_GOT or X86_64_RELOC_GOT_LOAD\n" " : addr = %p\n", nm, addr)); @@ -845,7 +845,7 @@ relocateSection(ObjectCode* oc, int curSection) nm, (void *)value)); } else { - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); if (addr == NULL) { errorBelch("\nlookupSymbol failed in relocateSection (relocate external)\n" @@ -1345,7 +1345,7 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->nlist[i].n_type & N_EXT) { if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) - && lookupSymbol_(nm)) { + && lookupDependentSymbol(nm, oc)) { // weak definition, and we already have a definition IF_DEBUG(linker, debugBelch(" weak: %s\n", nm)); } @@ -1497,7 +1497,7 @@ ocResolve_MachO(ObjectCode* oc) * have the address. */ if(NULL == symbol->addr) { - symbol->addr = lookupSymbol_((char*)symbol->name); + symbol->addr = lookupDependentSymbol((char*)symbol->name, oc); if(NULL == symbol->addr) barf("Failed to lookup symbol: %s", symbol->name); } else { ===================================== rts/linker/PEi386.c ===================================== @@ -185,6 +185,7 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" #include "GetEnv.h" +#include "CheckUnload.h" #include "linker/PEi386.h" #include "linker/PEi386Types.h" #include "linker/SymbolExtras.h" @@ -1894,7 +1895,7 @@ ocResolve_PEi386 ( ObjectCode* oc ) } else { copyName ( getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1 ); - S = (size_t) lookupSymbol_( (char*)symbol ); + S = (size_t) lookupDependentSymbol( (char*)symbol, oc ); if ((void*)S == NULL) { errorBelch(" | %" PATH_FMT ": unknown symbol `%s'", oc->fileName, symbol); releaseOcInfo (oc); ===================================== rts/linker/elf_got.c ===================================== @@ -88,7 +88,7 @@ fillGot(ObjectCode * oc) { if( STT_NOTYPE == ELF_ST_TYPE(symbol->elf_sym->st_info) || STB_WEAK == ELF_ST_BIND(symbol->elf_sym->st_info)) { if(0x0 == symbol->addr) { - symbol->addr = lookupSymbol_(symbol->name); + symbol->addr = lookupDependentSymbol(symbol->name, oc); if(0x0 == symbol->addr) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; ===================================== rts/sm/Evac.c ===================================== @@ -28,6 +28,7 @@ #include "CNF.h" #include "Scav.h" #include "NonMoving.h" +#include "CheckUnload.h" // n_unloaded_objects and markObjectCode #if defined(THREADED_RTS) && !defined(PARALLEL_GC) #define evacuate(p) evacuate1(p) @@ -593,6 +594,11 @@ loop: if (!HEAP_ALLOCED_GC(q)) { if (!major_gc) return; + // Note [Object unloading] in CheckUnload.c + if (RTS_UNLIKELY(unload_mark_needed)) { + markObjectCode(q); + } + info = get_itbl(q); switch (info->type) { ===================================== rts/sm/GC.c ===================================== @@ -97,6 +97,13 @@ * See also: Note [STATIC_LINK fields] in Storage.h. */ +/* Hot GC globals + * ~~~~~~~~~~~~~~ + * The globals below are quite hot during GC but read-only, initialized during + * the beginning of collection. It is important that they reside in the same + * cache-line to minimize unnecessary cache misses. + */ + /* N is the oldest generation being collected, where the generations * are numbered starting at 0. A major GC (indicated by the major_gc * flag) is when we're collecting all generations. We only attempt to @@ -105,6 +112,7 @@ uint32_t N; bool major_gc; bool deadlock_detect_gc; +bool unload_mark_needed; /* Data used for allocation area sizing. */ @@ -297,6 +305,12 @@ GarbageCollect (uint32_t collect_gen, static_flag == STATIC_FLAG_A ? STATIC_FLAG_B : STATIC_FLAG_A; } + if (major_gc) { + unload_mark_needed = prepareUnloadCheck(); + } else { + unload_mark_needed = false; + } + #if defined(THREADED_RTS) work_stealing = RtsFlags.ParFlags.parGcLoadBalancingEnabled && N >= RtsFlags.ParFlags.parGcLoadBalancingGen; @@ -810,9 +824,12 @@ GarbageCollect (uint32_t collect_gen, resetNurseries(); - // mark the garbage collected CAFs as dead #if defined(DEBUG) - if (major_gc && !RtsFlags.GcFlags.useNonmoving) { gcCAFs(); } + // Mark the garbage collected CAFs as dead. Done in `nonmovingGcCafs()` when + // non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + gcCAFs(); + } #endif // Update the stable name hash table @@ -823,9 +840,14 @@ GarbageCollect (uint32_t collect_gen, // hs_free_stable_ptr(), both of which access the StablePtr table. stablePtrUnlock(); - // Must be after stablePtrUnlock(), because it might free stable ptrs. - if (major_gc) { - checkUnload (gct->scavenged_static_objects); + // Unload dynamically-loaded object code after a major GC. + // See Note [Object unloading] in CheckUnload.c for details. + // + // TODO: Similar to `nonmovingGcCafs` non-moving GC should have its own + // collector for these objects, but that's currently not implemented, so we + // simply don't unload object code when non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + checkUnload(); } #if defined(PROFILING) ===================================== rts/sm/GC.h ===================================== @@ -35,6 +35,7 @@ extern uint32_t N; extern bool major_gc; /* See Note [Deadlock detection under nonmoving collector]. */ extern bool deadlock_detect_gc; +extern bool unload_mark_needed; extern bdescr *mark_stack_bd; extern bdescr *mark_stack_top_bd; ===================================== testsuite/tests/ghci/T16525a/T16525a.script ===================================== @@ -1,6 +1,10 @@ :set -fobject-code :load A import Control.Concurrent -_ <- forkIO $ threadDelay 1000000 >> (print (map v1 value)) +_ <- forkIO $ threadDelay 500000 >> print (map v1 value) :l [] System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC ===================================== testsuite/tests/ghci/T16525a/T16525a.stdout ===================================== @@ -0,0 +1 @@ +["a;lskdfa;lszkfsd;alkfjas"] ===================================== testsuite/tests/ghci/T16525a/all.T ===================================== @@ -1,6 +1,3 @@ test('T16525a', - [extra_files(['A.hs', 'B.hs', ]), - when(compiler_debugged(), extra_run_opts('+RTS -DS -RTS')), - # We don't support unloading with the dynamic linker - when(ghc_dynamic(), skip), ], + [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525a.script']) ===================================== testsuite/tests/ghci/T16525b/A.hs ===================================== @@ -0,0 +1,6 @@ +module A (a) where + +import B + +a :: () -> IO Int +a x = b x ===================================== testsuite/tests/ghci/T16525b/B.hs ===================================== @@ -0,0 +1,5 @@ +module B (b) where + +{-# NOINLINE b #-} +b :: () -> IO Int +b () = return 999999999 ===================================== testsuite/tests/ghci/T16525b/T16525b.script ===================================== @@ -0,0 +1,22 @@ +:set -fobject-code +:load A +import Control.Concurrent +import Control.Monad +:{ +_ <- forkIO $ do + replicateM_ 3 (a () >>= print >> threadDelay 500000) + putStrLn "===== THREAD DONE =====" +:} +:l [] +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 ===================================== testsuite/tests/ghci/T16525b/T16525b.stdout ===================================== @@ -0,0 +1,4 @@ +999999999 +999999999 +999999999 +===== THREAD DONE ===== ===================================== testsuite/tests/ghci/T16525b/all.T ===================================== @@ -0,0 +1,2 @@ +# Tests unloading an object file which is in use in a thread +test('T16525b', [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525b.script']) ===================================== testsuite/tests/rts/linker/linker_error.c ===================================== @@ -57,7 +57,10 @@ int main (int argc, char *argv[]) r = resolveObjs(); if (!r) { debugBelch("resolveObjs failed\n"); + // Mark the object as unloadable: unloadObj(obj); + // Actually unload it: + performMajorGC(); continue; } errorBelch("loading succeeded"); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67a1c9c14528a59a0a02582160ae40ced5939d01 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/67a1c9c14528a59a0a02582160ae40ced5939d01 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 Tue Nov 24 18:43:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 13:43:09 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-8.10] 38 commits: testsuite: Mark hie002 as high_memory_usage Message-ID: <5fbd543d56777_86cbee259037782@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: 5300e0e6 by Ben Gamari at 2020-11-24T13:40:34-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - 3e97158a by Ben Gamari at 2020-11-24T13:40:34-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 6df201b5 by Ben Gamari at 2020-11-24T13:40:34-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 878bc8c8 by Ben Gamari at 2020-11-24T13:40:34-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 26d535e5 by Ben Gamari at 2020-11-24T13:40:34-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - 1377402f by Ben Gamari at 2020-11-24T13:40:34-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 6f10802e by Ben Gamari at 2020-11-24T13:40:34-05:00 rts/BlockAlloc: Use relaxed operations - - - - - 48fd966b by Ben Gamari at 2020-11-24T13:40:34-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - aa2215f9 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - f2ea40ca by Ben Gamari at 2020-11-24T13:40:34-05:00 rts/Storage: Use atomics - - - - - e371a149 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts/Updates: Use proper atomic operations - - - - - 05975e84 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - 01d8d105 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts/GC: Use atomics - - - - - c30bbd92 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - 65daad33 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts/Storage: Accept races on heap size counters - - - - - 0fd2a3b4 by Ben Gamari at 2020-11-24T13:40:34-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - 69877da4 by GHC GitLab CI at 2020-11-24T13:40:34-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - e5217165 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - b313c317 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Use relaxed ordering on spinlock counters - - - - - f23aa99e by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 2790c396 by Ben Gamari at 2020-11-24T13:40:35-05:00 Strengthen ordering in releaseGCThreads - - - - - f711be8a by Ben Gamari at 2020-11-24T13:40:35-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - 928dc06d by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 95760050 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - 290ce1a3 by GHC GitLab CI at 2020-11-24T13:40:35-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - d5241ddf by Ben Gamari at 2020-11-24T13:40:35-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - d511cbb2 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - 9230100f by Ben Gamari at 2020-11-24T13:40:35-05:00 Mitigate data races in event manager startup/shutdown - - - - - 5db98cfe by Ben Gamari at 2020-11-24T13:40:35-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - 65b4ddf4 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Accept benign races in Proftimer - - - - - 4b5216f3 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 6ca8df01 by Ben Gamari at 2020-11-24T13:40:35-05:00 Fix #17289 - - - - - 5b89c84b by Ben Gamari at 2020-11-24T13:40:35-05:00 suppress #17289 (ticker) race - - - - - 0122610e by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - 3bfcaf4b by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 0a75b950 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - c1b7767f by Ben Gamari at 2020-11-24T13:40:35-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 01325b12 by Ben Gamari at 2020-11-24T13:40:35-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - 30 changed files: - .gitlab-ci.yml - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - includes/rts/TSANUtils.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Proftimer.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Sparks.c - + rts/SpinLock.c - rts/StablePtr.c - rts/Stats.c - rts/Stats.h - rts/ThreadPaused.c - rts/Timer.c - rts/Updates.h - rts/WSDeque.c - rts/WSDeque.h - rts/Weak.c - rts/posix/GetTime.c - rts/posix/OSThreads.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b4a532a1ce8a02afa5f9eb3672ca86f0ea36c6f...01325b12799cc3ccd997aa20006572b132e5b799 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b4a532a1ce8a02afa5f9eb3672ca86f0ea36c6f...01325b12799cc3ccd997aa20006572b132e5b799 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 Tue Nov 24 19:46:49 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 24 Nov 2020 14:46:49 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/opt_dumps Message-ID: <5fbd63296e3c8_86c11450e2851291@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/opt_dumps at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/opt_dumps 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 Tue Nov 24 19:49:02 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 24 Nov 2020 14:49:02 -0500 Subject: [Git][ghc/ghc][wip/andreask/opt_dumps] Optimize dumping of consecutive whitespace. Message-ID: <5fbd63aef809_86c113a5b2c5401a@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/opt_dumps at Glasgow Haskell Compiler / GHC Commits: 629628f8 by Andreas Klebinger at 2020-11-24T20:48:45+01:00 Optimize dumping of consecutive whitespace. The naive way of putting out n characters of indent would be something like `hPutStr hdl (replicate n ' ')`. However this is quite inefficient as we allocate an absurd number of strings consisting of simply spaces as we don't cache them. To improve on this we now track if we can simply write ascii spaces via hPutBuf instead. This is the case when running with -ddump-to-file where we force the encoding to be UTF8. This avoids both the cost of going through encoding as well as avoiding allocation churn from all the white space. Instead we simply use hPutBuf on a preallocated unlifted string. When dumping stg like this: > nofib/spectral/simple/Main.hs -fforce-recomp -ddump-stg-final -ddump-to-file -c +RTS -s Allocations went from 1,778 MB to 1,702MB. About a 4% reduction of allocation! I did not measure the difference in runtime but expect it to be similar. - - - - - 5 changed files: - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Utils/Error.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Ppr.hs Changes: ===================================== compiler/GHC/Driver/Ppr.hs ===================================== @@ -66,7 +66,7 @@ showSDocDebug dflags d = renderWithContext ctx d printForUser :: DynFlags -> Handle -> PrintUnqualified -> Depth -> SDoc -> IO () printForUser dflags handle unqual depth doc - = printSDocLn ctx PageMode handle doc + = printSDocLn ctx (PageMode False) handle doc where ctx = initSDocContext dflags (mkUserStyle unqual depth) -- | Like 'printSDocLn' but specialized with 'LeftMode' and ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1377,7 +1377,7 @@ defaultFatalMessager = hPutStrLn stderr jsonLogAction :: LogAction jsonLogAction dflags reason severity srcSpan msg = - defaultLogActionHPutStrDoc dflags stdout + defaultLogActionHPutStrDoc dflags True stdout (withPprStyle (PprCode CStyle) (doc $$ text "")) where str = renderWithContext (initSDocContext dflags defaultUserStyle) msg @@ -1400,9 +1400,9 @@ defaultLogAction dflags reason severity srcSpan msg SevWarning -> printWarns SevError -> printWarns where - printOut = defaultLogActionHPrintDoc dflags stdout - printErrs = defaultLogActionHPrintDoc dflags stderr - putStrSDoc = defaultLogActionHPutStrDoc dflags stdout + printOut = defaultLogActionHPrintDoc dflags False stdout + printErrs = defaultLogActionHPrintDoc dflags False stderr + putStrSDoc = defaultLogActionHPutStrDoc dflags False stdout -- Pretty print the warning flag, if any (#10752) message = mkLocMessageAnn flagMsg severity srcSpan msg @@ -1442,16 +1442,19 @@ defaultLogAction dflags reason severity srcSpan msg | otherwise = "" -- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline. -defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> IO () -defaultLogActionHPrintDoc dflags h d - = defaultLogActionHPutStrDoc dflags h (d $$ text "") - -defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> IO () -defaultLogActionHPutStrDoc dflags h d +defaultLogActionHPrintDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () +defaultLogActionHPrintDoc dflags asciiSpace h d + = defaultLogActionHPutStrDoc dflags asciiSpace h (d $$ text "") + +-- | The boolean arguments let's the pretty printer know if it can optimize indent +-- by writing ascii ' ' characters without going through decoding. +defaultLogActionHPutStrDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () +defaultLogActionHPutStrDoc dflags asciiSpace h d -- Don't add a newline at the end, so that successive -- calls to this log-action can output all on the same line - = printSDoc ctx Pretty.PageMode h d - where ctx = initSDocContext dflags defaultUserStyle + = printSDoc ctx (Pretty.PageMode asciiSpace) h d + where + ctx = initSDocContext dflags defaultUserStyle newtype FlushOut = FlushOut (IO ()) ===================================== compiler/GHC/Utils/Error.hs ===================================== @@ -327,7 +327,8 @@ dumpSDocWithStyle sty dflags dumpOpt hdr doc = $$ blankLine $$ doc return $ mkDumpDoc hdr d - defaultLogActionHPrintDoc dflags handle (withPprStyle sty doc') + -- When we dump to files we use UTF8. Which allows ascii spaces. + defaultLogActionHPrintDoc dflags True handle (withPprStyle sty doc') -- write the dump to stdout writeDump Nothing = do ===================================== compiler/GHC/Utils/Outputable.hs ===================================== @@ -563,7 +563,7 @@ pprCode cs d = withPprStyle (PprCode cs) d renderWithContext :: SDocContext -> SDoc -> String renderWithContext ctx sdoc - = let s = Pretty.style{ Pretty.mode = PageMode, + = let s = Pretty.style{ Pretty.mode = PageMode False, Pretty.lineLength = sdocLineLength ctx } in Pretty.renderStyle s $ runSDoc sdoc ctx ===================================== compiler/GHC/Utils/Ppr.hs ===================================== @@ -917,16 +917,26 @@ data Style , ribbonsPerLine :: Float -- ^ Ratio of line length to ribbon length } --- | The default style (@mode=PageMode, lineLength=100, ribbonsPerLine=1.5@). +-- | The default style (@mode=PageMode False, lineLength=100, ribbonsPerLine=1.5@). style :: Style -style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode } +style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode False } -- | Rendering mode. -data Mode = PageMode -- ^ Normal +data Mode = PageMode { asciiSpace :: Bool } -- ^ Normal | ZigZagMode -- ^ With zig-zag cuts | LeftMode -- ^ No indentation, infinitely long lines | OneLineMode -- ^ All on one line +-- | Can we output an ascii space character for spaces? +-- Mostly true, but not for e.g. UTF16 +-- See Note [putSpaces optimizations] for why we bother +-- to track this. +hasAsciiSpace :: Mode -> Bool +hasAsciiSpace mode = + case mode of + PageMode asciiSpace -> asciiSpace + _ -> False + -- | Render the @Doc@ to a String using the given @Style at . renderStyle :: Style -> Doc -> String renderStyle s = fullRender (mode s) (lineLength s) (ribbonsPerLine s) @@ -1034,6 +1044,20 @@ printDoc :: Mode -> Int -> Handle -> Doc -> IO () -- printDoc adds a newline to the end printDoc mode cols hdl doc = printDoc_ mode cols hdl (doc $$ text "") +{- Note [putSpaces optimizations] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +When using dump flags a lot of what we are dumping ends up being whitespace. +This is especially true for Core/Stg dumps. Enough so that it's worth optimizing. + +Especially in the common case of writing to an UTF8 or similarly encoded file +where space is equal to ascii space we use hPutBuf to write a preallocated +buffer to the file. This avoids a fair bit of allocation. + +For other cases we fall back to the old and slow path for simplicity. + +-} + printDoc_ :: Mode -> Int -> Handle -> Doc -> IO () -- printDoc_ does not add a newline at the end, so that -- successive calls can output stuff on the same line @@ -1051,9 +1075,27 @@ printDoc_ mode pprCols hdl doc -- the I/O library's encoding layer. (#3398) put (ZStr s) next = hPutFZS hdl s >> next put (LStr s) next = hPutPtrString hdl s >> next - put (RStr n c) next = hPutStr hdl (replicate n c) >> next + put (RStr n c) next + | c == ' ' + = putSpaces n >> next + | otherwise + = hPutStr hdl (replicate n c) >> next + putSpaces n + -- If we use ascii spaces we are allowed to use hPutBuf + -- See Note [putSpaces optimizations] + | hasAsciiSpace mode + , n <= 100 + = hPutBuf hdl (Ptr spaces') n + | hasAsciiSpace mode + , n > 100 + = hPutBuf hdl (Ptr spaces') 100 >> putSpaces (n-100) + + | otherwise = hPutStr hdl (replicate n ' ') done = return () -- hPutChar hdl '\n' + -- 100 spaces, so we avoid the allocation of replicate n ' ' + spaces' = " "# + -- some versions of hPutBuf will barf if the length is zero hPutPtrString :: Handle -> PtrString -> IO () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/629628f8b8df6425e58e74ab09612fbb592a66a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/629628f8b8df6425e58e74ab09612fbb592a66a3 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 Tue Nov 24 19:58:51 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Tue, 24 Nov 2020 14:58:51 -0500 Subject: [Git][ghc/ghc][wip/andreask/opt_dumps] Optimize dumping of consecutive whitespace. Message-ID: <5fbd65fb46f1b_86c113a5b2c558e6@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/opt_dumps at Glasgow Haskell Compiler / GHC Commits: 327c725a by Andreas Klebinger at 2020-11-24T20:57:43+01:00 Optimize dumping of consecutive whitespace. The naive way of putting out n characters of indent would be something like `hPutStr hdl (replicate n ' ')`. However this is quite inefficient as we allocate an absurd number of strings consisting of simply spaces as we don't cache them. To improve on this we now track if we can simply write ascii spaces via hPutBuf instead. This is the case when running with -ddump-to-file where we force the encoding to be UTF8. This avoids both the cost of going through encoding as well as avoiding allocation churn from all the white space. Instead we simply use hPutBuf on a preallocated unlifted string. When dumping stg like this: > nofib/spectral/simple/Main.hs -fforce-recomp -ddump-stg-final -ddump-to-file -c +RTS -s Allocations went from 1,778 MB to 1,702MB. About a 4% reduction of allocation! I did not measure the difference in runtime but expect it to be similar. Bumps the haddock submodule since the interface of GHC's Pretty slightly changed. - - - - - 6 changed files: - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Utils/Error.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Ppr.hs - utils/haddock Changes: ===================================== compiler/GHC/Driver/Ppr.hs ===================================== @@ -66,7 +66,7 @@ showSDocDebug dflags d = renderWithContext ctx d printForUser :: DynFlags -> Handle -> PrintUnqualified -> Depth -> SDoc -> IO () printForUser dflags handle unqual depth doc - = printSDocLn ctx PageMode handle doc + = printSDocLn ctx (PageMode False) handle doc where ctx = initSDocContext dflags (mkUserStyle unqual depth) -- | Like 'printSDocLn' but specialized with 'LeftMode' and ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1377,7 +1377,7 @@ defaultFatalMessager = hPutStrLn stderr jsonLogAction :: LogAction jsonLogAction dflags reason severity srcSpan msg = - defaultLogActionHPutStrDoc dflags stdout + defaultLogActionHPutStrDoc dflags True stdout (withPprStyle (PprCode CStyle) (doc $$ text "")) where str = renderWithContext (initSDocContext dflags defaultUserStyle) msg @@ -1400,9 +1400,9 @@ defaultLogAction dflags reason severity srcSpan msg SevWarning -> printWarns SevError -> printWarns where - printOut = defaultLogActionHPrintDoc dflags stdout - printErrs = defaultLogActionHPrintDoc dflags stderr - putStrSDoc = defaultLogActionHPutStrDoc dflags stdout + printOut = defaultLogActionHPrintDoc dflags False stdout + printErrs = defaultLogActionHPrintDoc dflags False stderr + putStrSDoc = defaultLogActionHPutStrDoc dflags False stdout -- Pretty print the warning flag, if any (#10752) message = mkLocMessageAnn flagMsg severity srcSpan msg @@ -1442,16 +1442,19 @@ defaultLogAction dflags reason severity srcSpan msg | otherwise = "" -- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline. -defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> IO () -defaultLogActionHPrintDoc dflags h d - = defaultLogActionHPutStrDoc dflags h (d $$ text "") - -defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> IO () -defaultLogActionHPutStrDoc dflags h d +defaultLogActionHPrintDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () +defaultLogActionHPrintDoc dflags asciiSpace h d + = defaultLogActionHPutStrDoc dflags asciiSpace h (d $$ text "") + +-- | The boolean arguments let's the pretty printer know if it can optimize indent +-- by writing ascii ' ' characters without going through decoding. +defaultLogActionHPutStrDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () +defaultLogActionHPutStrDoc dflags asciiSpace h d -- Don't add a newline at the end, so that successive -- calls to this log-action can output all on the same line - = printSDoc ctx Pretty.PageMode h d - where ctx = initSDocContext dflags defaultUserStyle + = printSDoc ctx (Pretty.PageMode asciiSpace) h d + where + ctx = initSDocContext dflags defaultUserStyle newtype FlushOut = FlushOut (IO ()) ===================================== compiler/GHC/Utils/Error.hs ===================================== @@ -327,7 +327,8 @@ dumpSDocWithStyle sty dflags dumpOpt hdr doc = $$ blankLine $$ doc return $ mkDumpDoc hdr d - defaultLogActionHPrintDoc dflags handle (withPprStyle sty doc') + -- When we dump to files we use UTF8. Which allows ascii spaces. + defaultLogActionHPrintDoc dflags True handle (withPprStyle sty doc') -- write the dump to stdout writeDump Nothing = do ===================================== compiler/GHC/Utils/Outputable.hs ===================================== @@ -563,7 +563,7 @@ pprCode cs d = withPprStyle (PprCode cs) d renderWithContext :: SDocContext -> SDoc -> String renderWithContext ctx sdoc - = let s = Pretty.style{ Pretty.mode = PageMode, + = let s = Pretty.style{ Pretty.mode = PageMode False, Pretty.lineLength = sdocLineLength ctx } in Pretty.renderStyle s $ runSDoc sdoc ctx ===================================== compiler/GHC/Utils/Ppr.hs ===================================== @@ -917,16 +917,26 @@ data Style , ribbonsPerLine :: Float -- ^ Ratio of line length to ribbon length } --- | The default style (@mode=PageMode, lineLength=100, ribbonsPerLine=1.5@). +-- | The default style (@mode=PageMode False, lineLength=100, ribbonsPerLine=1.5@). style :: Style -style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode } +style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode False } -- | Rendering mode. -data Mode = PageMode -- ^ Normal +data Mode = PageMode { asciiSpace :: Bool } -- ^ Normal | ZigZagMode -- ^ With zig-zag cuts | LeftMode -- ^ No indentation, infinitely long lines | OneLineMode -- ^ All on one line +-- | Can we output an ascii space character for spaces? +-- Mostly true, but not for e.g. UTF16 +-- See Note [putSpaces optimizations] for why we bother +-- to track this. +hasAsciiSpace :: Mode -> Bool +hasAsciiSpace mode = + case mode of + PageMode asciiSpace -> asciiSpace + _ -> False + -- | Render the @Doc@ to a String using the given @Style at . renderStyle :: Style -> Doc -> String renderStyle s = fullRender (mode s) (lineLength s) (ribbonsPerLine s) @@ -1034,6 +1044,20 @@ printDoc :: Mode -> Int -> Handle -> Doc -> IO () -- printDoc adds a newline to the end printDoc mode cols hdl doc = printDoc_ mode cols hdl (doc $$ text "") +{- Note [putSpaces optimizations] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +When using dump flags a lot of what we are dumping ends up being whitespace. +This is especially true for Core/Stg dumps. Enough so that it's worth optimizing. + +Especially in the common case of writing to an UTF8 or similarly encoded file +where space is equal to ascii space we use hPutBuf to write a preallocated +buffer to the file. This avoids a fair bit of allocation. + +For other cases we fall back to the old and slow path for simplicity. + +-} + printDoc_ :: Mode -> Int -> Handle -> Doc -> IO () -- printDoc_ does not add a newline at the end, so that -- successive calls can output stuff on the same line @@ -1051,9 +1075,27 @@ printDoc_ mode pprCols hdl doc -- the I/O library's encoding layer. (#3398) put (ZStr s) next = hPutFZS hdl s >> next put (LStr s) next = hPutPtrString hdl s >> next - put (RStr n c) next = hPutStr hdl (replicate n c) >> next + put (RStr n c) next + | c == ' ' + = putSpaces n >> next + | otherwise + = hPutStr hdl (replicate n c) >> next + putSpaces n + -- If we use ascii spaces we are allowed to use hPutBuf + -- See Note [putSpaces optimizations] + | hasAsciiSpace mode + , n <= 100 + = hPutBuf hdl (Ptr spaces') n + | hasAsciiSpace mode + , n > 100 + = hPutBuf hdl (Ptr spaces') 100 >> putSpaces (n-100) + + | otherwise = hPutStr hdl (replicate n ' ') done = return () -- hPutChar hdl '\n' + -- 100 spaces, so we avoid the allocation of replicate n ' ' + spaces' = " "# + -- some versions of hPutBuf will barf if the length is zero hPutPtrString :: Handle -> PtrString -> IO () ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 4d0498d503bd51b7d7626497580232685a2691a1 +Subproject commit b2f1aef40cf50cf08eb28f34a9af2b1f9155c2df View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/327c725acb2530e75f9e86d725f7ac3b130a001a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/327c725acb2530e75f9e86d725f7ac3b130a001a 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 Tue Nov 24 20:12:16 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 15:12:16 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Kill off Note [Unification with skolems] Message-ID: <5fbd6920a3fda_86cfd752bc57939@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 11802fc3 by Richard Eisenberg at 2020-11-24T15:04:23-05:00 Kill off Note [Unification with skolems] - - - - - 3 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Solver/Rewrite.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -1044,7 +1044,9 @@ isOverlappableTyVar, and the use of Skolem in instanceBindFun, above, means that these will be treated as fresh constants in the unification algorithm during instance lookup. Without this treatment, GHC would complain, saying that the choice of instance depended on the instantiation of 'a'; but of -course it isn't *going* to be instantiated. +course it isn't *going* to be instantiated. Note that it is necessary that +the unification algorithm returns SurelyApart for these super-skolems +for GHC to be able to commit to another instance. We do this only for super skolems. For example we reject g :: forall a => [a] -> Int ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -363,32 +363,6 @@ types are apart. This has practical consequences for the ability for closed type family applications to reduce. See test case indexed-types/should_compile/Overlap14. -Note [Unification with skolems] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -If we discover that two types unify if and only if a skolem variable is -substituted, we can't properly unify the types. Perhaps surprisingly, -we say that these types are SurelyApart. This is to allow an example -like the following: - - class C a b where - meth :: a -> b -> () - - instance C a a where ... - instance C a Int where - meth = meth -- a bit silly, but this is meant to be a small example - -NB: No -XOverlappingInstances or overlapp(ing|able|ed) pragmas. - -The recursive call within the definition of `meth` is actually ambiguous: -if the instance variable `a` becomes Int, then the first instance would -match. But this is silly, because if `a` were Int, then we would never -have ended up in the second instance in the first place. - -We thus say that an unbindable variable is SurelyApart from other -types. This allows us to accept the program above. - -See also Note [Binding when looking up instances] in GHC.Core.InstEnv. - -} -- | Simple unification of two types; all type variables are bindable @@ -1193,12 +1167,12 @@ uUnrefined env tv1' ty2 ty2' kco -- How could this happen? If we're only matching and if -- we're comparing forall-bound variables. - _ -> surelyApart -- See Note [Unification with skolems] + _ -> surelyApart }}}} uUnrefined env tv1' ty2 _ kco -- ty2 is not a type variable = case tvBindFlag env tv1' of - Skolem -> surelyApart -- See Note [Unification with skolems] + Skolem -> surelyApart BindMe -> bindTv env tv1' (ty2 `mkCastTy` mkSymCo kco) bindTv :: UMEnv -> OutTyVar -> Type -> UM () @@ -1242,6 +1216,8 @@ data BindFlag | Skolem -- This type variable is a skolem constant -- Don't bind it; it only matches itself -- These variables are SurelyApart from other types + -- See Note [Binding when looking up instances] in GHC.Core.InstEnv + -- for why it must be SurelyApart. deriving Eq {- ===================================== compiler/GHC/Tc/Solver/Rewrite.hs ===================================== @@ -1023,6 +1023,6 @@ ty_con_binders_ty_binders' = foldr go ([], False) go (Bndr tv (NamedTCB vis)) (bndrs, _) = (Named (Bndr tv vis) : bndrs, True) go (Bndr tv (AnonTCB af)) (bndrs, n) - = (Anon af (unrestricted (tyVarKind tv)) : bndrs, n) + = (Anon af (tymult (tyVarKind tv)) : bndrs, n) {-# INLINE go #-} {-# INLINE ty_con_binders_ty_binders' #-} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/11802fc3cb9d1a9bfe84193ed7f58508389f839c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/11802fc3cb9d1a9bfe84193ed7f58508389f839c 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 Tue Nov 24 20:14:57 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 15:14:57 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Introduce canNC Message-ID: <5fbd69c18e464_86c113a5b2c589cf@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 803bbf04 by Richard Eisenberg at 2020-11-24T15:14:44-05:00 Introduce canNC - - - - - 3 changed files: - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcType.hs Changes: ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -92,32 +92,20 @@ last time through, so we can skip the classification step. canonicalize :: Ct -> TcS (StopOrContinue Ct) canonicalize (CNonCanonical { cc_ev = ev }) = {-# SCC "canNC" #-} - case classifyPredType pred of - ClassPred cls tys -> do traceTcS "canEvNC:cls" (ppr cls <+> ppr tys) - canClassNC ev cls tys - EqPred eq_rel ty1 ty2 -> do traceTcS "canEvNC:eq" (ppr ty1 $$ ppr ty2) - canEqNC ev eq_rel ty1 ty2 - IrredPred {} -> do traceTcS "canEvNC:irred" (ppr pred) - canIrred OtherCIS ev - ForAllPred tvs th p -> do traceTcS "canEvNC:forall" (ppr pred) - canForAllNC ev tvs th p - where - pred = ctEvPred ev + canNC ev canonicalize (CQuantCan (QCI { qci_ev = ev, qci_pend_sc = pend_sc })) = canForAll ev pend_sc -canonicalize (CIrredCan { cc_ev = ev, cc_status = status }) - | EqPred eq_rel ty1 ty2 <- classifyPredType (ctEvPred ev) - = -- For insolubles (all of which are equalities), do /not/ rewrite the arguments +canonicalize (CIrredCan { cc_ev = ev }) + = canNC ev + -- Instead of rewriting the evidence before classifying, it's possible we + -- can make progress without the rewrite. Try this first. + -- For insolubles (all of which are equalities), do /not/ rewrite the arguments -- In #14350 doing so led entire-unnecessary and ridiculously large -- type function expansion. Instead, canEqNC just applies -- the substitution to the predicate, and may do decomposition; -- e.g. a ~ [a], where [G] a ~ [Int], can decompose - canEqNC ev eq_rel ty1 ty2 - - | otherwise - = canIrred status ev canonicalize (CDictCan { cc_ev = ev, cc_class = cls , cc_tyargs = xis, cc_pend_sc = pend_sc }) @@ -131,6 +119,20 @@ canonicalize (CEqCan { cc_ev = ev = {-# SCC "canEqLeafTyVarEq" #-} canEqNC ev eq_rel (canEqLHSType lhs) rhs +canNC :: CtEvidence -> TcS (StopOrContinue Ct) +canNC ev = + case classifyPredType pred of + ClassPred cls tys -> do traceTcS "canEvNC:cls" (ppr cls <+> ppr tys) + canClassNC ev cls tys + EqPred eq_rel ty1 ty2 -> do traceTcS "canEvNC:eq" (ppr ty1 $$ ppr ty2) + canEqNC ev eq_rel ty1 ty2 + IrredPred {} -> do traceTcS "canEvNC:irred" (ppr pred) + canIrred ev + ForAllPred tvs th p -> do traceTcS "canEvNC:forall" (ppr pred) + canForAllNC ev tvs th p + where + pred = ctEvPred ev + {- ************************************************************************ * * @@ -694,24 +696,24 @@ See also Note [Evidence for quantified constraints] in GHC.Core.Predicate. ************************************************************************ -} -canIrred :: CtIrredStatus -> CtEvidence -> TcS (StopOrContinue Ct) +canIrred :: CtEvidence -> TcS (StopOrContinue Ct) -- Precondition: ty not a tuple and no other evidence form -canIrred status ev +canIrred ev = do { let pred = ctEvPred ev ; traceTcS "can_pred" (text "IrredPred = " <+> ppr pred) ; (xi,co) <- rewrite ev pred -- co :: xi ~ pred ; rewriteEvidence ev xi co `andWhenContinue` \ new_ev -> do { -- Re-classify, in case rewriting has improved its shape - -- Code is like the CNonCanonical case of canonicalize, except + -- Code is like the canNC, except -- that the IrredPred branch stops work ; case classifyPredType (ctEvPred new_ev) of ClassPred cls tys -> canClassNC new_ev cls tys EqPred eq_rel ty1 ty2 -> canEqNC new_ev eq_rel ty1 ty2 - ForAllPred tvs th p -> do traceTcS "canEvNC:forall" (ppr pred) - canForAllNC ev tvs th p + ForAllPred {} -> pprPanic "rewriting revealed a ForAllTy" + (ppr ev) IrredPred {} -> continueWith $ - mkIrredCt status new_ev } } + mkIrredCt OtherCIS new_ev } } {- ********************************************************************* * * ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -1448,7 +1448,7 @@ data TcEvDest | HoleDest CoercionHole -- ^ fill in this hole with the evidence -- HoleDest is always used for type-equalities - -- See Note [Coercion holes] in "GHC.Core.TyCo.Rep" + -- See Note [Coercion holes] in GHC.Core.TyCo.Rep data CtEvidence = CtGiven -- Truly given, not depending on subgoals ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -83,7 +83,7 @@ module GHC.Tc.Utils.TcType ( isIntegerTy, isNaturalTy, isBoolTy, isUnitTy, isCharTy, isCallStackTy, isCallStackPred, isTauTy, isTauTyCon, tcIsTyVarTy, tcIsForAllTy, - isPredTy, isTyVarClassPred, isTyVarHead, isInsolubleOccursCheck, + isPredTy, isTyVarClassPred, isInsolubleOccursCheck, checkValidClsArgs, hasTyVarHead, isRigidTy, @@ -2136,18 +2136,6 @@ is_tc uniq ty = case tcSplitTyConApp_maybe ty of Just (tc, _) -> uniq == getUnique tc Nothing -> False --- | Does the given tyvar appear at the head of a chain of applications --- (a t1 ... tn) -isTyVarHead :: TcTyVar -> TcType -> Bool -isTyVarHead tv (TyVarTy tv') = tv == tv' -isTyVarHead tv (AppTy fun _) = isTyVarHead tv fun -isTyVarHead tv (CastTy ty _) = isTyVarHead tv ty -isTyVarHead _ (TyConApp {}) = False -isTyVarHead _ (LitTy {}) = False -isTyVarHead _ (ForAllTy {}) = False -isTyVarHead _ (FunTy {}) = False -isTyVarHead _ (CoercionTy {}) = False - {- Note [AppTy and ReprEq] ~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/803bbf04f5df6bb58f8cf05b74c82535184430fe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/803bbf04f5df6bb58f8cf05b74c82535184430fe 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 Tue Nov 24 20:23:55 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 15:23:55 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Remove isTyVarHead Message-ID: <5fbd6bdb9baae_86c111d4a00599ac@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 65a7815c by Richard Eisenberg at 2020-11-24T15:23:44-05:00 Remove isTyVarHead - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -1008,7 +1008,7 @@ now reduced to reflexivity. The solution here is to kick out representational inerts whenever the tyvar of a work item is "exposed", where exposed means being at the head of the top-level application chain (a t1 .. tn). See -TcType.isTyVarHead. This is encoded in (K3b). +is_can_eq_lhs_head. This is encoded in (K3b). Beware: if we make this test succeed too often, we kick out too much, and the solver might loop. Consider (#14363) @@ -1779,18 +1779,33 @@ kick_out_rewritable new_fr new_lhs -- (K2c) is guaranteed by the first guard of keep_eq kick_out_for_completeness -- (K3) and Note [K3: completeness of solving] - = case (eq_rel, new_lhs) of - (NomEq, _) -> rhs_ty `eqType` canEqLHSType new_lhs -- (K3a) - (ReprEq, TyVarLHS new_tv) -> isTyVarHead new_tv rhs_ty -- (K3b) - (ReprEq, TyFamLHS new_tf new_tf_args) -- (K3b) - | Just (rhs_tc, rhs_tc_args) <- tcSplitTyConApp_maybe rhs_ty - , tcEqTyConApps new_tf new_tf_args rhs_tc rhs_tc_args - -> True - | otherwise - -> False + = case eq_rel of + NomEq -> rhs_ty `eqType` canEqLHSType new_lhs -- (K3a) + ReprEq -> is_can_eq_lhs_head new_lhs rhs_ty -- (K3b) kick_out_eq ct = pprPanic "keep_eq" (ppr ct) + is_can_eq_lhs_head (TyVarLHS tv) = go + where + go (Rep.TyVarTy tv') = tv == tv' + go (Rep.AppTy fun _) = go fun + go (Rep.CastTy ty _) = go ty + go (Rep.TyConApp {}) = False + go (Rep.LitTy {}) = False + go (Rep.ForAllTy {}) = False + go (Rep.FunTy {}) = False + go (Rep.CoercionTy {}) = False + is_can_eq_lhs_head (TyFamLHS fun_tc fun_args) = go + where + go (Rep.TyVarTy {}) = False + go (Rep.AppTy {}) = False -- no TyConApp to the left of an AppTy + go (Rep.CastTy ty _) = go ty + go (Rep.TyConApp tc args) = tcEqTyConApps fun_tc fun_args tc args + go (Rep.LitTy {}) = False + go (Rep.ForAllTy {}) = False + go (Rep.FunTy {}) = False + go (Rep.CoercionTy {}) = False + kickOutAfterUnification :: TcTyVar -> TcS Int kickOutAfterUnification new_tv = do { ics <- getInertCans View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/65a7815c04574e49e62cc457d8476287366f62a4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/65a7815c04574e49e62cc457d8476287366f62a4 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 Tue Nov 24 20:34:17 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 24 Nov 2020 15:34:17 -0500 Subject: [Git][ghc/ghc][wip/T18894] Unleash exported bindings later Message-ID: <5fbd6e49577e_86cfcf8f286097d@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: 7e4a746b by Sebastian Graf at 2020-11-24T21:34:11+01:00 Unleash exported bindings later - - - - - 1 changed file: - compiler/GHC/Core/Opt/DmdAnal.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -70,24 +70,26 @@ dmdAnalProgram opts fam_envs rules binds = binds_plus_dmds where env = emptyAnalEnv opts fam_envs rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules - binds_plus_dmds = snd $ go env nopDmdType binds + binds_plus_dmds = snd $ go env binds - go _ dmd_ty [] = (dmd_ty, []) - go env dmd_ty (b:bs) = case b of + go _ [] = (nopDmdType, []) + go env (b:bs) = case b of NonRec id rhs | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel NonRecursive env topSubDmd id rhs - , (dmd_ty', bs') <- go env' (add_exported_use env' dmd_ty id') bs - , (dmd_ty'', id_dmd) <- findBndrDmd env' False (dmd_ty' `addLazyFVs` lazy_fvs) id' + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_use env' dmd_ty' id' `addLazyFVs` lazy_fvs + , (dmd_ty''', id_dmd) <- findBndrDmd env' False dmd_ty'' id' , let id'' = annotate_id_dmd id' id_dmd - -> (dmd_ty'', NonRec id'' rhs' : bs') + -> (dmd_ty''', NonRec id'' rhs' : bs') Rec pairs | (env', lazy_fvs, pairs') <- dmdFix TopLevel env topSubDmd pairs , let ids' = map fst pairs' - , (dmd_ty', bs') <- go env' (add_exported_uses env' dmd_ty ids') bs - , (dmd_ty'', id_dmds) <- findBndrsDmds env' (dmd_ty' `addLazyFVs` lazy_fvs) ids' + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_uses env' dmd_ty' ids' `addLazyFVs` lazy_fvs + , (dmd_ty''', id_dmds) <- findBndrsDmds env' dmd_ty'' ids' , let ids'' = zipWith annotate_id_dmd ids' id_dmds , let pairs'' = zipWith (\id'' (_, rhs') -> (id'', rhs')) ids'' pairs' - -> (dmd_ty'', Rec pairs'' : bs') + -> (dmd_ty''', Rec pairs'' : bs') annotate_id_dmd id dmd | isInterestingTopLevelFn id, not (id `elemVarSet` rule_fvs) @@ -98,7 +100,7 @@ dmdAnalProgram opts fam_envs rules binds = binds_plus_dmds add_exported_uses env = foldl' (add_exported_use env) add_exported_use env dmd_ty id - | isExportedId id || not (isInterestingTopLevelFn id) + | isExportedId id = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) | otherwise = dmd_ty View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7e4a746b507f973f56f4a5a012fdf6ee60978725 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7e4a746b507f973f56f4a5a012fdf6ee60978725 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 Tue Nov 24 20:55:58 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 15:55:58 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 2 commits: Accommodate #18987 Message-ID: <5fbd735e4261b_86c8b847fc632f7@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 99b6f9fa by Richard Eisenberg at 2020-11-24T15:54:15-05:00 Accommodate #18987 - - - - - 6ae2ad19 by Richard Eisenberg at 2020-11-24T15:55:45-05:00 let-bound skolems - - - - - 2 changed files: - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Monad.hs Changes: ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -710,8 +710,11 @@ canIrred ev ; case classifyPredType (ctEvPred new_ev) of ClassPred cls tys -> canClassNC new_ev cls tys EqPred eq_rel ty1 ty2 -> canEqNC new_ev eq_rel ty1 ty2 - ForAllPred {} -> pprPanic "rewriting revealed a ForAllTy" - (ppr ev) + ForAllPred tvs th p -> -- this is highly suspect; Quick Look + -- should never leave a meta-var filled + -- in with a polytype. This is #18987. + do traceTcS "canEvNC:forall" (ppr pred) + canForAllNC ev tvs th p IrredPred {} -> continueWith $ mkIrredCt OtherCIS new_ev } } ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -2146,7 +2146,7 @@ getHasGivenEqs tclvl check_local_given_tv_eq :: Ct -> HasGivenEqs check_local_given_tv_eq (CEqCan { cc_lhs = TyVarLHS tv, cc_ev = ev}) | given_here ev - = if is_outer_var tv then MaybeGivenEqs else LocalGivenEqs + = if is_outer_var tv then MaybeGivenEqs else NoGivenEqs -- See Note [Let-bound skolems] | otherwise = NoGivenEqs View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65a7815c04574e49e62cc457d8476287366f62a4...6ae2ad19e581fb0ad987c6b84ac291bd138f7991 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65a7815c04574e49e62cc457d8476287366f62a4...6ae2ad19e581fb0ad987c6b84ac291bd138f7991 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 Tue Nov 24 20:58:04 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Tue, 24 Nov 2020 15:58:04 -0500 Subject: [Git][ghc/ghc][wip/T18599] Implement toHie for new syntax via desugared forms Message-ID: <5fbd73dce6824_86c7d592406427b@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 2ca0d854 by Shayne Fletcher at 2020-11-24T15:57:33-05:00 Implement toHie for new syntax via desugared forms - - - - - 1 changed file: - compiler/GHC/Iface/Ext/Ast.hs Changes: ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,10 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] - GetField _ expr _ _ -> - [ toHie expr - ] - Projection _ _ _ -> [] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ca0d8543dae3853d15a8d0b5c4e586b058d7b4c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ca0d8543dae3853d15a8d0b5c4e586b058d7b4c 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 Tue Nov 24 22:03:54 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Tue, 24 Nov 2020 17:03:54 -0500 Subject: [Git][ghc/ghc][wip/T18894] Unleash exported bindings later Message-ID: <5fbd834acf06_86cfcf8f2869366@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: 72c5e65b by Sebastian Graf at 2020-11-24T23:03:46+01:00 Unleash exported bindings later - - - - - 1 changed file: - compiler/GHC/Core/Opt/DmdAnal.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -66,42 +66,43 @@ data DmdAnalOpts = DmdAnalOpts -- Note: use `seqBinds` on the result to avoid leaks due to lazyness (cf Note -- [Stamp out space leaks in demand analysis]) dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> [CoreRule] -> CoreProgram -> CoreProgram -dmdAnalProgram opts fam_envs rules binds = binds_plus_dmds +dmdAnalProgram opts fam_envs rules binds = snd $ go (emptyAnalEnv opts fam_envs) binds where - env = emptyAnalEnv opts fam_envs - rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules - binds_plus_dmds = snd $ go env nopDmdType binds - - go _ dmd_ty [] = (dmd_ty, []) - go env dmd_ty (b:bs) = case b of + go _ [] = (nopDmdType, []) + go env (b:bs) = case b of NonRec id rhs | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel NonRecursive env topSubDmd id rhs - , (dmd_ty', bs') <- go env' (add_exported_use env' dmd_ty id') bs - , (dmd_ty'', id_dmd) <- findBndrDmd env' False (dmd_ty' `addLazyFVs` lazy_fvs) id' + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_use env' dmd_ty' id' `addLazyFVs` lazy_fvs + , (dmd_ty''', id_dmd) <- findBndrDmd env' False dmd_ty'' id' , let id'' = annotate_id_dmd id' id_dmd - -> (dmd_ty'', NonRec id'' rhs' : bs') + -> (dmd_ty''', NonRec id'' rhs' : bs') Rec pairs | (env', lazy_fvs, pairs') <- dmdFix TopLevel env topSubDmd pairs , let ids' = map fst pairs' - , (dmd_ty', bs') <- go env' (add_exported_uses env' dmd_ty ids') bs - , (dmd_ty'', id_dmds) <- findBndrsDmds env' (dmd_ty' `addLazyFVs` lazy_fvs) ids' + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_uses env' dmd_ty' ids' `addLazyFVs` lazy_fvs + , (dmd_ty''', id_dmds) <- findBndrsDmds env' dmd_ty'' ids' , let ids'' = zipWith annotate_id_dmd ids' id_dmds , let pairs'' = zipWith (\id'' (_, rhs') -> (id'', rhs')) ids'' pairs' - -> (dmd_ty'', Rec pairs'' : bs') + -> (dmd_ty''', Rec pairs'' : bs') annotate_id_dmd id dmd - | isInterestingTopLevelFn id, not (id `elemVarSet` rule_fvs) - -- See Note [Absence analysis for stable unfoldings and RULES] + | isInterestingTopLevelFn id = id `setIdDemandInfo` dmd | otherwise = id `setIdDemandInfo` topDmd add_exported_uses env = foldl' (add_exported_use env) add_exported_use env dmd_ty id - | isExportedId id || not (isInterestingTopLevelFn id) + | isExportedId id || elemVarSet id rule_fvs + -- See Note [Absence analysis for stable unfoldings and RULES] = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) | otherwise = dmd_ty + rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules + + {- Note [Stamp out space leaks in demand analysis] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The demand analysis pass outputs a new copy of the Core program in View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/72c5e65bb8b5e37394cdbf26565a2a13d1ebe402 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/72c5e65bb8b5e37394cdbf26565a2a13d1ebe402 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 Tue Nov 24 22:23:36 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 17:23:36 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fbd87e88456b_86c879fa9c7005@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 2bdc4c8f by Moritz Angermann at 2020-11-24T17:23:28-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2bdc4c8ff9dcf17cc80ee609fb056fcd5459275e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2bdc4c8ff9dcf17cc80ee609fb056fcd5459275e 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 Tue Nov 24 22:28:43 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Tue, 24 Nov 2020 17:28:43 -0500 Subject: [Git][ghc/ghc][wip/amg/fieldselectors] 3 commits: Exclude NoFieldSelectors GREs from similarNameSuggestions Message-ID: <5fbd891b34110_86cfd752bc7146b@gitlab.mail> Adam Gundry pushed to branch wip/amg/fieldselectors at Glasgow Haskell Compiler / GHC Commits: 4dea2af5 by Adam Gundry at 2020-11-24T22:08:06+00:00 Exclude NoFieldSelectors GREs from similarNameSuggestions - - - - - 8904a2a7 by Adam Gundry at 2020-11-24T22:25:15+00:00 Hackily correct for T11941 - - - - - 461c9ba8 by Adam Gundry at 2020-11-24T22:28:35+00:00 Minor diff cleanup - - - - - 4 changed files: - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Unbound.hs - testsuite/tests/th/T11941.stderr - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Rename/Pat.hs ===================================== @@ -751,13 +751,16 @@ rnHsRecUpdFields flds ; sel <- setSrcSpan loc $ -- Defer renaming of overloaded fields to the typechecker -- See Note [Disambiguating record fields] in GHC.Tc.Gen.Head - do { mb <- lookupGlobalOccRn_overloaded_sel overload_ok lbl - ; case mb of - Nothing -> - do { addErr - (unknownSubordinateErr doc lbl) - ; return Nothing } - Just r -> return $ Just r } + -- AMG TODO: not clear why we need this test, but T11941 fails if we don't + if overload_ok == DuplicateRecordFields + then do { mb <- lookupGlobalOccRn_overloaded_sel overload_ok lbl + ; case mb of + Nothing -> + do { addErr + (unknownSubordinateErr doc lbl) + ; return Nothing } + Just r -> return $ Just r } + else fmap (Just . LookupOccRnUnique) $ lookupGlobalOccRn lbl ; arg' <- if pun then do { checkErr pun_ok (badPun (L loc lbl)) -- Discard any module qualifier (#11662) ===================================== compiler/GHC/Rename/Unbound.hs ===================================== @@ -193,6 +193,7 @@ similarNameSuggestions where_look dflags global_env | tried_is_qual = [ (rdr_qual, (rdr_qual, how)) | gre <- globalRdrEnvElts global_env , isGreOk where_look gre + , not (isNoFieldSelectorGRE gre) , let occ = greOccName gre , correct_name_space occ , (mod, how) <- qualsInScope gre @@ -201,6 +202,7 @@ similarNameSuggestions where_look dflags global_env | otherwise = [ (rdr_unqual, pair) | gre <- globalRdrEnvElts global_env , isGreOk where_look gre + , not (isNoFieldSelectorGRE gre) , let occ = greOccName gre rdr_unqual = mkRdrUnqual occ , correct_name_space occ ===================================== testsuite/tests/th/T11941.stderr ===================================== @@ -1,3 +1,6 @@ T11941.hs:7:30: error: - ‘getFrst’ is not a (visible) constructor field name \ No newline at end of file + Not in scope: ‘getFrst’ + Perhaps you meant one of these: + ‘getFirst’ (imported from Data.Monoid), + ‘getLast’ (imported from Data.Monoid) ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,3 +728,4 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/59a0c52a763690a5ac94e3ff4a2e1525cb5fa293...461c9ba829fd4090d7aa11366cc908f1b6a42cb3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/59a0c52a763690a5ac94e3ff4a2e1525cb5fa293...461c9ba829fd4090d7aa11366cc908f1b6a42cb3 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 Tue Nov 24 22:51:11 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 17:51:11 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Comment that intermediate cached values do not help Message-ID: <5fbd8e5f2f176_86c113a5b2c7313d@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 2b7af3cd by Richard Eisenberg at 2020-11-24T22:50:54+00:00 Comment that intermediate cached values do not help - - - - - 1 changed file: - compiler/GHC/Tc/Solver/Rewrite.hs Changes: ===================================== compiler/GHC/Tc/Solver/Rewrite.hs ===================================== @@ -832,6 +832,9 @@ rewrite_exact_fam_app tc tys do { result3 <- try_to_reduce tc xis ; case result3 of Just (co, xi) -> finish True (homogenise xi co) + -- We could add an item to the cache relating F xis to the final result, + -- where xis is the result of STEP 3. But testing showed that this + -- leads to 10-20% regressions in the T9872x tests, so we don't do it. Nothing -> -- we have made no progress at all: STEP 7. return (homogenise reduced (mkTcReflCo role reduced)) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2b7af3cd500bb587736ff455645fb4cd5ff986f3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2b7af3cd500bb587736ff455645fb4cd5ff986f3 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 Wed Nov 25 00:31:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 19:31:56 -0500 Subject: [Git][ghc/ghc][wip/angerman/arm64] 324 commits: Make the parser module less dependent on DynFlags Message-ID: <5fbda5fc68bb4_86c7d5924095028@gitlab.mail> Ben Gamari pushed to branch wip/angerman/arm64 at Glasgow Haskell Compiler / GHC Commits: 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.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/Node.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a1fa55fadcb7a729a949aa434ea527f1690ac0d...2ed3e6c0f179c06828712832d1176519cdfa82a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a1fa55fadcb7a729a949aa434ea527f1690ac0d...2ed3e6c0f179c06828712832d1176519cdfa82a6 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 Wed Nov 25 00:33:19 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 19:33:19 -0500 Subject: [Git][ghc/ghc][wip/angerman/arm64] [macOS] support for arm64 Message-ID: <5fbda64f86007_86ce89fc5c96721@gitlab.mail> Ben Gamari pushed to branch wip/angerman/arm64 at Glasgow Haskell Compiler / GHC Commits: 8a1fa55f by Moritz Angermann at 2020-10-02T11:05:16+08:00 [macOS] support for arm64 Adding basic changes to support arm64-apple-darwin - - - - - 8 changed files: - aclocal.m4 - config.sub - includes/rts/storage/GC.h - llvm-targets - rts/Adjustor.c - rts/StgCRun.c - rts/sm/Storage.c - utils/llvm-targets/gen-data-layout.sh Changes: ===================================== aclocal.m4 ===================================== @@ -1976,7 +1976,7 @@ AC_MSG_CHECKING(for path to top of build tree) # `libraries/base/System/Info.hs`'s documentation. AC_DEFUN([GHC_CONVERT_CPU],[ case "$1" in - aarch64*) + aarch64*|arm64*) $2="aarch64" ;; alpha*) ===================================== config.sub ===================================== @@ -1,8 +1,8 @@ #! /bin/sh # Configuration validation subroutine script. -# Copyright 1992-2019 Free Software Foundation, Inc. +# Copyright 1992-2020 Free Software Foundation, Inc. -timestamp='2019-01-05' +timestamp='2020-09-08' # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by @@ -67,7 +67,7 @@ Report bugs and patches to ." version="\ GNU config.sub ($timestamp) -Copyright 1992-2019 Free Software Foundation, Inc. +Copyright 1992-2020 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." @@ -124,28 +124,27 @@ case $1 in ;; *-*-*-*) basic_machine=$field1-$field2 - os=$field3-$field4 + basic_os=$field3-$field4 ;; *-*-*) # Ambiguous whether COMPANY is present, or skipped and KERNEL-OS is two # parts maybe_os=$field2-$field3 case $maybe_os in - nto-qnx* | linux-gnu* | linux-android* | linux-dietlibc \ - | linux-newlib* | linux-musl* | linux-uclibc* | uclinux-uclibc* \ + nto-qnx* | linux-* | uclinux-uclibc* \ | uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* \ | netbsd*-eabi* | kopensolaris*-gnu* | cloudabi*-eabi* \ | storm-chaos* | os2-emx* | rtmk-nova*) basic_machine=$field1 - os=$maybe_os + basic_os=$maybe_os ;; android-linux) basic_machine=$field1-unknown - os=linux-android + basic_os=linux-android ;; *) basic_machine=$field1-$field2 - os=$field3 + basic_os=$field3 ;; esac ;; @@ -154,7 +153,7 @@ case $1 in case $field1-$field2 in decstation-3100) basic_machine=mips-dec - os= + basic_os= ;; *-*) # Second component is usually, but not always the OS @@ -162,7 +161,7 @@ case $1 in # Prevent following clause from handling this valid os sun*os*) basic_machine=$field1 - os=$field2 + basic_os=$field2 ;; # Manufacturers dec* | mips* | sequent* | encore* | pc533* | sgi* | sony* \ @@ -175,11 +174,11 @@ case $1 in | microblaze* | sim | cisco \ | oki | wec | wrs | winbond) basic_machine=$field1-$field2 - os= + basic_os= ;; *) basic_machine=$field1 - os=$field2 + basic_os=$field2 ;; esac ;; @@ -191,450 +190,451 @@ case $1 in case $field1 in 386bsd) basic_machine=i386-pc - os=bsd + basic_os=bsd ;; a29khif) basic_machine=a29k-amd - os=udi + basic_os=udi ;; adobe68k) basic_machine=m68010-adobe - os=scout + basic_os=scout ;; alliant) basic_machine=fx80-alliant - os= + basic_os= ;; altos | altos3068) basic_machine=m68k-altos - os= + basic_os= ;; am29k) basic_machine=a29k-none - os=bsd + basic_os=bsd ;; amdahl) basic_machine=580-amdahl - os=sysv + basic_os=sysv ;; amiga) basic_machine=m68k-unknown - os= + basic_os= ;; amigaos | amigados) basic_machine=m68k-unknown - os=amigaos + basic_os=amigaos ;; amigaunix | amix) basic_machine=m68k-unknown - os=sysv4 + basic_os=sysv4 ;; apollo68) basic_machine=m68k-apollo - os=sysv + basic_os=sysv ;; apollo68bsd) basic_machine=m68k-apollo - os=bsd + basic_os=bsd ;; aros) basic_machine=i386-pc - os=aros + basic_os=aros ;; aux) basic_machine=m68k-apple - os=aux + basic_os=aux ;; balance) basic_machine=ns32k-sequent - os=dynix + basic_os=dynix ;; blackfin) basic_machine=bfin-unknown - os=linux + basic_os=linux ;; cegcc) basic_machine=arm-unknown - os=cegcc + basic_os=cegcc ;; convex-c1) basic_machine=c1-convex - os=bsd + basic_os=bsd ;; convex-c2) basic_machine=c2-convex - os=bsd + basic_os=bsd ;; convex-c32) basic_machine=c32-convex - os=bsd + basic_os=bsd ;; convex-c34) basic_machine=c34-convex - os=bsd + basic_os=bsd ;; convex-c38) basic_machine=c38-convex - os=bsd + basic_os=bsd ;; cray) basic_machine=j90-cray - os=unicos + basic_os=unicos ;; crds | unos) basic_machine=m68k-crds - os= + basic_os= ;; da30) basic_machine=m68k-da30 - os= + basic_os= ;; decstation | pmax | pmin | dec3100 | decstatn) basic_machine=mips-dec - os= + basic_os= ;; delta88) basic_machine=m88k-motorola - os=sysv3 + basic_os=sysv3 ;; dicos) basic_machine=i686-pc - os=dicos + basic_os=dicos ;; djgpp) basic_machine=i586-pc - os=msdosdjgpp + basic_os=msdosdjgpp ;; ebmon29k) basic_machine=a29k-amd - os=ebmon + basic_os=ebmon ;; es1800 | OSE68k | ose68k | ose | OSE) basic_machine=m68k-ericsson - os=ose + basic_os=ose ;; gmicro) basic_machine=tron-gmicro - os=sysv + basic_os=sysv ;; go32) basic_machine=i386-pc - os=go32 + basic_os=go32 ;; h8300hms) basic_machine=h8300-hitachi - os=hms + basic_os=hms ;; h8300xray) basic_machine=h8300-hitachi - os=xray + basic_os=xray ;; h8500hms) basic_machine=h8500-hitachi - os=hms + basic_os=hms ;; harris) basic_machine=m88k-harris - os=sysv3 + basic_os=sysv3 ;; - hp300) + hp300 | hp300hpux) basic_machine=m68k-hp + basic_os=hpux ;; hp300bsd) basic_machine=m68k-hp - os=bsd - ;; - hp300hpux) - basic_machine=m68k-hp - os=hpux + basic_os=bsd ;; hppaosf) basic_machine=hppa1.1-hp - os=osf + basic_os=osf ;; hppro) basic_machine=hppa1.1-hp - os=proelf + basic_os=proelf ;; i386mach) basic_machine=i386-mach - os=mach - ;; - vsta) - basic_machine=i386-pc - os=vsta + basic_os=mach ;; isi68 | isi) basic_machine=m68k-isi - os=sysv + basic_os=sysv ;; m68knommu) basic_machine=m68k-unknown - os=linux + basic_os=linux ;; magnum | m3230) basic_machine=mips-mips - os=sysv + basic_os=sysv ;; merlin) basic_machine=ns32k-utek - os=sysv + basic_os=sysv ;; mingw64) basic_machine=x86_64-pc - os=mingw64 + basic_os=mingw64 ;; mingw32) basic_machine=i686-pc - os=mingw32 + basic_os=mingw32 ;; mingw32ce) basic_machine=arm-unknown - os=mingw32ce + basic_os=mingw32ce ;; monitor) basic_machine=m68k-rom68k - os=coff + basic_os=coff ;; morphos) basic_machine=powerpc-unknown - os=morphos + basic_os=morphos ;; moxiebox) basic_machine=moxie-unknown - os=moxiebox + basic_os=moxiebox ;; msdos) basic_machine=i386-pc - os=msdos + basic_os=msdos ;; msys) basic_machine=i686-pc - os=msys + basic_os=msys ;; mvs) basic_machine=i370-ibm - os=mvs + basic_os=mvs ;; nacl) basic_machine=le32-unknown - os=nacl + basic_os=nacl ;; ncr3000) basic_machine=i486-ncr - os=sysv4 + basic_os=sysv4 ;; netbsd386) basic_machine=i386-pc - os=netbsd + basic_os=netbsd ;; netwinder) basic_machine=armv4l-rebel - os=linux + basic_os=linux ;; news | news700 | news800 | news900) basic_machine=m68k-sony - os=newsos + basic_os=newsos ;; news1000) basic_machine=m68030-sony - os=newsos + basic_os=newsos ;; necv70) basic_machine=v70-nec - os=sysv + basic_os=sysv ;; nh3000) basic_machine=m68k-harris - os=cxux + basic_os=cxux ;; nh[45]000) basic_machine=m88k-harris - os=cxux + basic_os=cxux ;; nindy960) basic_machine=i960-intel - os=nindy + basic_os=nindy ;; mon960) basic_machine=i960-intel - os=mon960 + basic_os=mon960 ;; nonstopux) basic_machine=mips-compaq - os=nonstopux + basic_os=nonstopux ;; os400) basic_machine=powerpc-ibm - os=os400 + basic_os=os400 ;; OSE68000 | ose68000) basic_machine=m68000-ericsson - os=ose + basic_os=ose ;; os68k) basic_machine=m68k-none - os=os68k + basic_os=os68k ;; paragon) basic_machine=i860-intel - os=osf + basic_os=osf ;; parisc) basic_machine=hppa-unknown - os=linux + basic_os=linux + ;; + psp) + basic_machine=mipsallegrexel-sony + basic_os=psp ;; pw32) basic_machine=i586-unknown - os=pw32 + basic_os=pw32 ;; rdos | rdos64) basic_machine=x86_64-pc - os=rdos + basic_os=rdos ;; rdos32) basic_machine=i386-pc - os=rdos + basic_os=rdos ;; rom68k) basic_machine=m68k-rom68k - os=coff + basic_os=coff ;; sa29200) basic_machine=a29k-amd - os=udi + basic_os=udi ;; sei) basic_machine=mips-sei - os=seiux + basic_os=seiux ;; sequent) basic_machine=i386-sequent - os= + basic_os= ;; sps7) basic_machine=m68k-bull - os=sysv2 + basic_os=sysv2 ;; st2000) basic_machine=m68k-tandem - os= + basic_os= ;; stratus) basic_machine=i860-stratus - os=sysv4 + basic_os=sysv4 ;; sun2) basic_machine=m68000-sun - os= + basic_os= ;; sun2os3) basic_machine=m68000-sun - os=sunos3 + basic_os=sunos3 ;; sun2os4) basic_machine=m68000-sun - os=sunos4 + basic_os=sunos4 ;; sun3) basic_machine=m68k-sun - os= + basic_os= ;; sun3os3) basic_machine=m68k-sun - os=sunos3 + basic_os=sunos3 ;; sun3os4) basic_machine=m68k-sun - os=sunos4 + basic_os=sunos4 ;; sun4) basic_machine=sparc-sun - os= + basic_os= ;; sun4os3) basic_machine=sparc-sun - os=sunos3 + basic_os=sunos3 ;; sun4os4) basic_machine=sparc-sun - os=sunos4 + basic_os=sunos4 ;; sun4sol2) basic_machine=sparc-sun - os=solaris2 + basic_os=solaris2 ;; sun386 | sun386i | roadrunner) basic_machine=i386-sun - os= + basic_os= ;; sv1) basic_machine=sv1-cray - os=unicos + basic_os=unicos ;; symmetry) basic_machine=i386-sequent - os=dynix + basic_os=dynix ;; t3e) basic_machine=alphaev5-cray - os=unicos + basic_os=unicos ;; t90) basic_machine=t90-cray - os=unicos + basic_os=unicos ;; toad1) basic_machine=pdp10-xkl - os=tops20 + basic_os=tops20 ;; tpf) basic_machine=s390x-ibm - os=tpf + basic_os=tpf ;; udi29k) basic_machine=a29k-amd - os=udi + basic_os=udi ;; ultra3) basic_machine=a29k-nyu - os=sym1 + basic_os=sym1 ;; v810 | necv810) basic_machine=v810-nec - os=none + basic_os=none ;; vaxv) basic_machine=vax-dec - os=sysv + basic_os=sysv ;; vms) basic_machine=vax-dec - os=vms + basic_os=vms + ;; + vsta) + basic_machine=i386-pc + basic_os=vsta ;; vxworks960) basic_machine=i960-wrs - os=vxworks + basic_os=vxworks ;; vxworks68) basic_machine=m68k-wrs - os=vxworks + basic_os=vxworks ;; vxworks29k) basic_machine=a29k-wrs - os=vxworks + basic_os=vxworks ;; xbox) basic_machine=i686-pc - os=mingw32 + basic_os=mingw32 ;; ymp) basic_machine=ymp-cray - os=unicos + basic_os=unicos ;; *) basic_machine=$1 - os= + basic_os= ;; esac ;; @@ -686,17 +686,17 @@ case $basic_machine in bluegene*) cpu=powerpc vendor=ibm - os=cnk + basic_os=cnk ;; decsystem10* | dec10*) cpu=pdp10 vendor=dec - os=tops10 + basic_os=tops10 ;; decsystem20* | dec20*) cpu=pdp10 vendor=dec - os=tops20 + basic_os=tops20 ;; delta | 3300 | motorola-3300 | motorola-delta \ | 3300-motorola | delta-motorola) @@ -706,7 +706,7 @@ case $basic_machine in dpx2*) cpu=m68k vendor=bull - os=sysv3 + basic_os=sysv3 ;; encore | umax | mmax) cpu=ns32k @@ -715,7 +715,7 @@ case $basic_machine in elxsi) cpu=elxsi vendor=elxsi - os=${os:-bsd} + basic_os=${basic_os:-bsd} ;; fx2800) cpu=i860 @@ -728,7 +728,7 @@ case $basic_machine in h3050r* | hiux*) cpu=hppa1.1 vendor=hitachi - os=hiuxwe2 + basic_os=hiuxwe2 ;; hp3k9[0-9][0-9] | hp9[0-9][0-9]) cpu=hppa1.0 @@ -771,36 +771,36 @@ case $basic_machine in i*86v32) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv32 + basic_os=sysv32 ;; i*86v4*) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv4 + basic_os=sysv4 ;; i*86v) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=sysv + basic_os=sysv ;; i*86sol2) cpu=`echo "$1" | sed -e 's/86.*/86/'` vendor=pc - os=solaris2 + basic_os=solaris2 ;; j90 | j90-cray) cpu=j90 vendor=cray - os=${os:-unicos} + basic_os=${basic_os:-unicos} ;; iris | iris4d) cpu=mips vendor=sgi - case $os in + case $basic_os in irix*) ;; *) - os=irix4 + basic_os=irix4 ;; esac ;; @@ -811,26 +811,26 @@ case $basic_machine in *mint | mint[0-9]* | *MiNT | *MiNT[0-9]*) cpu=m68k vendor=atari - os=mint + basic_os=mint ;; news-3600 | risc-news) cpu=mips vendor=sony - os=newsos + basic_os=newsos ;; next | m*-next) cpu=m68k vendor=next - case $os in + case $basic_os in openstep*) ;; nextstep*) ;; ns2*) - os=nextstep2 + basic_os=nextstep2 ;; *) - os=nextstep3 + basic_os=nextstep3 ;; esac ;; @@ -841,12 +841,12 @@ case $basic_machine in op50n-* | op60c-*) cpu=hppa1.1 vendor=oki - os=proelf + basic_os=proelf ;; pa-hitachi) cpu=hppa1.1 vendor=hitachi - os=hiuxwe2 + basic_os=hiuxwe2 ;; pbd) cpu=sparc @@ -883,12 +883,12 @@ case $basic_machine in sde) cpu=mipsisa32 vendor=sde - os=${os:-elf} + basic_os=${basic_os:-elf} ;; simso-wrs) cpu=sparclite vendor=wrs - os=vxworks + basic_os=vxworks ;; tower | tower-32) cpu=m68k @@ -905,7 +905,7 @@ case $basic_machine in w89k-*) cpu=hppa1.1 vendor=winbond - os=proelf + basic_os=proelf ;; none) cpu=none @@ -958,11 +958,11 @@ case $cpu-$vendor in # some cases the only manufacturer, in others, it is the most popular. craynv-unknown) vendor=cray - os=${os:-unicosmp} + basic_os=${basic_os:-unicosmp} ;; c90-unknown | c90-cray) vendor=cray - os=${os:-unicos} + basic_os=${Basic_os:-unicos} ;; fx80-unknown) vendor=alliant @@ -1006,7 +1006,7 @@ case $cpu-$vendor in dpx20-unknown | dpx20-bull) cpu=rs6000 vendor=bull - os=${os:-bosx} + basic_os=${basic_os:-bosx} ;; # Here we normalize CPU types irrespective of the vendor @@ -1015,7 +1015,7 @@ case $cpu-$vendor in ;; blackfin-*) cpu=bfin - os=linux + basic_os=linux ;; c54x-*) cpu=tic54x @@ -1028,7 +1028,7 @@ case $cpu-$vendor in ;; e500v[12]-*) cpu=powerpc - os=$os"spe" + basic_os=${basic_os}"spe" ;; mips3*-*) cpu=mips64 @@ -1038,7 +1038,7 @@ case $cpu-$vendor in ;; m68knommu-*) cpu=m68k - os=linux + basic_os=linux ;; m9s12z-* | m68hcs12z-* | hcs12z-* | s12z-*) cpu=s12z @@ -1048,7 +1048,7 @@ case $cpu-$vendor in ;; parisc-*) cpu=hppa - os=linux + basic_os=linux ;; pentium-* | p5-* | k5-* | k6-* | nexgen-* | viac3-*) cpu=i586 @@ -1104,11 +1104,14 @@ case $cpu-$vendor in xscale-* | xscalee[bl]-*) cpu=`echo "$cpu" | sed 's/^xscale/arm/'` ;; + arm64-*) + cpu=aarch64 + ;; # Recognize the canonical CPU Types that limit and/or modify the # company names they are paired with. cr16-*) - os=${os:-elf} + basic_os=${basic_os:-elf} ;; crisv32-* | etraxfs*-*) cpu=crisv32 @@ -1119,7 +1122,7 @@ case $cpu-$vendor in vendor=axis ;; crx-*) - os=${os:-elf} + basic_os=${basic_os:-elf} ;; neo-tandem) cpu=neo @@ -1141,16 +1144,12 @@ case $cpu-$vendor in cpu=nsx vendor=tandem ;; - s390-*) - cpu=s390 - vendor=ibm - ;; - s390x-*) - cpu=s390x - vendor=ibm + mipsallegrexel-sony) + cpu=mipsallegrexel + vendor=sony ;; tile*-*) - os=${os:-linux-gnu} + basic_os=${basic_os:-linux-gnu} ;; *) @@ -1167,12 +1166,12 @@ case $cpu-$vendor in | am33_2.0 \ | amdgcn \ | arc | arceb \ - | arm | arm[lb]e | arme[lb] | armv* \ + | arm | arm[lb]e | arme[lb] | armv* \ | avr | avr32 \ | asmjs \ | ba \ | be32 | be64 \ - | bfin | bs2000 \ + | bfin | bpf | bs2000 \ | c[123]* | c30 | [cjt]90 | c4x \ | c8051 | clipper | craynv | csky | cydra \ | d10v | d30v | dlx | dsp16xx \ @@ -1232,6 +1231,7 @@ case $cpu-$vendor in | pyramid \ | riscv | riscv32 | riscv64 \ | rl78 | romp | rs6000 | rx \ + | s390 | s390x \ | score \ | sh | shl \ | sh[1234] | sh[24]a | sh[24]ae[lb] | sh[23]e | she[lb] | sh[lb]e \ @@ -1278,8 +1278,43 @@ esac # Decode manufacturer-specific aliases for certain operating systems. -if [ x$os != x ] +if test x$basic_os != x then + +# First recognize some ad-hoc caes, or perhaps split kernel-os, or else just +# set os. +case $basic_os in + gnu/linux*) + kernel=linux + os=`echo $basic_os | sed -e 's|gnu/linux|gnu|'` + ;; + nto-qnx*) + kernel=nto + os=`echo $basic_os | sed -e 's|nto-qnx|qnx|'` + ;; + *-*) + # shellcheck disable=SC2162 + IFS="-" read kernel os <&2 - exit 1 + # No normalization, but not necessarily accepted, that comes below. ;; esac + else # Here we handle the default operating systems that come with various machines. @@ -1533,6 +1493,7 @@ else # will signal an error saying that MANUFACTURER isn't an operating # system, and we'll never get to this point. +kernel= case $cpu-$vendor in score-*) os=elf @@ -1544,7 +1505,8 @@ case $cpu-$vendor in os=riscix1.2 ;; arm*-rebel) - os=linux + kernel=linux + os=gnu ;; arm*-semi) os=aout @@ -1710,84 +1672,169 @@ case $cpu-$vendor in os=none ;; esac + fi +# Now, validate our (potentially fixed-up) OS. +case $os in + # Sometimes we do "kernel-abi", so those need to count as OSes. + musl* | newlib* | uclibc*) + ;; + # Likewise for "kernel-libc" + eabi | eabihf | gnueabi | gnueabihf) + ;; + # Now accept the basic system types. + # The portable systems comes first. + # Each alternative MUST end in a * to match a version number. + gnu* | android* | bsd* | mach* | minix* | genix* | ultrix* | irix* \ + | *vms* | esix* | aix* | cnk* | sunos | sunos[34]* \ + | hpux* | unos* | osf* | luna* | dgux* | auroraux* | solaris* \ + | sym* | plan9* | psp* | sim* | xray* | os68k* | v88r* \ + | hiux* | abug | nacl* | netware* | windows* \ + | os9* | macos* | osx* | ios* \ + | mpw* | magic* | mmixware* | mon960* | lnews* \ + | amigaos* | amigados* | msdos* | newsos* | unicos* | aof* \ + | aos* | aros* | cloudabi* | sortix* | twizzler* \ + | nindy* | vxsim* | vxworks* | ebmon* | hms* | mvs* \ + | clix* | riscos* | uniplus* | iris* | isc* | rtu* | xenix* \ + | mirbsd* | netbsd* | dicos* | openedition* | ose* \ + | bitrig* | openbsd* | solidbsd* | libertybsd* | os108* \ + | ekkobsd* | freebsd* | riscix* | lynxos* | os400* \ + | bosx* | nextstep* | cxux* | aout* | elf* | oabi* \ + | ptx* | coff* | ecoff* | winnt* | domain* | vsta* \ + | udi* | lites* | ieee* | go32* | aux* | hcos* \ + | chorusrdb* | cegcc* | glidix* \ + | cygwin* | msys* | pe* | moss* | proelf* | rtems* \ + | midipix* | mingw32* | mingw64* | mint* \ + | uxpv* | beos* | mpeix* | udk* | moxiebox* \ + | interix* | uwin* | mks* | rhapsody* | darwin* \ + | openstep* | oskit* | conix* | pw32* | nonstopux* \ + | storm-chaos* | tops10* | tenex* | tops20* | its* \ + | os2* | vos* | palmos* | uclinux* | nucleus* | morphos* \ + | scout* | superux* | sysv* | rtmk* | tpf* | windiss* \ + | powermax* | dnix* | nx6 | nx7 | sei* | dragonfly* \ + | skyos* | haiku* | rdos* | toppers* | drops* | es* \ + | onefs* | tirtos* | phoenix* | fuchsia* | redox* | bme* \ + | midnightbsd* | amdhsa* | unleashed* | emscripten* | wasi* \ + | nsk* | powerunix* | genode* | zvmoe* | qnx* ) + ;; + # This one is extra strict with allowed versions + sco3.2v2 | sco3.2v[4-9]* | sco5v6*) + # Don't forget version if it is 3.2v4 or newer. + ;; + none) + ;; + *) + echo Invalid configuration \`"$1"\': OS \`"$os"\' not recognized 1>&2 + exit 1 + ;; +esac + +# As a final step for OS-related things, validate the OS-kernel combination +# (given a valid OS), if there is a kernel. +case $kernel-$os in + linux-gnu* | linux-dietlibc* | linux-android* | linux-newlib* | linux-musl* | linux-uclibc* ) + ;; + -dietlibc* | -newlib* | -musl* | -uclibc* ) + # These are just libc implementations, not actual OSes, and thus + # require a kernel. + echo "Invalid configuration \`$1': libc \`$os' needs explicit kernel." 1>&2 + exit 1 + ;; + kfreebsd*-gnu* | kopensolaris*-gnu*) + ;; + nto-qnx*) + ;; + *-eabi* | *-gnueabi*) + ;; + -*) + # Blank kernel with real OS is always fine. + ;; + *-*) + echo "Invalid configuration \`$1': Kernel \`$kernel' not known to work with OS \`$os'." 1>&2 + exit 1 + ;; +esac + # Here we handle the case where we know the os, and the CPU type, but not the # manufacturer. We pick the logical manufacturer. case $vendor in unknown) - case $os in - riscix*) + case $cpu-$os in + *-riscix*) vendor=acorn ;; - sunos*) + *-sunos*) vendor=sun ;; - cnk*|-aix*) + *-cnk* | *-aix*) vendor=ibm ;; - beos*) + *-beos*) vendor=be ;; - hpux*) + *-hpux*) vendor=hp ;; - mpeix*) + *-mpeix*) vendor=hp ;; - hiux*) + *-hiux*) vendor=hitachi ;; - unos*) + *-unos*) vendor=crds ;; - dgux*) + *-dgux*) vendor=dg ;; - luna*) + *-luna*) vendor=omron ;; - genix*) + *-genix*) vendor=ns ;; - clix*) + *-clix*) vendor=intergraph ;; - mvs* | opened*) + *-mvs* | *-opened*) + vendor=ibm + ;; + *-os400*) vendor=ibm ;; - os400*) + s390-* | s390x-*) vendor=ibm ;; - ptx*) + *-ptx*) vendor=sequent ;; - tpf*) + *-tpf*) vendor=ibm ;; - vxsim* | vxworks* | windiss*) + *-vxsim* | *-vxworks* | *-windiss*) vendor=wrs ;; - aux*) + *-aux*) vendor=apple ;; - hms*) + *-hms*) vendor=hitachi ;; - mpw* | macos*) + *-mpw* | *-macos*) vendor=apple ;; - *mint | mint[0-9]* | *MiNT | MiNT[0-9]*) + *-*mint | *-mint[0-9]* | *-*MiNT | *-MiNT[0-9]*) vendor=atari ;; - vos*) + *-vos*) vendor=stratus ;; esac ;; esac -echo "$cpu-$vendor-$os" +echo "$cpu-$vendor-${kernel:+$kernel-}$os" exit # Local variables: ===================================== includes/rts/storage/GC.h ===================================== @@ -202,7 +202,7 @@ typedef void* AdjustorExecutable; AdjustorWritable allocateExec(W_ len, AdjustorExecutable *exec_addr); void flushExec(W_ len, AdjustorExecutable exec_addr); -#if defined(ios_HOST_OS) +#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) AdjustorWritable execToWritable(AdjustorExecutable exec); #endif void freeExec (AdjustorExecutable p); ===================================== llvm-targets ===================================== @@ -1,7 +1,7 @@ -[("i386-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) -,("i686-unknown-windows", ("e-m:x-p:32:32-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) -,("x86_64-unknown-windows", ("e-m:w-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+soft-float -fp16 -vfp2 -vfp2sp -vfp2d16 -vfp2d16sp -vfp3 -vfp3sp -vfp3d16 -vfp3d16sp -vfp4 -vfp4sp -vfp4d16 -vfp4d16sp -fp-armv8 -fp-armv8sp -fp-armv8d16 -fp-armv8d16sp -fullfp16 -neon -crypto -dotprod -fp16fml -fp64 -d32 -fpregs +strict-align")) +[("i386-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("i686-unknown-windows", ("e-m:x-p:32:32-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:32-n8:16:32-a:0:32-S32", "pentium4", "")) +,("x86_64-unknown-windows", ("e-m:w-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("arm-unknown-linux-gnueabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm7tdmi", "+strict-align")) ,("arm-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("arm-unknown-linux-musleabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("armv6-unknown-linux-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1136jf-s", "+strict-align")) @@ -21,31 +21,32 @@ ,("aarch64-unknown-linux-gnu", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("aarch64-unknown-linux-musl", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("aarch64-unknown-linux", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i386-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i386-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux-musl", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("i686-unknown-linux", ("e-m:e-p:32:32-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) -,("x86_64-unknown-linux-gnu", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux-musl", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-linux-android", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16")) -,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) +,("i386-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i386-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux-gnu", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux-musl", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("i686-unknown-linux", ("e-m:e-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:32-n8:16:32-S128", "pentium4", "")) +,("x86_64-unknown-linux-gnu", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-musl", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-linux-android", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "+sse4.2 +popcnt +cx16")) +,("armv7-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) ,("aarch64-unknown-linux-android", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2d16 +vfp2d16sp +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) +,("armv7a-unknown-linux-androideabi", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+fpregs +vfp2 +vfp2sp +vfp3 +vfp3d16 +vfp3d16sp +vfp3sp -fp16 -vfp4 -vfp4d16 -vfp4d16sp -vfp4sp -fp-armv8 -fp-armv8d16 -fp-armv8d16sp -fp-armv8sp -fullfp16 +fp64 +d32 +neon -crypto -fp16fml")) ,("powerpc64le-unknown-linux-gnu", ("e-m:e-i64:64-n32:64", "ppc64le", "")) ,("powerpc64le-unknown-linux-musl", ("e-m:e-i64:64-n32:64", "ppc64le", "+secure-plt")) ,("powerpc64le-unknown-linux", ("e-m:e-i64:64-n32:64", "ppc64le", "")) ,("s390x-ibm-linux", ("E-m:e-i1:8:16-i8:8:16-i64:64-f128:64-a:8:16-n32:64", "z10", "")) -,("i386-apple-darwin", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) -,("x86_64-apple-darwin", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) -,("armv7-apple-ios", ("e-m:o-p:32:32-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) -,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+neon")) -,("i386-apple-ios", ("e-m:o-p:32:32-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) -,("x86_64-apple-ios", ("e-m:o-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) -,("amd64-portbld-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) -,("x86_64-unknown-freebsd", ("e-m:e-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", "")) +,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", "")) +,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "vortex", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) +,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) +,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes")) +,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) +,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) +,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) +,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("aarch64-unknown-freebsd", ("e-m:e-i8:8:32-i16:16:32-i64:64-i128:128-n32:64-S128", "generic", "+neon")) ,("armv6-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "arm1176jzf-s", "+strict-align")) ,("armv7-unknown-freebsd-gnueabihf", ("e-m:e-p:32:32-Fi8-i64:64-v128:64:128-a:0:32-n32-S64", "generic", "+strict-align")) ===================================== rts/Adjustor.c ===================================== @@ -99,7 +99,7 @@ freeHaskellFunctionPtr(void* ptr) { ffi_closure *cl; -#if defined(ios_HOST_OS) +#if defined(ios_HOST_OS) || defined(darwin_HOST_OS) cl = execToWritable(ptr); #else cl = (ffi_closure*)ptr; ===================================== rts/StgCRun.c ===================================== @@ -923,7 +923,7 @@ StgRun(StgFunPtr f, StgRegTable *basereg) { "br %1\n\t" ".globl " STG_RETURN "\n\t" -#if !defined(ios_HOST_OS) +#if !defined(ios_HOST_OS) && !defined(darwin_HOST_OS) ".type " STG_RETURN ", %%function\n" #endif STG_RETURN ":\n\t" ===================================== rts/sm/Storage.c ===================================== @@ -30,7 +30,7 @@ #include "GC.h" #include "Evac.h" #include "NonMoving.h" -#if defined(ios_HOST_OS) +#if defined(ios_HOST_OS) || defined(darwin_HOST_OS) #include "Hash.h" #endif @@ -1639,7 +1639,7 @@ StgWord calcTotalCompactW (void) should be modified to use allocateExec instead of VirtualAlloc. ------------------------------------------------------------------------- */ -#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) +#if (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) #include #endif @@ -1670,7 +1670,7 @@ void flushExec (W_ len, AdjustorExecutable exec_addr) /* x86 doesn't need to do anything, so just suppress some warnings. */ (void)len; (void)exec_addr; -#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && defined(ios_HOST_OS) +#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) /* On iOS we need to use the special 'sys_icache_invalidate' call. */ sys_icache_invalidate(exec_addr, len); #elif defined(__clang__) @@ -1725,7 +1725,7 @@ void freeExec (AdjustorExecutable addr) RELEASE_SM_LOCK } -#elif defined(ios_HOST_OS) +#elif (defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) && (defined(ios_HOST_OS) || defined(darwin_HOST_OS)) static HashTable* allocatedExecs; ===================================== utils/llvm-targets/gen-data-layout.sh ===================================== @@ -84,9 +84,12 @@ TARGETS=( # macOS "i386-apple-darwin" "x86_64-apple-darwin" + "arm64-apple-darwin" # iOS - "armv7-apple-ios arm64-apple-ios" - "i386-apple-ios x86_64-apple-ios" + "armv7-apple-ios" + "arm64-apple-ios" + "i386-apple-ios" + "x86_64-apple-ios" ######################### # FreeBSD View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a1fa55fadcb7a729a949aa434ea527f1690ac0d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a1fa55fadcb7a729a949aa434ea527f1690ac0d 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 Wed Nov 25 00:36:46 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 19:36:46 -0500 Subject: [Git][ghc/ghc][wip/angerman/sized] [Sized Cmm] properly retain sizes. Message-ID: <5fbda71eca0fa_86c8b847fc1008d4@gitlab.mail> Ben Gamari pushed to branch wip/angerman/sized at Glasgow Haskell Compiler / GHC Commits: 993b3581 by Moritz Angermann at 2020-11-24T19:36:40-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/993b35813f44647314b55f4792493521436d907f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/993b35813f44647314b55f4792493521436d907f 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 Wed Nov 25 00:43:22 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 19:43:22 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-8.10] rts/Stats: Reintroduce mut_user_time Message-ID: <5fbda8aaed457_86c158da3501022a@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: b781156f by Ben Gamari at 2020-11-24T19:42:27-05:00 rts/Stats: Reintroduce mut_user_time Fix the previous backport; this function was dead code in master but is still needed due to ProfHeap.c in ghc-8.10. - - - - - 2 changed files: - rts/Stats.c - rts/Stats.h Changes: ===================================== rts/Stats.c ===================================== @@ -86,6 +86,27 @@ Time stat_getElapsedTime(void) Measure the current MUT time, for profiling ------------------------------------------------------------------------ */ +static double +mut_user_time_until( Time t ) +{ + ACQUIRE_LOCK(&stats_mutex); + double ret = TimeToSecondsDbl(t - stats.gc_cpu_ns - stats.nonmoving_gc_cpu_ns); + RELEASE_LOCK(&stats_mutex); + return ret + // heapCensus() time is included in GC_tot_cpu, so we don't need + // to subtract it here. + + // TODO: This seems wrong to me. Surely we should be subtracting + // (at least) start_init_cpu? +} + +double +mut_user_time( void ) +{ + Time cpu = getProcessCPUTime(); + return mut_user_time_until(cpu); +} + #if defined(PROFILING) /* mut_user_time_during_RP() returns the MUT time during retainer profiling. ===================================== rts/Stats.h ===================================== @@ -66,6 +66,8 @@ void initStats0(void); void initStats1(void); void resetChildProcessStats(void); +double mut_user_time(void); + void statDescribeGens( void ); Time stat_getElapsedGCTime(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b781156f4802dd2770fff3080200d497a76d8baf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b781156f4802dd2770fff3080200d497a76d8baf 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 Wed Nov 25 01:01:03 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 20:01:03 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/no-fptr Message-ID: <5fbdaccfa4b8b_86c111d4a001036ed@gitlab.mail> Ben Gamari pushed new branch wip/no-fptr at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/no-fptr 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 Wed Nov 25 01:02:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 20:02:40 -0500 Subject: [Git][ghc/ghc][wip/keepAlive-the-return-of-the-primop] 22 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fbdad30d458_86cfd752bc10527a@gitlab.mail> Ben Gamari pushed to branch wip/keepAlive-the-return-of-the-primop at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 6e16c853 by Ben Gamari at 2020-11-24T10:49:12-05:00 base: Add unsafeWithForeignPtr - - - - - 5dc677fe by Ben Gamari at 2020-11-24T10:59:59-05:00 base: Introduce GHC.ForeignPtr.Ops module This contains a variety of peek/poke operations for ForeignPtr accesses. - - - - - 3c9d4db7 by Ben Gamari at 2020-11-24T10:59:59-05:00 GHC.IO.Buffer: Use ForeignPtr-specialised peek/poke - - - - - e190afc1 by Ben Gamari at 2020-11-24T11:05:55-05:00 GHC.Data.ByteArray: Initial commit - - - - - 70c6f4f4 by Ben Gamari at 2020-11-24T20:00:48-05:00 StringBuffer: Rid it of ForeignPtrs Bumps haddock submodule. - - - - - 64394779 by Ben Gamari at 2020-11-24T20:00:56-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - cbb83eff by Ben Gamari at 2020-11-24T20:00:56-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 4c9a7a16 by Ben Gamari at 2020-11-24T20:00:56-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - dac48341 by Ben Gamari at 2020-11-24T20:00:56-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - 91821101 by Ben Gamari at 2020-11-24T20:00:56-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - 0b7d6a3e by Ben Gamari at 2020-11-24T20:02:08-05:00 genprimopcode: Add a second levity-polymorphic tyvar This will be needed shortly. - - - - - c54ca943 by GHC GitLab CI at 2020-11-24T20:02:08-05:00 Introduce keepAlive primop - - - - - 103452a9 by Ben Gamari at 2020-11-24T20:02:08-05:00 base: Use keepAlive# in withForeignPtr - - - - - 0aa024af by Ben Gamari at 2020-11-24T20:02:08-05:00 Implement withByteArrayContents in terms of keepAlive# - - - - - e75c5080 by Ben Gamari at 2020-11-24T20:02:08-05:00 base: Implement GHC.ForeignPtr.Ops in terms of keepAlive# - - - - - 945b8cba by Ben Gamari at 2020-11-24T20:02:08-05:00 base: Use keepAlive# in Foreign.Marshal.Alloc - - - - - 86ee8fda by Ben Gamari at 2020-11-24T20:02:08-05:00 ghc-compact: Use keepAlive# in GHC.Compact.Serialized - - - - - 2e809f72 by Ben Gamari at 2020-11-24T20:02:08-05:00 testsuite: Accept - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - + compiler/GHC/Data/ByteArray.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Utils/Binary.hs - compiler/ghc.cabal.in - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/base/Debug/Trace.hs - libraries/base/Foreign/ForeignPtr/Imp.hs - libraries/base/Foreign/Marshal/Alloc.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/ForeignPtr.hs - + libraries/base/GHC/ForeignPtr/Ops.hs - libraries/base/GHC/IO/Buffer.hs - libraries/base/base.cabal - libraries/bytestring - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/ghc-boot/GHC/Utils/Encoding.hs - libraries/ghc-compact/GHC/Compact/Serialized.hs - rts/Capability.c - rts/Capability.h - rts/LinkerInternals.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/17ad689a701eae4c7647574c857530515a0d344b...2e809f72c7f900da77b48df397463d6c95f0b1d6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/17ad689a701eae4c7647574c857530515a0d344b...2e809f72c7f900da77b48df397463d6c95f0b1d6 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 Wed Nov 25 01:35:18 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 24 Nov 2020 20:35:18 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/backport/9.0/T18857 Message-ID: <5fbdb4d6b6c9f_86cbee25901065c8@gitlab.mail> Moritz Angermann pushed new branch wip/backport/9.0/T18857 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backport/9.0/T18857 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 Wed Nov 25 01:39:50 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 24 Nov 2020 20:39:50 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/backport/8.10/T18857 Message-ID: <5fbdb5e624b58_86c113a5b2c1067ab@gitlab.mail> Moritz Angermann pushed new branch wip/backport/8.10/T18857 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backport/8.10/T18857 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 Wed Nov 25 01:46:31 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 24 Nov 2020 20:46:31 -0500 Subject: [Git][ghc/ghc][wip/angerman/arm64] 324 commits: Make the parser module less dependent on DynFlags Message-ID: <5fbdb777d643_86c7d59240111773@gitlab.mail> Moritz Angermann pushed to branch wip/angerman/arm64 at Glasgow Haskell Compiler / GHC Commits: 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.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/Node.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a1fa55fadcb7a729a949aa434ea527f1690ac0d...2ed3e6c0f179c06828712832d1176519cdfa82a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8a1fa55fadcb7a729a949aa434ea527f1690ac0d...2ed3e6c0f179c06828712832d1176519cdfa82a6 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 Wed Nov 25 02:06:39 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 21:06:39 -0500 Subject: [Git][ghc/ghc][wip/no-fptr] 7 commits: GHC.Data.ByteArray: Initial commit Message-ID: <5fbdbc2f70749_86c158da35011777@gitlab.mail> Ben Gamari pushed to branch wip/no-fptr at Glasgow Haskell Compiler / GHC Commits: ece52044 by Ben Gamari at 2020-11-24T21:06:18-05:00 GHC.Data.ByteArray: Initial commit - - - - - 292bd5b4 by Ben Gamari at 2020-11-24T21:06:22-05:00 StringBuffer: Rid it of ForeignPtrs Bumps haddock submodule. - - - - - 8b53778c by Ben Gamari at 2020-11-24T21:06:22-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - a7f9997f by Ben Gamari at 2020-11-24T21:06:22-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 389717fc by Ben Gamari at 2020-11-24T21:06:22-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - 240498b1 by Ben Gamari at 2020-11-24T21:06:22-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - 0f4327d8 by Ben Gamari at 2020-11-24T21:06:22-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - 10 changed files: - + compiler/GHC/Data/ByteArray.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Utils/Binary.hs - compiler/ghc.cabal.in - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/IO/Buffer.hs - libraries/bytestring - libraries/ghc-boot/GHC/Utils/Encoding.hs - testsuite/tests/parser/should_run/CountParserDeps.stdout - utils/haddock Changes: ===================================== compiler/GHC/Data/ByteArray.hs ===================================== @@ -0,0 +1,280 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Data.ByteArray + ( -- * Immutable byte arrays + ByteArray + , getByteArray + , unsafeByteArrayContents + , withByteArrayContents + , sizeofByteArray + + -- * Mutable byte arrays + , MutableByteArray + , getMutableByteArray + , unsafeMutableByteArrayContents + , newMutableByteArray + , newPinnedMutableByteArray + , copyByteArray + , copyAddrToMutableByteArray + , unsafeFreezeByteArray + + -- * Writing + , writeWordArray + , writeWord8Array + , writeWord16Array + , writeWord32Array + , writeWord64Array + , writeIntArray + , writeInt8Array + , writeInt16Array + , writeInt32Array + , writeInt64Array + , writeCharArray + + -- * Reading + , readWordArray + , readWord8Array + , readWord16Array + , readWord32Array + , readWord64Array + , readIntArray + , readInt8Array + , readInt16Array + , readInt32Array + , readInt64Array + , readCharArray + + -- * Immutable indexing + , indexWordArray + , indexWord8Array + , indexWord16Array + , indexWord32Array + , indexWord64Array + , indexIntArray + , indexInt8Array + , indexInt16Array + , indexInt32Array + , indexInt64Array + , indexCharArray + ) where + +import GHC.Base +import GHC.Exts +import GHC.Word +import GHC.Int +import Unsafe.Coerce + +data MutableByteArray = MutableByteArray { getMutableByteArray :: !(MutableByteArray# RealWorld) } + +data ByteArray = ByteArray { getByteArray :: !ByteArray# } + +unsafeByteArrayContents :: ByteArray -> Ptr a +unsafeByteArrayContents (ByteArray ba) = Ptr (byteArrayContents# ba) + +unsafeMutableByteArrayContents :: MutableByteArray -> Ptr a +unsafeMutableByteArrayContents = unsafeByteArrayContents . unsafeCoerce + +withByteArrayContents :: ByteArray -> (Ptr a -> IO b) -> IO b +withByteArrayContents (ByteArray ba) f = do + r <- f $ Ptr (byteArrayContents# ba) + IO $ \s -> case touch# ba s of s' -> (# s', () #) + return r + +newMutableByteArray :: Int -> IO MutableByteArray +newMutableByteArray (I# size) = IO $ \s -> + case newByteArray# size s of + (# s', mba #) -> (# s', MutableByteArray mba #) + +newPinnedMutableByteArray :: Int -> IO MutableByteArray +newPinnedMutableByteArray (I# size) = IO $ \s -> + case newPinnedByteArray# size s of + (# s', mba #) -> (# s', MutableByteArray mba #) + +copyByteArray + :: ByteArray -- ^ source + -> Int -- ^ source offset + -> MutableByteArray -- ^ destination + -> Int -- ^ destination offset + -> Int -- ^ length to copy + -> IO () +copyByteArray (ByteArray src) (I# src_ofs) (MutableByteArray dst) (I# dst_ofs) (I# len) = + IO $ \s -> + case copyByteArray# src src_ofs dst dst_ofs len s of + s' -> (# s', () #) + +copyAddrToMutableByteArray :: Ptr a -> MutableByteArray -> Int -> Int -> IO () +copyAddrToMutableByteArray (Ptr src) (MutableByteArray dst) (I# dst_ofs) (I# len) = IO $ \s -> + case copyAddrToByteArray# src dst dst_ofs len s of + s' -> (# s', () #) + +unsafeFreezeByteArray + :: MutableByteArray + -> IO ByteArray +unsafeFreezeByteArray (MutableByteArray mba) = IO $ \s -> + case unsafeFreezeByteArray# mba s of + (# s', ba #) -> (# s', ByteArray ba #) + +sizeofByteArray :: ByteArray -> Int +sizeofByteArray (ByteArray arr) = I# (sizeofByteArray# arr) + + +readWordArray :: MutableByteArray -> Int -> IO Word +readWordArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWordArray# arr ix s0 of + (# s1, r #) -> (# s1, W# r #) + +readWord8Array :: MutableByteArray -> Int -> IO Word8 +readWord8Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord8Array# arr ix s0 of + (# s1, r #) -> (# s1, W8# r #) + +readWord16Array :: MutableByteArray -> Int -> IO Word16 +readWord16Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord16Array# arr ix s0 of + (# s1, r #) -> (# s1, W16# r #) + +readWord32Array :: MutableByteArray -> Int -> IO Word32 +readWord32Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord32Array# arr ix s0 of + (# s1, r #) -> (# s1, W32# r #) + +readWord64Array :: MutableByteArray -> Int -> IO Word64 +readWord64Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord64Array# arr ix s0 of + (# s1, r #) -> (# s1, W64# r #) + +readIntArray :: MutableByteArray -> Int -> IO Int +readIntArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readIntArray# arr ix s0 of + (# s1, r #) -> (# s1, I# r #) + +readInt8Array :: MutableByteArray -> Int -> IO Int8 +readInt8Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt8Array# arr ix s0 of + (# s1, r #) -> (# s1, I8# r #) + +readInt16Array :: MutableByteArray -> Int -> IO Int16 +readInt16Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt16Array# arr ix s0 of + (# s1, r #) -> (# s1, I16# r #) + +readInt32Array :: MutableByteArray -> Int -> IO Int32 +readInt32Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt32Array# arr ix s0 of + (# s1, r #) -> (# s1, I32# r #) + +readInt64Array :: MutableByteArray -> Int -> IO Int64 +readInt64Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt64Array# arr ix s0 of + (# s1, r #) -> (# s1, I64# r #) + +readCharArray :: MutableByteArray -> Int -> IO Char +readCharArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readCharArray# arr ix s0 of + (# s1, r #) -> (# s1, C# r #) + + + +writeWordArray :: MutableByteArray -> Int -> Word -> IO () +writeWordArray (MutableByteArray arr) (I# ix) (W# x) = IO $ \s0 -> + case writeWordArray# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord8Array :: MutableByteArray -> Int -> Word8 -> IO () +writeWord8Array (MutableByteArray arr) (I# ix) (W8# x) = IO $ \s0 -> + case writeWord8Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord16Array :: MutableByteArray -> Int -> Word16 -> IO () +writeWord16Array (MutableByteArray arr) (I# ix) (W16# x) = IO $ \s0 -> + case writeWord16Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord32Array :: MutableByteArray -> Int -> Word32 -> IO () +writeWord32Array (MutableByteArray arr) (I# ix) (W32# x) = IO $ \s0 -> + case writeWord32Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord64Array :: MutableByteArray -> Int -> Word64 -> IO () +writeWord64Array (MutableByteArray arr) (I# ix) (W64# x) = IO $ \s0 -> + case writeWord64Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeIntArray :: MutableByteArray -> Int -> Int -> IO () +writeIntArray (MutableByteArray arr) (I# ix) (I# x) = IO $ \s0 -> + case writeIntArray# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt8Array :: MutableByteArray -> Int -> Int8 -> IO () +writeInt8Array (MutableByteArray arr) (I# ix) (I8# x) = IO $ \s0 -> + case writeInt8Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt16Array :: MutableByteArray -> Int -> Int16 -> IO () +writeInt16Array (MutableByteArray arr) (I# ix) (I16# x) = IO $ \s0 -> + case writeInt16Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt32Array :: MutableByteArray -> Int -> Int32 -> IO () +writeInt32Array (MutableByteArray arr) (I# ix) (I32# x) = IO $ \s0 -> + case writeInt32Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt64Array :: MutableByteArray -> Int -> Int64 -> IO () +writeInt64Array (MutableByteArray arr) (I# ix) (I64# x) = IO $ \s0 -> + case writeInt64Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeCharArray :: MutableByteArray -> Int -> Char -> IO () +writeCharArray (MutableByteArray arr) (I# ix) (C# x) = IO $ \s0 -> + case writeCharArray# arr ix x s0 of + s1 -> (# s1, () #) + + + +indexWordArray :: ByteArray -> Int -> Word +indexWordArray (ByteArray arr) (I# ix) = + W# (indexWordArray# arr ix) + +indexWord8Array :: ByteArray -> Int -> Word8 +indexWord8Array (ByteArray arr) (I# ix) = + W8# (indexWord8Array# arr ix) + +indexWord16Array :: ByteArray -> Int -> Word16 +indexWord16Array (ByteArray arr) (I# ix) = + W16# (indexWord16Array# arr ix) + +indexWord32Array :: ByteArray -> Int -> Word32 +indexWord32Array (ByteArray arr) (I# ix) = + W32# (indexWord32Array# arr ix) + +indexWord64Array :: ByteArray -> Int -> Word64 +indexWord64Array (ByteArray arr) (I# ix) = + W64# (indexWord64Array# arr ix) + +indexIntArray :: ByteArray -> Int -> Int +indexIntArray (ByteArray arr) (I# ix) = + I# (indexIntArray# arr ix) + +indexInt8Array :: ByteArray -> Int -> Int8 +indexInt8Array (ByteArray arr) (I# ix) = + I8# (indexInt8Array# arr ix) + +indexInt16Array :: ByteArray -> Int -> Int16 +indexInt16Array (ByteArray arr) (I# ix) = + I16# (indexInt16Array# arr ix) + +indexInt32Array :: ByteArray -> Int -> Int32 +indexInt32Array (ByteArray arr) (I# ix) = + I32# (indexInt32Array# arr ix) + +indexInt64Array :: ByteArray -> Int -> Int64 +indexInt64Array (ByteArray arr) (I# ix) = + I64# (indexInt64Array# arr ix) + +indexCharArray :: ByteArray -> Int -> Char +indexCharArray (ByteArray arr) (I# ix) = + C# (indexCharArray# arr ix) + ===================================== compiler/GHC/Data/StringBuffer.hs ===================================== @@ -17,7 +17,7 @@ Buffers for scanning string input stored in external arrays. module GHC.Data.StringBuffer ( - StringBuffer(..), + StringBuffer, len, cur, -- non-abstract for vs\/HaskellService -- * Creation\/destruction @@ -26,6 +26,7 @@ module GHC.Data.StringBuffer hPutStringBuffer, appendStringBuffers, stringToStringBuffer, + byteStringToStringBuffer, -- * Inspection nextChar, @@ -54,10 +55,13 @@ import GHC.Prelude import GHC.Utils.Encoding import GHC.Data.FastString +import GHC.Data.ByteArray import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain import GHC.Utils.Misc +import qualified Data.ByteString as BS +import qualified Data.ByteString.Unsafe as BS import Data.Maybe import Control.Exception import System.IO @@ -65,6 +69,7 @@ import System.IO.Unsafe ( unsafePerformIO ) import GHC.IO.Encoding.UTF8 ( mkUTF8 ) import GHC.IO.Encoding.Failure ( CodingFailureMode(IgnoreCodingFailure) ) +import GHC.Word import GHC.Exts import Foreign @@ -81,7 +86,7 @@ import Foreign -- data StringBuffer = StringBuffer { - buf :: {-# UNPACK #-} !(ForeignPtr Word8), + buf :: {-# UNPACK #-} !ByteArray, len :: {-# UNPACK #-} !Int, -- length cur :: {-# UNPACK #-} !Int -- current pos } @@ -102,34 +107,35 @@ instance Show StringBuffer where -- managed by the garbage collector. hGetStringBuffer :: FilePath -> IO StringBuffer hGetStringBuffer fname = do - h <- openBinaryFile fname ReadMode - size_i <- hFileSize h - offset_i <- skipBOM h size_i 0 -- offset is 0 initially - let size = fromIntegral $ size_i - offset_i - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> do - r <- if size == 0 then return 0 else hGetBuf h ptr size - hClose h - if (r /= size) - then ioError (userError "short read of file") - else newUTF8StringBuffer buf ptr size + h <- openBinaryFile fname ReadMode + size_i <- hFileSize h + offset_i <- skipBOM h size_i 0 -- offset is 0 initially + let size = fromIntegral $ size_i - offset_i + buf <- newPinnedMutableByteArray (size+3) + r <- if size == 0 + then return 0 + else hGetBuf h (unsafeMutableByteArrayContents buf) size + hClose h + if r /= size + then ioError (userError "short read of file") + else newUTF8StringBuffer buf size hGetStringBufferBlock :: Handle -> Int -> IO StringBuffer -hGetStringBufferBlock handle wanted - = do size_i <- hFileSize handle - offset_i <- hTell handle >>= skipBOM handle size_i - let size = min wanted (fromIntegral $ size_i-offset_i) - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> - do r <- if size == 0 then return 0 else hGetBuf handle ptr size - if r /= size - then ioError (userError $ "short read of file: "++show(r,size,size_i,handle)) - else newUTF8StringBuffer buf ptr size +hGetStringBufferBlock handle wanted = do + size_i <- hFileSize handle + offset_i <- hTell handle >>= skipBOM handle size_i + let size = min wanted (fromIntegral $ size_i-offset_i) + buf <- newPinnedMutableByteArray (size+3) + r <- if size == 0 + then return 0 + else hGetBuf handle (unsafeMutableByteArrayContents buf) size + if r /= size + then ioError (userError $ "short read of file: "++show(r,size,size_i,handle)) + else newUTF8StringBuffer buf size hPutStringBuffer :: Handle -> StringBuffer -> IO () -hPutStringBuffer hdl (StringBuffer buf len cur) - = withForeignPtr (plusForeignPtr buf cur) $ \ptr -> - hPutBuf hdl ptr len +hPutStringBuffer hdl (StringBuffer buf len cur) = do + withByteArrayContents buf $ \ptr -> hPutBuf hdl (ptr `plusPtr` cur) len -- | Skip the byte-order mark if there is one (see #1744 and #6016), -- and return the new position of the handle in bytes. @@ -156,39 +162,45 @@ skipBOM h size offset = where safeEncoding = mkUTF8 IgnoreCodingFailure -newUTF8StringBuffer :: ForeignPtr Word8 -> Ptr Word8 -> Int -> IO StringBuffer -newUTF8StringBuffer buf ptr size = do - pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0] +-- | @newUTF8StringBuffer buf size@ creates a 'StringBuffer' from a +-- 'MutableByteArray' of length @size+3@ containing UTF-8 encoded text. A three +-- byte sentinel will be added to the end of the buffer. +newUTF8StringBuffer :: MutableByteArray -> Int -> IO StringBuffer +newUTF8StringBuffer buf size = do -- sentinels for UTF-8 decoding - return $ StringBuffer buf size 0 + writeWord8Array buf (size+0) 0 + writeWord8Array buf (size+1) 0 + writeWord8Array buf (size+3) 0 + buf' <- unsafeFreezeByteArray buf + return $ StringBuffer buf' size 0 appendStringBuffers :: StringBuffer -> StringBuffer -> IO StringBuffer -appendStringBuffers sb1 sb2 - = do newBuf <- mallocForeignPtrArray (size+3) - withForeignPtr newBuf $ \ptr -> - withForeignPtr (buf sb1) $ \sb1Ptr -> - withForeignPtr (buf sb2) $ \sb2Ptr -> - do copyArray ptr (sb1Ptr `advancePtr` cur sb1) sb1_len - copyArray (ptr `advancePtr` sb1_len) (sb2Ptr `advancePtr` cur sb2) sb2_len - pokeArray (ptr `advancePtr` size) [0,0,0] - return (StringBuffer newBuf size 0) - where sb1_len = calcLen sb1 - sb2_len = calcLen sb2 - calcLen sb = len sb - cur sb - size = sb1_len + sb2_len +appendStringBuffers sb1 sb2 = do + dst <- newPinnedMutableByteArray (size+3) + copyByteArray (buf sb1) (cur sb1) dst 0 sb1_len + copyByteArray (buf sb2) (cur sb2) dst sb1_len sb2_len + newUTF8StringBuffer dst size + where + sb1_len = calcLen sb1 + sb2_len = calcLen sb2 + calcLen sb = len sb - cur sb + size = sb1_len + sb2_len + +byteStringToStringBuffer :: BS.ByteString -> StringBuffer +byteStringToStringBuffer bs = unsafePerformIO $ do + let size = BS.length bs + buf <- newPinnedMutableByteArray (size+3) + BS.unsafeUseAsCString bs (\p -> copyAddrToMutableByteArray p buf 0 size) + newUTF8StringBuffer buf size -- | Encode a 'String' into a 'StringBuffer' as UTF-8. The resulting buffer -- is automatically managed by the garbage collector. stringToStringBuffer :: String -> StringBuffer -stringToStringBuffer str = - unsafePerformIO $ do +stringToStringBuffer str = unsafePerformIO $ do let size = utf8EncodedLength str - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> do - utf8EncodeString ptr str - pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0] - -- sentinels for UTF-8 decoding - return (StringBuffer buf size 0) + buf <- newPinnedMutableByteArray (size+3) + utf8EncodeString (unsafeMutableByteArrayContents buf) str + newUTF8StringBuffer buf size -- ----------------------------------------------------------------------------- -- Grab a character @@ -202,12 +214,10 @@ stringToStringBuffer str = nextChar :: StringBuffer -> (Char,StringBuffer) nextChar (StringBuffer buf len (I# cur#)) = -- Getting our fingers dirty a little here, but this is performance-critical - inlinePerformIO $ - withForeignPtr buf $ \(Ptr a#) -> - case utf8DecodeCharAddr# (a# `plusAddr#` cur#) 0# of - (# c#, nBytes# #) -> - let cur' = I# (cur# +# nBytes#) in - return (C# c#, StringBuffer buf len cur') + case utf8DecodeCharByteArray# (getByteArray buf) cur# of + (# c#, nBytes# #) -> + let cur' = I# (cur# +# nBytes#) + in (C# c#, StringBuffer buf len cur') -- | Return the first UTF-8 character of a nonempty 'StringBuffer' (analogous -- to 'Data.List.head'). __Warning:__ The behavior is undefined if the @@ -219,10 +229,9 @@ currentChar = fst . nextChar prevChar :: StringBuffer -> Char -> Char prevChar (StringBuffer _ _ 0) deflt = deflt prevChar (StringBuffer buf _ cur) _ = - inlinePerformIO $ - withForeignPtr buf $ \p -> do - p' <- utf8PrevChar (p `plusPtr` cur) - return (fst (utf8DecodeChar p')) + let !(I# p') = utf8PrevChar (getByteArray buf) cur + !(# c, _ #) = utf8DecodeCharByteArray# (getByteArray buf) p' + in C# c -- ----------------------------------------------------------------------------- -- Moving @@ -257,18 +266,18 @@ atEnd (StringBuffer _ l c) = l == c -- wanted line. Lines begin at 1. atLine :: Int -> StringBuffer -> Maybe StringBuffer atLine line sb@(StringBuffer buf len _) = - inlinePerformIO $ - withForeignPtr buf $ \p -> do - p' <- skipToLine line len p - if p' == nullPtr - then return Nothing - else - let - delta = p' `minusPtr` p - in return $ Just (sb { cur = delta - , len = len - delta - }) - + inlinePerformIO $ withByteArrayContents buf $ \p -> do + p' <- skipToLine line len p + if p' == nullPtr + then return Nothing + else + let !delta = p' `minusPtr` p + in return $ Just (sb { cur = delta + , len = len - delta + }) + +-- | @skipToLine line len op0@ finds the byte offset to the beginning of +-- the given line number. skipToLine :: Int -> Int -> Ptr Word8 -> IO (Ptr Word8) skipToLine !line !len !op0 = go 1 op0 where @@ -300,39 +309,42 @@ lexemeToString :: StringBuffer -> Int -- ^ @n@, the number of bytes -> String lexemeToString _ 0 = "" -lexemeToString (StringBuffer buf _ cur) bytes = - utf8DecodeStringLazy buf cur bytes +lexemeToString (StringBuffer buf _ (I# cur#)) (I# bytes#) = + utf8DecodeByteArrayLazy# (getByteArray buf) cur# bytes# lexemeToFastString :: StringBuffer -> Int -- ^ @n@, the number of bytes -> FastString lexemeToFastString _ 0 = nilFS lexemeToFastString (StringBuffer buf _ cur) len = - inlinePerformIO $ - withForeignPtr buf $ \ptr -> - return $! mkFastStringBytes (ptr `plusPtr` cur) len + inlinePerformIO $ + withByteArrayContents buf $ \ptr -> + return $! mkFastStringBytes (ptr `plusPtr` cur) len -- | Return the previous @n@ characters (or fewer if we are less than @n@ -- characters into the buffer. decodePrevNChars :: Int -> StringBuffer -> String -decodePrevNChars n (StringBuffer buf _ cur) = - inlinePerformIO $ withForeignPtr buf $ \p0 -> - go p0 n "" (p0 `plusPtr` (cur - 1)) +decodePrevNChars n (StringBuffer buf0 _ cur) = + go (getByteArray buf0) (min n (cur - 1)) "" (cur - 1) where - go :: Ptr Word8 -> Int -> String -> Ptr Word8 -> IO String - go buf0 n acc p | n == 0 || buf0 >= p = return acc - go buf0 n acc p = do - p' <- utf8PrevChar p - let (c,_) = utf8DecodeChar p' - go buf0 (n - 1) (c:acc) p' + go :: ByteArray# -> Int -> String -> Int -> String + go buf n acc ofs + | n == 0 = acc + | otherwise = + let !ofs'@(I# ofs'#) = utf8PrevChar buf ofs + !(# c,_ #) = utf8DecodeCharByteArray# buf ofs'# + in go buf (n - 1) (C# c:acc) ofs' -- ----------------------------------------------------------------------------- -- Parsing integer strings in various bases parseUnsignedInteger :: StringBuffer -> Int -> Integer -> (Char->Int) -> Integer -parseUnsignedInteger (StringBuffer buf _ cur) len radix char_to_int - = inlinePerformIO $ withForeignPtr buf $ \ptr -> return $! let - go i x | i == len = x - | otherwise = case fst (utf8DecodeChar (ptr `plusPtr` (cur + i))) of - '_' -> go (i + 1) x -- skip "_" (#14473) - char -> go (i + 1) (x * radix + toInteger (char_to_int char)) - in go 0 0 +parseUnsignedInteger (StringBuffer buf _ (I# cur)) (I# len) radix char_to_int + = go (len +# cur) cur 0 + where + go :: Int# -> Int# -> Integer -> Integer + go end i !acc + | isTrue# (i ==# end) = acc + | otherwise = + case utf8DecodeCharByteArray# (getByteArray buf) i of + (# '_'#, _ #) -> go end (i +# 1#) acc -- skip "_" (#14473) + (# char, _ #) -> go end (i +# 1#) (acc * radix + toInteger (char_to_int (C# char))) ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised @@ -84,6 +85,7 @@ import Data.Array import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import GHC.ForeignPtr import Data.IORef import Data.Char ( ord, chr ) import Data.Time @@ -96,7 +98,10 @@ import GHC.Real ( Ratio(..) ) type BinArray = ForeignPtr Word8 - +#if !MIN_VERSION_base(4,15,0) +unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b +unsafeWithForeignPtr = withForeignPtr +#endif --------------------------------------------------------------- -- BinData @@ -111,14 +116,14 @@ instance Binary BinData where put_ bh (BinData sz dat) = do put_ bh sz putPrim bh sz $ \dest -> - withForeignPtr dat $ \orig -> + unsafeWithForeignPtr dat $ \orig -> copyBytes dest orig sz -- get bh = do sz <- get bh dat <- mallocForeignPtrBytes sz getPrim bh sz $ \orig -> - withForeignPtr dat $ \dest -> + unsafeWithForeignPtr dat $ \dest -> copyBytes dest orig sz return (BinData sz dat) @@ -226,7 +231,7 @@ writeBinMem (BinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode arr <- readIORef arr_r ix <- readFastMutInt ix_r - withForeignPtr arr $ \p -> hPutBuf h p ix + unsafeWithForeignPtr arr $ \p -> hPutBuf h p ix hClose h readBinMem :: FilePath -> IO BinHandle @@ -236,7 +241,7 @@ readBinMem filename = do filesize' <- hFileSize h let filesize = fromIntegral filesize' arr <- mallocForeignPtrBytes filesize - count <- withForeignPtr arr $ \p -> hGetBuf h p filesize + count <- unsafeWithForeignPtr arr $ \p -> hGetBuf h p filesize when (count /= filesize) $ error ("Binary.readBinMem: only read " ++ show count ++ " bytes") hClose h @@ -280,7 +285,7 @@ putPrim h@(BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ expandBin h (ix + size) arr <- readIORef arr_r - withForeignPtr arr $ \op -> f (op `plusPtr` ix) + unsafeWithForeignPtr arr $ \op -> f (op `plusPtr` ix) writeFastMutInt ix_r (ix + size) -- -- | Similar to putPrim but advances the index by the actual number of @@ -302,7 +307,10 @@ getPrim (BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing) arr <- readIORef arr_r - w <- withForeignPtr arr $ \op -> f (op `plusPtr` ix) + w <- f (unsafeForeignPtrToPtr arr `plusPtr` ix) + touchForeignPtr arr + -- This is safe WRT #17760 as we we guarantee that the above line doesn't + -- diverge writeFastMutInt ix_r (ix + size) return w ===================================== compiler/ghc.cabal.in ===================================== @@ -356,6 +356,7 @@ Library GHC.Data.Bag GHC.Data.Bitmap GHC.Data.BooleanFormula + GHC.Data.ByteArray GHC.Data.EnumSet GHC.Data.FastMutInt GHC.Data.FastString ===================================== libraries/base/GHC/Event/Array.hs ===================================== @@ -33,7 +33,7 @@ import Foreign.ForeignPtr (ForeignPtr, withForeignPtr) import Foreign.Ptr (Ptr, nullPtr, plusPtr) import Foreign.Storable (Storable(..)) import GHC.Base hiding (empty) -import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_) +import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_, unsafeWithForeignPtr) import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (show) @@ -78,9 +78,9 @@ reallocArray p newSize oldSize = reallocHack undefined p reallocHack dummy src = do let size = sizeOf dummy dst <- mallocPlainForeignPtrBytes (newSize * size) - withForeignPtr src $ \s -> + unsafeWithForeignPtr src $ \s -> when (s /= nullPtr && oldSize > 0) . - withForeignPtr dst $ \d -> do + unsafeWithForeignPtr dst $ \d -> do _ <- memcpy d s (fromIntegral (oldSize * size)) return () return dst @@ -99,8 +99,8 @@ duplicate a = dupHack undefined a dupHack dummy (Array ref) = do AC es len cap <- readIORef ref ary <- allocArray cap - withForeignPtr ary $ \dest -> - withForeignPtr es $ \src -> do + unsafeWithForeignPtr ary $ \dest -> + unsafeWithForeignPtr es $ \src -> do _ <- memcpy dest src (fromIntegral (len * sizeOf dummy)) return () Array `fmap` newIORef (AC ary len cap) @@ -119,8 +119,8 @@ unsafeRead :: Storable a => Array a -> Int -> IO a unsafeRead (Array ref) ix = do AC es _ cap <- readIORef ref CHECK_BOUNDS("unsafeRead",cap,ix) - withForeignPtr es $ \p -> - peekElemOff p ix + unsafeWithForeignPtr es $ \ptr -> peekElemOff ptr ix + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge unsafeWrite :: Storable a => Array a -> Int -> a -> IO () unsafeWrite (Array ref) ix a = do @@ -130,13 +130,15 @@ unsafeWrite (Array ref) ix a = do unsafeWrite' :: Storable a => AC a -> Int -> a -> IO () unsafeWrite' (AC es _ cap) ix a = CHECK_BOUNDS("unsafeWrite'",cap,ix) - withForeignPtr es $ \p -> - pokeElemOff p ix a + unsafeWithForeignPtr es $ \ptr -> pokeElemOff ptr ix a + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge +-- | Precondition: continuation must not diverge due to use of +-- 'unsafeWithForeignPtr'. unsafeLoad :: Array a -> (Ptr a -> Int -> IO Int) -> IO Int unsafeLoad (Array ref) load = do AC es _ cap <- readIORef ref - len' <- withForeignPtr es $ \p -> load p cap + len' <- unsafeWithForeignPtr es $ \p -> load p cap writeIORef ref (AC es len' cap) return len' @@ -146,7 +148,7 @@ unsafeCopyFromBuffer :: Storable a => Array a -> Ptr a -> Int -> IO () unsafeCopyFromBuffer (Array ref) sptr n = readIORef ref >>= \(AC es _ cap) -> CHECK_BOUNDS("unsafeCopyFromBuffer", cap, n) - withForeignPtr es $ \pdest -> do + unsafeWithForeignPtr es $ \pdest -> do let size = sizeOfPtr sptr undefined _ <- memcpy pdest sptr (fromIntegral $ n * size) writeIORef ref (AC es n cap) @@ -198,7 +200,7 @@ forM_ ary g = forHack ary g undefined AC es len _ <- readIORef ref let size = sizeOf dummy offset = len * size - withForeignPtr es $ \p -> do + unsafeWithForeignPtr es $ \p -> do let go n | n >= offset = return () | otherwise = do f =<< peek (p `plusPtr` n) @@ -269,8 +271,8 @@ copy' d dstart s sstart maxCount = copyHack d s undefined then return dac else do AC dst dlen dcap <- ensureCapacity' dac (dstart + count) - withForeignPtr dst $ \dptr -> - withForeignPtr src $ \sptr -> do + unsafeWithForeignPtr dst $ \dptr -> + unsafeWithForeignPtr src $ \sptr -> do _ <- memcpy (dptr `plusPtr` (dstart * size)) (sptr `plusPtr` (sstart * size)) (fromIntegral (count * size)) @@ -286,7 +288,7 @@ removeAt a i = removeHack a undefined let size = sizeOf dummy newLen = oldLen - 1 when (newLen > 0 && i < newLen) . - withForeignPtr fp $ \ptr -> do + unsafeWithForeignPtr fp $ \ptr -> do _ <- memmove (ptr `plusPtr` (size * i)) (ptr `plusPtr` (size * (i+1))) (fromIntegral (size * (newLen-i))) ===================================== libraries/base/GHC/IO/Buffer.hs ===================================== @@ -73,6 +73,7 @@ import GHC.Show import GHC.Real import GHC.List import GHC.ForeignPtr.Ops +import GHC.ForeignPtr (unsafeWithForeignPtr) import Foreign.C.Types import Foreign.ForeignPtr import Foreign.Storable @@ -118,17 +119,17 @@ type CharBufElem = Char type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char -peekCharBuf arr ix = withForeignPtr arr $ \p -> do +peekCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> do (c,_) <- readCharBufPtr p ix return c {-# INLINE readCharBuf #-} readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) -readCharBuf arr ix = withForeignPtr arr $ \p -> readCharBufPtr p ix +readCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> readCharBufPtr p ix {-# INLINE writeCharBuf #-} writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int -writeCharBuf arr ix c = withForeignPtr arr $ \p -> writeCharBufPtr p ix c +writeCharBuf arr ix c = unsafeWithForeignPtr arr $ \p -> writeCharBufPtr p ix c {-# INLINE readCharBufPtr #-} readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit e043aacfc4202a59ccae8b8c8cf0e1ad83a3f209 +Subproject commit 4cbf0cd6053411139a08ff67c7ec5eae1da87b03 ===================================== libraries/ghc-boot/GHC/Utils/Encoding.hs ===================================== @@ -17,12 +17,15 @@ module GHC.Utils.Encoding ( -- * UTF-8 utf8DecodeCharAddr#, + utf8DecodeCharByteArray#, utf8PrevChar, utf8CharStart, utf8DecodeChar, utf8DecodeByteString, + utf8DecodeByteArray, utf8DecodeShortByteString, utf8CompareShortByteString, + utf8DecodeByteArrayLazy#, utf8DecodeStringLazy, utf8EncodeChar, utf8EncodeString, @@ -53,6 +56,7 @@ import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import Data.ByteString.Short.Internal (ShortByteString(..)) +import GHC.Word import GHC.Exts -- ----------------------------------------------------------------------------- @@ -131,15 +135,17 @@ utf8DecodeChar !(Ptr a#) = -- the start of the current character is, given any position in a -- stream. This function finds the start of the previous character, -- assuming there *is* a previous character. -utf8PrevChar :: Ptr Word8 -> IO (Ptr Word8) -utf8PrevChar p = utf8CharStart (p `plusPtr` (-1)) +utf8PrevChar :: ByteArray# -> Int -> Int +utf8PrevChar arr ofs = utf8CharStart arr (ofs - 1) -utf8CharStart :: Ptr Word8 -> IO (Ptr Word8) -utf8CharStart p = go p - where go p = do w <- peek p - if w >= 0x80 && w < 0xC0 - then go (p `plusPtr` (-1)) - else return p +utf8CharStart :: ByteArray# -> Int -> Int +utf8CharStart = go + where + go arr ofs@(I# ofs#) + | w >= 0x80 && w < 0xC0 = go arr (ofs - 1) + | otherwise = ofs + where + w = W8# (indexWord8Array# arr ofs#) {-# INLINE utf8DecodeLazy# #-} utf8DecodeLazy# :: (IO ()) -> (Int# -> (# Char#, Int# #)) -> Int# -> IO [Char] @@ -158,6 +164,12 @@ utf8DecodeByteString :: ByteString -> [Char] utf8DecodeByteString (BS.PS fptr offset len) = utf8DecodeStringLazy fptr offset len +utf8DecodeByteArrayLazy# :: ByteArray# -> Int# -> Int# -> [Char] +utf8DecodeByteArrayLazy# a# offset# len# + = unsafeDupablePerformIO $ + let decodeChar i = utf8DecodeCharByteArray# a# (i +# offset#) + in utf8DecodeLazy# (return ()) decodeChar len# + utf8DecodeStringLazy :: ForeignPtr Word8 -> Int -> Int -> [Char] utf8DecodeStringLazy fp offset (I# len#) = unsafeDupablePerformIO $ do @@ -200,12 +212,15 @@ utf8CompareShortByteString (SBS a1) (SBS a2) = go 0# 0# | isTrue# (b1_1 `ltWord#` b2_1) -> LT | otherwise -> go (off1 +# 1#) (off2 +# 1#) -utf8DecodeShortByteString :: ShortByteString -> [Char] -utf8DecodeShortByteString (SBS ba#) +utf8DecodeByteArray :: ByteArray# -> [Char] +utf8DecodeByteArray ba# = unsafeDupablePerformIO $ let len# = sizeofByteArray# ba# in utf8DecodeLazy# (return ()) (utf8DecodeCharByteArray# ba#) len# +utf8DecodeShortByteString :: ShortByteString -> [Char] +utf8DecodeShortByteString (SBS ba#) = utf8DecodeByteArray ba# + countUTF8Chars :: ShortByteString -> IO Int countUTF8Chars (SBS ba) = go 0# 0# where ===================================== testsuite/tests/parser/should_run/CountParserDeps.stdout ===================================== @@ -1,4 +1,4 @@ -Found 235 parser module dependencies +Found 236 parser module dependencies GHC.Builtin.Names GHC.Builtin.PrimOps GHC.Builtin.Types @@ -62,6 +62,7 @@ GHC.Core.Utils GHC.CoreToIface GHC.Data.Bag GHC.Data.BooleanFormula +GHC.Data.ByteArray GHC.Data.EnumSet GHC.Data.FastMutInt GHC.Data.FastString ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 25fa8fde84701c010fa466c2648f8f6d10265e8f +Subproject commit 81dcb5545c88a6113777c6d87cd687278356d3a3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/918211013cced851784c1f5ec5c68f97317f0f13...0f4327d893252acf6a7e7d4914a8168b2f16944e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/918211013cced851784c1f5ec5c68f97317f0f13...0f4327d893252acf6a7e7d4914a8168b2f16944e 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 Wed Nov 25 02:14:57 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 21:14:57 -0500 Subject: [Git][ghc/ghc][wip/keepAlive-the-return-of-the-primop] 15 commits: GHC.Data.ByteArray: Initial commit Message-ID: <5fbdbe21364d3_86c8b847fc1187f9@gitlab.mail> Ben Gamari pushed to branch wip/keepAlive-the-return-of-the-primop at Glasgow Haskell Compiler / GHC Commits: ece52044 by Ben Gamari at 2020-11-24T21:06:18-05:00 GHC.Data.ByteArray: Initial commit - - - - - 292bd5b4 by Ben Gamari at 2020-11-24T21:06:22-05:00 StringBuffer: Rid it of ForeignPtrs Bumps haddock submodule. - - - - - 8b53778c by Ben Gamari at 2020-11-24T21:06:22-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - a7f9997f by Ben Gamari at 2020-11-24T21:06:22-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 389717fc by Ben Gamari at 2020-11-24T21:06:22-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - 240498b1 by Ben Gamari at 2020-11-24T21:06:22-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - 0f4327d8 by Ben Gamari at 2020-11-24T21:06:22-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - c4ade229 by Ben Gamari at 2020-11-24T21:14:27-05:00 genprimopcode: Add a second levity-polymorphic tyvar This will be needed shortly. - - - - - a9345c24 by GHC GitLab CI at 2020-11-24T21:14:27-05:00 Introduce keepAlive primop - - - - - a687d17d by Ben Gamari at 2020-11-24T21:14:27-05:00 base: Use keepAlive# in withForeignPtr - - - - - 6ff6a0b6 by Ben Gamari at 2020-11-24T21:14:27-05:00 Implement withByteArrayContents in terms of keepAlive# - - - - - 9a922ddd by Ben Gamari at 2020-11-24T21:14:27-05:00 base: Implement GHC.ForeignPtr.Ops in terms of keepAlive# - - - - - 12993132 by Ben Gamari at 2020-11-24T21:14:27-05:00 base: Use keepAlive# in Foreign.Marshal.Alloc - - - - - c7e3b873 by Ben Gamari at 2020-11-24T21:14:27-05:00 ghc-compact: Use keepAlive# in GHC.Compact.Serialized - - - - - c80bd779 by Ben Gamari at 2020-11-24T21:14:27-05:00 testsuite: Accept - - - - - 23 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - + compiler/GHC/Data/ByteArray.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Utils/Binary.hs - compiler/ghc.cabal.in - libraries/base/Foreign/Marshal/Alloc.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/ForeignPtr.hs - libraries/base/GHC/ForeignPtr/Ops.hs - libraries/base/GHC/IO/Buffer.hs - libraries/bytestring - libraries/ghc-boot/GHC/Utils/Encoding.hs - libraries/ghc-compact/GHC/Compact/Serialized.hs - testsuite/tests/ghci/should_fail/T15055.stderr - testsuite/tests/package/package06e.stderr - testsuite/tests/package/package07e.stderr - testsuite/tests/package/package08e.stderr - testsuite/tests/parser/should_run/CountParserDeps.stdout - utils/genprimopcode/Main.hs - utils/haddock Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -2963,6 +2963,20 @@ primop NumSparks "numSparks#" GenPrimOp has_side_effects = True out_of_line = True + +------------------------------------------------------------------------ +section "Controlling object lifetime" + {Ensuring that objects don't die a premature death.} +------------------------------------------------------------------------ + +-- See Note [keepAlive# magic] in GHC.CoreToStg.Prep. +primop KeepAliveOp "keepAlive#" GenPrimOp + o -> State# RealWorld -> (State# RealWorld -> p) -> p + { TODO. } + with + strictness = { \ _arity -> mkClosedStrictSig [topDmd, topDmd, strictOnceApply1Dmd] topDiv } + + ------------------------------------------------------------------------ section "Tag to enum stuff" {Convert back and forth between values of enumerated types ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -1642,6 +1642,8 @@ app_ok primop_ok fun args -> False -- for the special cases for SeqOp and DataToTagOp | DataToTagOp <- op -> False + | KeepAliveOp <- op + -> False | otherwise -> primop_ok op -- Check the primop itself ===================================== compiler/GHC/CoreToStg/Prep.hs ===================================== @@ -32,7 +32,10 @@ import GHC.Tc.Utils.Env import GHC.Unit import GHC.Builtin.Names +import GHC.Builtin.PrimOps import GHC.Builtin.Types +import GHC.Builtin.Types.Prim ( realWorldStatePrimTy ) +import GHC.Types.Id.Make ( realWorldPrimId, mkPrimOpId ) import GHC.Core.Utils import GHC.Core.Opt.Arity @@ -47,6 +50,7 @@ import GHC.Core.TyCon import GHC.Core.DataCon import GHC.Core.Opt.OccurAnal + import GHC.Data.Maybe import GHC.Data.OrdList import GHC.Data.FastString @@ -63,7 +67,6 @@ import GHC.Types.Var.Set import GHC.Types.Var.Env import GHC.Types.Id import GHC.Types.Id.Info -import GHC.Types.Id.Make ( realWorldPrimId ) import GHC.Types.Basic import GHC.Types.Name ( NamedThing(..), nameSrcSpan, isInternalName ) import GHC.Types.SrcLoc ( SrcSpan(..), realSrcLocSpan, mkRealSrcLoc ) @@ -784,6 +787,38 @@ cpeApp top_env expr -- rather than the far superior "f x y". Test case is par01. = let (terminal, args', depth') = collect_args arg in cpe_app env terminal (args' ++ args) (depth + depth' - 1) + + cpe_app env + (Var f) + args + n + | Just KeepAliveOp <- isPrimOpId_maybe f + , CpeApp (Type arg_rep) + : CpeApp (Type arg_ty) + : CpeApp (Type _result_rep) + : CpeApp (Type result_ty) + : CpeApp arg + : CpeApp s0 + : CpeApp k + : rest <- pprTrace "cpe_app keepAlive#" (ppr args) args + = do { pprTraceM "cpe_app(keepAlive#)" (ppr n) + ; y <- newVar result_ty + ; s2 <- newVar realWorldStatePrimTy + ; -- beta reduce if possible + ; (floats, k') <- case k of + Lam s body -> cpe_app (extendCorePrepEnvExpr env s s0) body rest (n-2) + _ -> cpe_app env k (CpeApp s0 : rest) (n-1) + ; let touchId = mkPrimOpId TouchOp + expr = Case k' y result_ty [(DEFAULT, [], rhs)] + rhs = let scrut = mkApps (Var touchId) [Type arg_rep, Type arg_ty, arg, Var realWorldPrimId] + in Case scrut s2 result_ty [(DEFAULT, [], Var y)] + ; pprTraceM "cpe_app(keepAlive)" (ppr expr) + ; (floats', expr') <- cpeBody env expr + ; return (floats `appendFloats` floats', expr') + } + | Just KeepAliveOp <- isPrimOpId_maybe f + = panic "invalid keepAlive# application" + cpe_app env (Var f) (CpeApp _runtimeRep at Type{} : CpeApp _type at Type{} : CpeApp arg : rest) n | f `hasKey` runRWKey -- N.B. While it may appear that n == 1 in the case of runRW# ===================================== compiler/GHC/Data/ByteArray.hs ===================================== @@ -0,0 +1,285 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Data.ByteArray + ( -- * Immutable byte arrays + ByteArray + , getByteArray + , unsafeByteArrayContents + , withByteArrayContents + , sizeofByteArray + + -- * Mutable byte arrays + , MutableByteArray + , getMutableByteArray + , unsafeMutableByteArrayContents + , newMutableByteArray + , newPinnedMutableByteArray + , copyByteArray + , copyAddrToMutableByteArray + , unsafeFreezeByteArray + + -- * Writing + , writeWordArray + , writeWord8Array + , writeWord16Array + , writeWord32Array + , writeWord64Array + , writeIntArray + , writeInt8Array + , writeInt16Array + , writeInt32Array + , writeInt64Array + , writeCharArray + + -- * Reading + , readWordArray + , readWord8Array + , readWord16Array + , readWord32Array + , readWord64Array + , readIntArray + , readInt8Array + , readInt16Array + , readInt32Array + , readInt64Array + , readCharArray + + -- * Immutable indexing + , indexWordArray + , indexWord8Array + , indexWord16Array + , indexWord32Array + , indexWord64Array + , indexIntArray + , indexInt8Array + , indexInt16Array + , indexInt32Array + , indexInt64Array + , indexCharArray + ) where + +import GHC.Base +import GHC.Exts +import GHC.Word +import GHC.Int +import Unsafe.Coerce + +data MutableByteArray = MutableByteArray { getMutableByteArray :: !(MutableByteArray# RealWorld) } + +data ByteArray = ByteArray { getByteArray :: !ByteArray# } + +unsafeByteArrayContents :: ByteArray -> Ptr a +unsafeByteArrayContents (ByteArray ba) = Ptr (byteArrayContents# ba) + +unsafeMutableByteArrayContents :: MutableByteArray -> Ptr a +unsafeMutableByteArrayContents = unsafeByteArrayContents . unsafeCoerce + +withByteArrayContents :: ByteArray -> (Ptr a -> IO b) -> IO b +#if MIN_VERSION_base(4,15,0) +withByteArrayContents (ByteArray ba) f = + IO $ \s -> keepAlive# ba s (unIO (f (Ptr (byteArrayContents# ba)))) +#else +withByteArrayContents (ByteArray ba) f = do + r <- f $ Ptr (byteArrayContents# ba) + IO $ \s -> case touch# ba s of s' -> (# s', () #) + return r +#endif + +newMutableByteArray :: Int -> IO MutableByteArray +newMutableByteArray (I# size) = IO $ \s -> + case newByteArray# size s of + (# s', mba #) -> (# s', MutableByteArray mba #) + +newPinnedMutableByteArray :: Int -> IO MutableByteArray +newPinnedMutableByteArray (I# size) = IO $ \s -> + case newPinnedByteArray# size s of + (# s', mba #) -> (# s', MutableByteArray mba #) + +copyByteArray + :: ByteArray -- ^ source + -> Int -- ^ source offset + -> MutableByteArray -- ^ destination + -> Int -- ^ destination offset + -> Int -- ^ length to copy + -> IO () +copyByteArray (ByteArray src) (I# src_ofs) (MutableByteArray dst) (I# dst_ofs) (I# len) = + IO $ \s -> + case copyByteArray# src src_ofs dst dst_ofs len s of + s' -> (# s', () #) + +copyAddrToMutableByteArray :: Ptr a -> MutableByteArray -> Int -> Int -> IO () +copyAddrToMutableByteArray (Ptr src) (MutableByteArray dst) (I# dst_ofs) (I# len) = IO $ \s -> + case copyAddrToByteArray# src dst dst_ofs len s of + s' -> (# s', () #) + +unsafeFreezeByteArray + :: MutableByteArray + -> IO ByteArray +unsafeFreezeByteArray (MutableByteArray mba) = IO $ \s -> + case unsafeFreezeByteArray# mba s of + (# s', ba #) -> (# s', ByteArray ba #) + +sizeofByteArray :: ByteArray -> Int +sizeofByteArray (ByteArray arr) = I# (sizeofByteArray# arr) + + +readWordArray :: MutableByteArray -> Int -> IO Word +readWordArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWordArray# arr ix s0 of + (# s1, r #) -> (# s1, W# r #) + +readWord8Array :: MutableByteArray -> Int -> IO Word8 +readWord8Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord8Array# arr ix s0 of + (# s1, r #) -> (# s1, W8# r #) + +readWord16Array :: MutableByteArray -> Int -> IO Word16 +readWord16Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord16Array# arr ix s0 of + (# s1, r #) -> (# s1, W16# r #) + +readWord32Array :: MutableByteArray -> Int -> IO Word32 +readWord32Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord32Array# arr ix s0 of + (# s1, r #) -> (# s1, W32# r #) + +readWord64Array :: MutableByteArray -> Int -> IO Word64 +readWord64Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord64Array# arr ix s0 of + (# s1, r #) -> (# s1, W64# r #) + +readIntArray :: MutableByteArray -> Int -> IO Int +readIntArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readIntArray# arr ix s0 of + (# s1, r #) -> (# s1, I# r #) + +readInt8Array :: MutableByteArray -> Int -> IO Int8 +readInt8Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt8Array# arr ix s0 of + (# s1, r #) -> (# s1, I8# r #) + +readInt16Array :: MutableByteArray -> Int -> IO Int16 +readInt16Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt16Array# arr ix s0 of + (# s1, r #) -> (# s1, I16# r #) + +readInt32Array :: MutableByteArray -> Int -> IO Int32 +readInt32Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt32Array# arr ix s0 of + (# s1, r #) -> (# s1, I32# r #) + +readInt64Array :: MutableByteArray -> Int -> IO Int64 +readInt64Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt64Array# arr ix s0 of + (# s1, r #) -> (# s1, I64# r #) + +readCharArray :: MutableByteArray -> Int -> IO Char +readCharArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readCharArray# arr ix s0 of + (# s1, r #) -> (# s1, C# r #) + + + +writeWordArray :: MutableByteArray -> Int -> Word -> IO () +writeWordArray (MutableByteArray arr) (I# ix) (W# x) = IO $ \s0 -> + case writeWordArray# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord8Array :: MutableByteArray -> Int -> Word8 -> IO () +writeWord8Array (MutableByteArray arr) (I# ix) (W8# x) = IO $ \s0 -> + case writeWord8Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord16Array :: MutableByteArray -> Int -> Word16 -> IO () +writeWord16Array (MutableByteArray arr) (I# ix) (W16# x) = IO $ \s0 -> + case writeWord16Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord32Array :: MutableByteArray -> Int -> Word32 -> IO () +writeWord32Array (MutableByteArray arr) (I# ix) (W32# x) = IO $ \s0 -> + case writeWord32Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord64Array :: MutableByteArray -> Int -> Word64 -> IO () +writeWord64Array (MutableByteArray arr) (I# ix) (W64# x) = IO $ \s0 -> + case writeWord64Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeIntArray :: MutableByteArray -> Int -> Int -> IO () +writeIntArray (MutableByteArray arr) (I# ix) (I# x) = IO $ \s0 -> + case writeIntArray# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt8Array :: MutableByteArray -> Int -> Int8 -> IO () +writeInt8Array (MutableByteArray arr) (I# ix) (I8# x) = IO $ \s0 -> + case writeInt8Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt16Array :: MutableByteArray -> Int -> Int16 -> IO () +writeInt16Array (MutableByteArray arr) (I# ix) (I16# x) = IO $ \s0 -> + case writeInt16Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt32Array :: MutableByteArray -> Int -> Int32 -> IO () +writeInt32Array (MutableByteArray arr) (I# ix) (I32# x) = IO $ \s0 -> + case writeInt32Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt64Array :: MutableByteArray -> Int -> Int64 -> IO () +writeInt64Array (MutableByteArray arr) (I# ix) (I64# x) = IO $ \s0 -> + case writeInt64Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeCharArray :: MutableByteArray -> Int -> Char -> IO () +writeCharArray (MutableByteArray arr) (I# ix) (C# x) = IO $ \s0 -> + case writeCharArray# arr ix x s0 of + s1 -> (# s1, () #) + + + +indexWordArray :: ByteArray -> Int -> Word +indexWordArray (ByteArray arr) (I# ix) = + W# (indexWordArray# arr ix) + +indexWord8Array :: ByteArray -> Int -> Word8 +indexWord8Array (ByteArray arr) (I# ix) = + W8# (indexWord8Array# arr ix) + +indexWord16Array :: ByteArray -> Int -> Word16 +indexWord16Array (ByteArray arr) (I# ix) = + W16# (indexWord16Array# arr ix) + +indexWord32Array :: ByteArray -> Int -> Word32 +indexWord32Array (ByteArray arr) (I# ix) = + W32# (indexWord32Array# arr ix) + +indexWord64Array :: ByteArray -> Int -> Word64 +indexWord64Array (ByteArray arr) (I# ix) = + W64# (indexWord64Array# arr ix) + +indexIntArray :: ByteArray -> Int -> Int +indexIntArray (ByteArray arr) (I# ix) = + I# (indexIntArray# arr ix) + +indexInt8Array :: ByteArray -> Int -> Int8 +indexInt8Array (ByteArray arr) (I# ix) = + I8# (indexInt8Array# arr ix) + +indexInt16Array :: ByteArray -> Int -> Int16 +indexInt16Array (ByteArray arr) (I# ix) = + I16# (indexInt16Array# arr ix) + +indexInt32Array :: ByteArray -> Int -> Int32 +indexInt32Array (ByteArray arr) (I# ix) = + I32# (indexInt32Array# arr ix) + +indexInt64Array :: ByteArray -> Int -> Int64 +indexInt64Array (ByteArray arr) (I# ix) = + I64# (indexInt64Array# arr ix) + +indexCharArray :: ByteArray -> Int -> Char +indexCharArray (ByteArray arr) (I# ix) = + C# (indexCharArray# arr ix) + ===================================== compiler/GHC/Data/StringBuffer.hs ===================================== @@ -17,7 +17,7 @@ Buffers for scanning string input stored in external arrays. module GHC.Data.StringBuffer ( - StringBuffer(..), + StringBuffer, len, cur, -- non-abstract for vs\/HaskellService -- * Creation\/destruction @@ -26,6 +26,7 @@ module GHC.Data.StringBuffer hPutStringBuffer, appendStringBuffers, stringToStringBuffer, + byteStringToStringBuffer, -- * Inspection nextChar, @@ -54,10 +55,13 @@ import GHC.Prelude import GHC.Utils.Encoding import GHC.Data.FastString +import GHC.Data.ByteArray import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain import GHC.Utils.Misc +import qualified Data.ByteString as BS +import qualified Data.ByteString.Unsafe as BS import Data.Maybe import Control.Exception import System.IO @@ -65,6 +69,7 @@ import System.IO.Unsafe ( unsafePerformIO ) import GHC.IO.Encoding.UTF8 ( mkUTF8 ) import GHC.IO.Encoding.Failure ( CodingFailureMode(IgnoreCodingFailure) ) +import GHC.Word import GHC.Exts import Foreign @@ -81,7 +86,7 @@ import Foreign -- data StringBuffer = StringBuffer { - buf :: {-# UNPACK #-} !(ForeignPtr Word8), + buf :: {-# UNPACK #-} !ByteArray, len :: {-# UNPACK #-} !Int, -- length cur :: {-# UNPACK #-} !Int -- current pos } @@ -102,34 +107,35 @@ instance Show StringBuffer where -- managed by the garbage collector. hGetStringBuffer :: FilePath -> IO StringBuffer hGetStringBuffer fname = do - h <- openBinaryFile fname ReadMode - size_i <- hFileSize h - offset_i <- skipBOM h size_i 0 -- offset is 0 initially - let size = fromIntegral $ size_i - offset_i - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> do - r <- if size == 0 then return 0 else hGetBuf h ptr size - hClose h - if (r /= size) - then ioError (userError "short read of file") - else newUTF8StringBuffer buf ptr size + h <- openBinaryFile fname ReadMode + size_i <- hFileSize h + offset_i <- skipBOM h size_i 0 -- offset is 0 initially + let size = fromIntegral $ size_i - offset_i + buf <- newPinnedMutableByteArray (size+3) + r <- if size == 0 + then return 0 + else hGetBuf h (unsafeMutableByteArrayContents buf) size + hClose h + if r /= size + then ioError (userError "short read of file") + else newUTF8StringBuffer buf size hGetStringBufferBlock :: Handle -> Int -> IO StringBuffer -hGetStringBufferBlock handle wanted - = do size_i <- hFileSize handle - offset_i <- hTell handle >>= skipBOM handle size_i - let size = min wanted (fromIntegral $ size_i-offset_i) - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> - do r <- if size == 0 then return 0 else hGetBuf handle ptr size - if r /= size - then ioError (userError $ "short read of file: "++show(r,size,size_i,handle)) - else newUTF8StringBuffer buf ptr size +hGetStringBufferBlock handle wanted = do + size_i <- hFileSize handle + offset_i <- hTell handle >>= skipBOM handle size_i + let size = min wanted (fromIntegral $ size_i-offset_i) + buf <- newPinnedMutableByteArray (size+3) + r <- if size == 0 + then return 0 + else hGetBuf handle (unsafeMutableByteArrayContents buf) size + if r /= size + then ioError (userError $ "short read of file: "++show(r,size,size_i,handle)) + else newUTF8StringBuffer buf size hPutStringBuffer :: Handle -> StringBuffer -> IO () -hPutStringBuffer hdl (StringBuffer buf len cur) - = withForeignPtr (plusForeignPtr buf cur) $ \ptr -> - hPutBuf hdl ptr len +hPutStringBuffer hdl (StringBuffer buf len cur) = do + withByteArrayContents buf $ \ptr -> hPutBuf hdl (ptr `plusPtr` cur) len -- | Skip the byte-order mark if there is one (see #1744 and #6016), -- and return the new position of the handle in bytes. @@ -156,39 +162,45 @@ skipBOM h size offset = where safeEncoding = mkUTF8 IgnoreCodingFailure -newUTF8StringBuffer :: ForeignPtr Word8 -> Ptr Word8 -> Int -> IO StringBuffer -newUTF8StringBuffer buf ptr size = do - pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0] +-- | @newUTF8StringBuffer buf size@ creates a 'StringBuffer' from a +-- 'MutableByteArray' of length @size+3@ containing UTF-8 encoded text. A three +-- byte sentinel will be added to the end of the buffer. +newUTF8StringBuffer :: MutableByteArray -> Int -> IO StringBuffer +newUTF8StringBuffer buf size = do -- sentinels for UTF-8 decoding - return $ StringBuffer buf size 0 + writeWord8Array buf (size+0) 0 + writeWord8Array buf (size+1) 0 + writeWord8Array buf (size+3) 0 + buf' <- unsafeFreezeByteArray buf + return $ StringBuffer buf' size 0 appendStringBuffers :: StringBuffer -> StringBuffer -> IO StringBuffer -appendStringBuffers sb1 sb2 - = do newBuf <- mallocForeignPtrArray (size+3) - withForeignPtr newBuf $ \ptr -> - withForeignPtr (buf sb1) $ \sb1Ptr -> - withForeignPtr (buf sb2) $ \sb2Ptr -> - do copyArray ptr (sb1Ptr `advancePtr` cur sb1) sb1_len - copyArray (ptr `advancePtr` sb1_len) (sb2Ptr `advancePtr` cur sb2) sb2_len - pokeArray (ptr `advancePtr` size) [0,0,0] - return (StringBuffer newBuf size 0) - where sb1_len = calcLen sb1 - sb2_len = calcLen sb2 - calcLen sb = len sb - cur sb - size = sb1_len + sb2_len +appendStringBuffers sb1 sb2 = do + dst <- newPinnedMutableByteArray (size+3) + copyByteArray (buf sb1) (cur sb1) dst 0 sb1_len + copyByteArray (buf sb2) (cur sb2) dst sb1_len sb2_len + newUTF8StringBuffer dst size + where + sb1_len = calcLen sb1 + sb2_len = calcLen sb2 + calcLen sb = len sb - cur sb + size = sb1_len + sb2_len + +byteStringToStringBuffer :: BS.ByteString -> StringBuffer +byteStringToStringBuffer bs = unsafePerformIO $ do + let size = BS.length bs + buf <- newPinnedMutableByteArray (size+3) + BS.unsafeUseAsCString bs (\p -> copyAddrToMutableByteArray p buf 0 size) + newUTF8StringBuffer buf size -- | Encode a 'String' into a 'StringBuffer' as UTF-8. The resulting buffer -- is automatically managed by the garbage collector. stringToStringBuffer :: String -> StringBuffer -stringToStringBuffer str = - unsafePerformIO $ do +stringToStringBuffer str = unsafePerformIO $ do let size = utf8EncodedLength str - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> do - utf8EncodeString ptr str - pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0] - -- sentinels for UTF-8 decoding - return (StringBuffer buf size 0) + buf <- newPinnedMutableByteArray (size+3) + utf8EncodeString (unsafeMutableByteArrayContents buf) str + newUTF8StringBuffer buf size -- ----------------------------------------------------------------------------- -- Grab a character @@ -202,12 +214,10 @@ stringToStringBuffer str = nextChar :: StringBuffer -> (Char,StringBuffer) nextChar (StringBuffer buf len (I# cur#)) = -- Getting our fingers dirty a little here, but this is performance-critical - inlinePerformIO $ - withForeignPtr buf $ \(Ptr a#) -> - case utf8DecodeCharAddr# (a# `plusAddr#` cur#) 0# of - (# c#, nBytes# #) -> - let cur' = I# (cur# +# nBytes#) in - return (C# c#, StringBuffer buf len cur') + case utf8DecodeCharByteArray# (getByteArray buf) cur# of + (# c#, nBytes# #) -> + let cur' = I# (cur# +# nBytes#) + in (C# c#, StringBuffer buf len cur') -- | Return the first UTF-8 character of a nonempty 'StringBuffer' (analogous -- to 'Data.List.head'). __Warning:__ The behavior is undefined if the @@ -219,10 +229,9 @@ currentChar = fst . nextChar prevChar :: StringBuffer -> Char -> Char prevChar (StringBuffer _ _ 0) deflt = deflt prevChar (StringBuffer buf _ cur) _ = - inlinePerformIO $ - withForeignPtr buf $ \p -> do - p' <- utf8PrevChar (p `plusPtr` cur) - return (fst (utf8DecodeChar p')) + let !(I# p') = utf8PrevChar (getByteArray buf) cur + !(# c, _ #) = utf8DecodeCharByteArray# (getByteArray buf) p' + in C# c -- ----------------------------------------------------------------------------- -- Moving @@ -257,18 +266,18 @@ atEnd (StringBuffer _ l c) = l == c -- wanted line. Lines begin at 1. atLine :: Int -> StringBuffer -> Maybe StringBuffer atLine line sb@(StringBuffer buf len _) = - inlinePerformIO $ - withForeignPtr buf $ \p -> do - p' <- skipToLine line len p - if p' == nullPtr - then return Nothing - else - let - delta = p' `minusPtr` p - in return $ Just (sb { cur = delta - , len = len - delta - }) - + inlinePerformIO $ withByteArrayContents buf $ \p -> do + p' <- skipToLine line len p + if p' == nullPtr + then return Nothing + else + let !delta = p' `minusPtr` p + in return $ Just (sb { cur = delta + , len = len - delta + }) + +-- | @skipToLine line len op0@ finds the byte offset to the beginning of +-- the given line number. skipToLine :: Int -> Int -> Ptr Word8 -> IO (Ptr Word8) skipToLine !line !len !op0 = go 1 op0 where @@ -300,39 +309,42 @@ lexemeToString :: StringBuffer -> Int -- ^ @n@, the number of bytes -> String lexemeToString _ 0 = "" -lexemeToString (StringBuffer buf _ cur) bytes = - utf8DecodeStringLazy buf cur bytes +lexemeToString (StringBuffer buf _ (I# cur#)) (I# bytes#) = + utf8DecodeByteArrayLazy# (getByteArray buf) cur# bytes# lexemeToFastString :: StringBuffer -> Int -- ^ @n@, the number of bytes -> FastString lexemeToFastString _ 0 = nilFS lexemeToFastString (StringBuffer buf _ cur) len = - inlinePerformIO $ - withForeignPtr buf $ \ptr -> - return $! mkFastStringBytes (ptr `plusPtr` cur) len + inlinePerformIO $ + withByteArrayContents buf $ \ptr -> + return $! mkFastStringBytes (ptr `plusPtr` cur) len -- | Return the previous @n@ characters (or fewer if we are less than @n@ -- characters into the buffer. decodePrevNChars :: Int -> StringBuffer -> String -decodePrevNChars n (StringBuffer buf _ cur) = - inlinePerformIO $ withForeignPtr buf $ \p0 -> - go p0 n "" (p0 `plusPtr` (cur - 1)) +decodePrevNChars n (StringBuffer buf0 _ cur) = + go (getByteArray buf0) (min n (cur - 1)) "" (cur - 1) where - go :: Ptr Word8 -> Int -> String -> Ptr Word8 -> IO String - go buf0 n acc p | n == 0 || buf0 >= p = return acc - go buf0 n acc p = do - p' <- utf8PrevChar p - let (c,_) = utf8DecodeChar p' - go buf0 (n - 1) (c:acc) p' + go :: ByteArray# -> Int -> String -> Int -> String + go buf n acc ofs + | n == 0 = acc + | otherwise = + let !ofs'@(I# ofs'#) = utf8PrevChar buf ofs + !(# c,_ #) = utf8DecodeCharByteArray# buf ofs'# + in go buf (n - 1) (C# c:acc) ofs' -- ----------------------------------------------------------------------------- -- Parsing integer strings in various bases parseUnsignedInteger :: StringBuffer -> Int -> Integer -> (Char->Int) -> Integer -parseUnsignedInteger (StringBuffer buf _ cur) len radix char_to_int - = inlinePerformIO $ withForeignPtr buf $ \ptr -> return $! let - go i x | i == len = x - | otherwise = case fst (utf8DecodeChar (ptr `plusPtr` (cur + i))) of - '_' -> go (i + 1) x -- skip "_" (#14473) - char -> go (i + 1) (x * radix + toInteger (char_to_int char)) - in go 0 0 +parseUnsignedInteger (StringBuffer buf _ (I# cur)) (I# len) radix char_to_int + = go (len +# cur) cur 0 + where + go :: Int# -> Int# -> Integer -> Integer + go end i !acc + | isTrue# (i ==# end) = acc + | otherwise = + case utf8DecodeCharByteArray# (getByteArray buf) i of + (# '_'#, _ #) -> go end (i +# 1#) acc -- skip "_" (#14473) + (# char, _ #) -> go end (i +# 1#) (acc * radix + toInteger (char_to_int (C# char))) ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1541,6 +1541,8 @@ emitPrimOp dflags primop = case primop of TraceMarkerOp -> alwaysExternal SetThreadAllocationCounter -> alwaysExternal + KeepAliveOp -> panic "keepAlive# should have been eliminated in CorePrep" + where profile = targetProfile dflags platform = profilePlatform profile ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised @@ -84,6 +85,7 @@ import Data.Array import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import GHC.ForeignPtr import Data.IORef import Data.Char ( ord, chr ) import Data.Time @@ -96,7 +98,10 @@ import GHC.Real ( Ratio(..) ) type BinArray = ForeignPtr Word8 - +#if !MIN_VERSION_base(4,15,0) +unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b +unsafeWithForeignPtr = withForeignPtr +#endif --------------------------------------------------------------- -- BinData @@ -111,14 +116,14 @@ instance Binary BinData where put_ bh (BinData sz dat) = do put_ bh sz putPrim bh sz $ \dest -> - withForeignPtr dat $ \orig -> + unsafeWithForeignPtr dat $ \orig -> copyBytes dest orig sz -- get bh = do sz <- get bh dat <- mallocForeignPtrBytes sz getPrim bh sz $ \orig -> - withForeignPtr dat $ \dest -> + unsafeWithForeignPtr dat $ \dest -> copyBytes dest orig sz return (BinData sz dat) @@ -226,7 +231,7 @@ writeBinMem (BinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode arr <- readIORef arr_r ix <- readFastMutInt ix_r - withForeignPtr arr $ \p -> hPutBuf h p ix + unsafeWithForeignPtr arr $ \p -> hPutBuf h p ix hClose h readBinMem :: FilePath -> IO BinHandle @@ -236,7 +241,7 @@ readBinMem filename = do filesize' <- hFileSize h let filesize = fromIntegral filesize' arr <- mallocForeignPtrBytes filesize - count <- withForeignPtr arr $ \p -> hGetBuf h p filesize + count <- unsafeWithForeignPtr arr $ \p -> hGetBuf h p filesize when (count /= filesize) $ error ("Binary.readBinMem: only read " ++ show count ++ " bytes") hClose h @@ -280,7 +285,7 @@ putPrim h@(BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ expandBin h (ix + size) arr <- readIORef arr_r - withForeignPtr arr $ \op -> f (op `plusPtr` ix) + unsafeWithForeignPtr arr $ \op -> f (op `plusPtr` ix) writeFastMutInt ix_r (ix + size) -- -- | Similar to putPrim but advances the index by the actual number of @@ -302,7 +307,10 @@ getPrim (BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing) arr <- readIORef arr_r - w <- withForeignPtr arr $ \op -> f (op `plusPtr` ix) + w <- f (unsafeForeignPtrToPtr arr `plusPtr` ix) + touchForeignPtr arr + -- This is safe WRT #17760 as we we guarantee that the above line doesn't + -- diverge writeFastMutInt ix_r (ix + size) return w ===================================== compiler/ghc.cabal.in ===================================== @@ -356,6 +356,7 @@ Library GHC.Data.Bag GHC.Data.Bitmap GHC.Data.BooleanFormula + GHC.Data.ByteArray GHC.Data.EnumSet GHC.Data.FastMutInt GHC.Data.FastString ===================================== libraries/base/Foreign/Marshal/Alloc.hs ===================================== @@ -116,19 +116,6 @@ alloca :: forall a b . Storable a => (Ptr a -> IO b) -> IO b alloca = allocaBytesAligned (sizeOf (undefined :: a)) (alignment (undefined :: a)) --- Note [NOINLINE for touch#] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~ --- Both allocaBytes and allocaBytesAligned use the touch#, which is notoriously --- fragile in the presence of simplification (see #14346). In particular, the --- simplifier may drop the continuation containing the touch# if it can prove --- that the action passed to allocaBytes will not return. The hack introduced to --- fix this for 8.2.2 is to mark allocaBytes as NOINLINE, ensuring that the --- simplifier can't see the divergence. --- --- These can be removed once #14375 is fixed, which suggests that we instead do --- away with touch# in favor of a primitive that will capture the scoping left --- implicit in the case of touch#. - -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument -- a pointer to a temporarily allocated block of memory of @n@ bytes. -- The block of memory is sufficiently aligned for any of the basic @@ -143,12 +130,8 @@ allocaBytes (I# size) action = IO $ \ s0 -> case unsafeFreezeByteArray# mbarr# s1 of { (# s2, barr# #) -> let addr = Ptr (byteArrayContents# barr#) in case action addr of { IO action' -> - case action' s2 of { (# s3, r #) -> - case touch# barr# s3 of { s4 -> - (# s4, r #) - }}}}} --- See Note [NOINLINE for touch#] -{-# NOINLINE allocaBytes #-} + keepAlive# barr# s2 action' + }}} allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> @@ -156,12 +139,8 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> case unsafeFreezeByteArray# mbarr# s1 of { (# s2, barr# #) -> let addr = Ptr (byteArrayContents# barr#) in case action addr of { IO action' -> - case action' s2 of { (# s3, r #) -> - case touch# barr# s3 of { s4 -> - (# s4, r #) - }}}}} --- See Note [NOINLINE for touch#] -{-# NOINLINE allocaBytesAligned #-} + keepAlive# barr# s2 action' + }}} -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the size needed to store values of type @b at . The returned pointer ===================================== libraries/base/GHC/Event/Array.hs ===================================== @@ -33,7 +33,7 @@ import Foreign.ForeignPtr (ForeignPtr, withForeignPtr) import Foreign.Ptr (Ptr, nullPtr, plusPtr) import Foreign.Storable (Storable(..)) import GHC.Base hiding (empty) -import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_) +import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_, unsafeWithForeignPtr) import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (show) @@ -78,9 +78,9 @@ reallocArray p newSize oldSize = reallocHack undefined p reallocHack dummy src = do let size = sizeOf dummy dst <- mallocPlainForeignPtrBytes (newSize * size) - withForeignPtr src $ \s -> + unsafeWithForeignPtr src $ \s -> when (s /= nullPtr && oldSize > 0) . - withForeignPtr dst $ \d -> do + unsafeWithForeignPtr dst $ \d -> do _ <- memcpy d s (fromIntegral (oldSize * size)) return () return dst @@ -99,8 +99,8 @@ duplicate a = dupHack undefined a dupHack dummy (Array ref) = do AC es len cap <- readIORef ref ary <- allocArray cap - withForeignPtr ary $ \dest -> - withForeignPtr es $ \src -> do + unsafeWithForeignPtr ary $ \dest -> + unsafeWithForeignPtr es $ \src -> do _ <- memcpy dest src (fromIntegral (len * sizeOf dummy)) return () Array `fmap` newIORef (AC ary len cap) @@ -119,8 +119,8 @@ unsafeRead :: Storable a => Array a -> Int -> IO a unsafeRead (Array ref) ix = do AC es _ cap <- readIORef ref CHECK_BOUNDS("unsafeRead",cap,ix) - withForeignPtr es $ \p -> - peekElemOff p ix + unsafeWithForeignPtr es $ \ptr -> peekElemOff ptr ix + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge unsafeWrite :: Storable a => Array a -> Int -> a -> IO () unsafeWrite (Array ref) ix a = do @@ -130,13 +130,15 @@ unsafeWrite (Array ref) ix a = do unsafeWrite' :: Storable a => AC a -> Int -> a -> IO () unsafeWrite' (AC es _ cap) ix a = CHECK_BOUNDS("unsafeWrite'",cap,ix) - withForeignPtr es $ \p -> - pokeElemOff p ix a + unsafeWithForeignPtr es $ \ptr -> pokeElemOff ptr ix a + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge +-- | Precondition: continuation must not diverge due to use of +-- 'unsafeWithForeignPtr'. unsafeLoad :: Array a -> (Ptr a -> Int -> IO Int) -> IO Int unsafeLoad (Array ref) load = do AC es _ cap <- readIORef ref - len' <- withForeignPtr es $ \p -> load p cap + len' <- unsafeWithForeignPtr es $ \p -> load p cap writeIORef ref (AC es len' cap) return len' @@ -146,7 +148,7 @@ unsafeCopyFromBuffer :: Storable a => Array a -> Ptr a -> Int -> IO () unsafeCopyFromBuffer (Array ref) sptr n = readIORef ref >>= \(AC es _ cap) -> CHECK_BOUNDS("unsafeCopyFromBuffer", cap, n) - withForeignPtr es $ \pdest -> do + unsafeWithForeignPtr es $ \pdest -> do let size = sizeOfPtr sptr undefined _ <- memcpy pdest sptr (fromIntegral $ n * size) writeIORef ref (AC es n cap) @@ -198,7 +200,7 @@ forM_ ary g = forHack ary g undefined AC es len _ <- readIORef ref let size = sizeOf dummy offset = len * size - withForeignPtr es $ \p -> do + unsafeWithForeignPtr es $ \p -> do let go n | n >= offset = return () | otherwise = do f =<< peek (p `plusPtr` n) @@ -269,8 +271,8 @@ copy' d dstart s sstart maxCount = copyHack d s undefined then return dac else do AC dst dlen dcap <- ensureCapacity' dac (dstart + count) - withForeignPtr dst $ \dptr -> - withForeignPtr src $ \sptr -> do + unsafeWithForeignPtr dst $ \dptr -> + unsafeWithForeignPtr src $ \sptr -> do _ <- memcpy (dptr `plusPtr` (dstart * size)) (sptr `plusPtr` (sstart * size)) (fromIntegral (count * size)) @@ -286,7 +288,7 @@ removeAt a i = removeHack a undefined let size = sizeOf dummy newLen = oldLen - 1 when (newLen > 0 && i < newLen) . - withForeignPtr fp $ \ptr -> do + unsafeWithForeignPtr fp $ \ptr -> do _ <- memmove (ptr `plusPtr` (size * i)) (ptr `plusPtr` (size * (i+1))) (fromIntegral (size * (newLen-i))) ===================================== libraries/base/GHC/ForeignPtr.hs ===================================== @@ -526,7 +526,9 @@ withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b -- or from the object pointed to by the -- 'ForeignPtr', using the operations from the -- 'Storable' class. -withForeignPtr = unsafeWithForeignPtr +withForeignPtr fo@(ForeignPtr _ r) f = IO $ \s -> + case f (unsafeForeignPtrToPtr fo) of + IO action# -> keepAlive# r s action# -- | This is similar to 'withForeignPtr' but comes with an important caveat: -- the user must guarantee that the continuation does not diverge (e.g. loop or ===================================== libraries/base/GHC/ForeignPtr/Ops.hs ===================================== @@ -51,121 +51,114 @@ import GHC.Word import GHC.Int import GHC.Base import GHC.ForeignPtr -import GHC.Ptr - -withFP :: ForeignPtr a - -> (Addr# -> State# RealWorld -> (# State# RealWorld, b #)) - -> IO b -withFP fp f = - withForeignPtr fp (\(Ptr addr) -> IO (f addr)) peekWord8ForeignPtr :: ForeignPtr ty -> Int -> IO Word8 -peekWord8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord8OffAddr# addr d s0 of +peekWord8ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord8OffAddr# addr d) of (# s1, r #) -> (# s1, W8# r #) peekWord16ForeignPtr :: ForeignPtr ty -> Int -> IO Word16 -peekWord16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord16OffAddr# addr d s0 of +peekWord16ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord16OffAddr# addr d) of (# s1, r #) -> (# s1, W16# r #) peekWord32ForeignPtr :: ForeignPtr ty -> Int -> IO Word32 -peekWord32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord32OffAddr# addr d s0 of +peekWord32ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord32OffAddr# addr d) of (# s1, r #) -> (# s1, W32# r #) peekWord64ForeignPtr :: ForeignPtr ty -> Int -> IO Word64 -peekWord64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord64OffAddr# addr d s0 of +peekWord64ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord64OffAddr# addr d) of (# s1, r #) -> (# s1, W64# r #) peekWordForeignPtr :: ForeignPtr ty -> Int -> IO Word -peekWordForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord64OffAddr# addr d s0 of +peekWordForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord64OffAddr# addr d) of (# s1, r #) -> (# s1, W# r #) peekInt8ForeignPtr :: ForeignPtr ty -> Int -> IO Int8 -peekInt8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt8ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I8# r #) peekInt16ForeignPtr :: ForeignPtr ty -> Int -> IO Int16 -peekInt16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt16ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I16# r #) peekInt32ForeignPtr :: ForeignPtr ty -> Int -> IO Int32 -peekInt32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt32ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I32# r #) peekInt64ForeignPtr :: ForeignPtr ty -> Int -> IO Int64 -peekInt64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt64ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I64# r #) peekIntForeignPtr :: ForeignPtr ty -> Int -> IO Int -peekIntForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekIntForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I# r #) peekCharForeignPtr :: ForeignPtr ty -> Int -> IO Char -peekCharForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readCharOffAddr# addr d s0 of +peekCharForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readCharOffAddr# addr d) of (# s1, r #) -> (# s1, C# r #) pokeWord8ForeignPtr :: ForeignPtr ty -> Int -> Word8 -> IO () -pokeWord8ForeignPtr fp (I# d) (W8# n) = withFP fp $ \addr s0 -> - case writeWord8OffAddr# addr d n s0 of +pokeWord8ForeignPtr (ForeignPtr addr c) (I# d) (W8# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord8OffAddr# addr d n) of s1 -> (# s1, () #) pokeWord16ForeignPtr :: ForeignPtr ty -> Int -> Word16 -> IO () -pokeWord16ForeignPtr fp (I# d) (W16# n) = withFP fp $ \addr s0 -> - case writeWord16OffAddr# addr d n s0 of +pokeWord16ForeignPtr (ForeignPtr addr c) (I# d) (W16# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord16OffAddr# addr d n) of s1 -> (# s1, () #) pokeWord32ForeignPtr :: ForeignPtr ty -> Int -> Word32 -> IO () -pokeWord32ForeignPtr fp (I# d) (W32# n) = withFP fp $ \addr s0 -> - case writeWord32OffAddr# addr d n s0 of +pokeWord32ForeignPtr (ForeignPtr addr c) (I# d) (W32# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord32OffAddr# addr d n) of s1 -> (# s1, () #) pokeWord64ForeignPtr :: ForeignPtr ty -> Int -> Word64 -> IO () -pokeWord64ForeignPtr fp (I# d) (W64# n) = withFP fp $ \addr s0 -> - case writeWord64OffAddr# addr d n s0 of +pokeWord64ForeignPtr (ForeignPtr addr c) (I# d) (W64# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord64OffAddr# addr d n) of s1 -> (# s1, () #) pokeWordForeignPtr :: ForeignPtr ty -> Int -> Word -> IO () -pokeWordForeignPtr fp (I# d) (W# n) = withFP fp $ \addr s0 -> - case writeWord64OffAddr# addr d n s0 of +pokeWordForeignPtr (ForeignPtr addr c) (I# d) (W# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord64OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt8ForeignPtr :: ForeignPtr ty -> Int -> Int8 -> IO () -pokeInt8ForeignPtr fp (I# d) (I8# n) = withFP fp $ \addr s0 -> - case writeInt8OffAddr# addr d n s0 of +pokeInt8ForeignPtr (ForeignPtr addr c) (I# d) (I8# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt8OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt16ForeignPtr :: ForeignPtr ty -> Int -> Int16 -> IO () -pokeInt16ForeignPtr fp (I# d) (I16# n) = withFP fp $ \addr s0 -> - case writeInt16OffAddr# addr d n s0 of +pokeInt16ForeignPtr (ForeignPtr addr c) (I# d) (I16# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt16OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt32ForeignPtr :: ForeignPtr ty -> Int -> Int32 -> IO () -pokeInt32ForeignPtr fp (I# d) (I32# n) = withFP fp $ \addr s0 -> - case writeInt32OffAddr# addr d n s0 of +pokeInt32ForeignPtr (ForeignPtr addr c) (I# d) (I32# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt32OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt64ForeignPtr :: ForeignPtr ty -> Int -> Int64 -> IO () -pokeInt64ForeignPtr fp (I# d) (I64# n) = withFP fp $ \addr s0 -> - case writeInt64OffAddr# addr d n s0 of +pokeInt64ForeignPtr (ForeignPtr addr c) (I# d) (I64# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt64OffAddr# addr d n) of s1 -> (# s1, () #) pokeIntForeignPtr :: ForeignPtr ty -> Int -> Int -> IO () -pokeIntForeignPtr fp (I# d) (I# n) = withFP fp $ \addr s0 -> - case writeInt64OffAddr# addr d n s0 of +pokeIntForeignPtr (ForeignPtr addr c) (I# d) (I# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt64OffAddr# addr d n) of s1 -> (# s1, () #) pokeCharForeignPtr :: ForeignPtr ty -> Int -> Char -> IO () -pokeCharForeignPtr fp (I# d) (C# n) = withFP fp $ \addr s0 -> - case writeCharOffAddr# addr d n s0 of +pokeCharForeignPtr (ForeignPtr addr c) (I# d) (C# n) = IO $ \s0 -> + case keepAlive# c s0 (writeCharOffAddr# addr d n) of s1 -> (# s1, () #) ===================================== libraries/base/GHC/IO/Buffer.hs ===================================== @@ -73,6 +73,7 @@ import GHC.Show import GHC.Real import GHC.List import GHC.ForeignPtr.Ops +import GHC.ForeignPtr (unsafeWithForeignPtr) import Foreign.C.Types import Foreign.ForeignPtr import Foreign.Storable @@ -118,17 +119,17 @@ type CharBufElem = Char type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char -peekCharBuf arr ix = withForeignPtr arr $ \p -> do +peekCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> do (c,_) <- readCharBufPtr p ix return c {-# INLINE readCharBuf #-} readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) -readCharBuf arr ix = withForeignPtr arr $ \p -> readCharBufPtr p ix +readCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> readCharBufPtr p ix {-# INLINE writeCharBuf #-} writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int -writeCharBuf arr ix c = withForeignPtr arr $ \p -> writeCharBufPtr p ix c +writeCharBuf arr ix c = unsafeWithForeignPtr arr $ \p -> writeCharBufPtr p ix c {-# INLINE readCharBufPtr #-} readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit e043aacfc4202a59ccae8b8c8cf0e1ad83a3f209 +Subproject commit 4cbf0cd6053411139a08ff67c7ec5eae1da87b03 ===================================== libraries/ghc-boot/GHC/Utils/Encoding.hs ===================================== @@ -17,12 +17,15 @@ module GHC.Utils.Encoding ( -- * UTF-8 utf8DecodeCharAddr#, + utf8DecodeCharByteArray#, utf8PrevChar, utf8CharStart, utf8DecodeChar, utf8DecodeByteString, + utf8DecodeByteArray, utf8DecodeShortByteString, utf8CompareShortByteString, + utf8DecodeByteArrayLazy#, utf8DecodeStringLazy, utf8EncodeChar, utf8EncodeString, @@ -53,6 +56,7 @@ import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import Data.ByteString.Short.Internal (ShortByteString(..)) +import GHC.Word import GHC.Exts -- ----------------------------------------------------------------------------- @@ -131,15 +135,17 @@ utf8DecodeChar !(Ptr a#) = -- the start of the current character is, given any position in a -- stream. This function finds the start of the previous character, -- assuming there *is* a previous character. -utf8PrevChar :: Ptr Word8 -> IO (Ptr Word8) -utf8PrevChar p = utf8CharStart (p `plusPtr` (-1)) +utf8PrevChar :: ByteArray# -> Int -> Int +utf8PrevChar arr ofs = utf8CharStart arr (ofs - 1) -utf8CharStart :: Ptr Word8 -> IO (Ptr Word8) -utf8CharStart p = go p - where go p = do w <- peek p - if w >= 0x80 && w < 0xC0 - then go (p `plusPtr` (-1)) - else return p +utf8CharStart :: ByteArray# -> Int -> Int +utf8CharStart = go + where + go arr ofs@(I# ofs#) + | w >= 0x80 && w < 0xC0 = go arr (ofs - 1) + | otherwise = ofs + where + w = W8# (indexWord8Array# arr ofs#) {-# INLINE utf8DecodeLazy# #-} utf8DecodeLazy# :: (IO ()) -> (Int# -> (# Char#, Int# #)) -> Int# -> IO [Char] @@ -158,6 +164,12 @@ utf8DecodeByteString :: ByteString -> [Char] utf8DecodeByteString (BS.PS fptr offset len) = utf8DecodeStringLazy fptr offset len +utf8DecodeByteArrayLazy# :: ByteArray# -> Int# -> Int# -> [Char] +utf8DecodeByteArrayLazy# a# offset# len# + = unsafeDupablePerformIO $ + let decodeChar i = utf8DecodeCharByteArray# a# (i +# offset#) + in utf8DecodeLazy# (return ()) decodeChar len# + utf8DecodeStringLazy :: ForeignPtr Word8 -> Int -> Int -> [Char] utf8DecodeStringLazy fp offset (I# len#) = unsafeDupablePerformIO $ do @@ -200,12 +212,15 @@ utf8CompareShortByteString (SBS a1) (SBS a2) = go 0# 0# | isTrue# (b1_1 `ltWord#` b2_1) -> LT | otherwise -> go (off1 +# 1#) (off2 +# 1#) -utf8DecodeShortByteString :: ShortByteString -> [Char] -utf8DecodeShortByteString (SBS ba#) +utf8DecodeByteArray :: ByteArray# -> [Char] +utf8DecodeByteArray ba# = unsafeDupablePerformIO $ let len# = sizeofByteArray# ba# in utf8DecodeLazy# (return ()) (utf8DecodeCharByteArray# ba#) len# +utf8DecodeShortByteString :: ShortByteString -> [Char] +utf8DecodeShortByteString (SBS ba#) = utf8DecodeByteArray ba# + countUTF8Chars :: ShortByteString -> IO Int countUTF8Chars (SBS ba) = go 0# 0# where ===================================== libraries/ghc-compact/GHC/Compact/Serialized.hs ===================================== @@ -29,6 +29,7 @@ module GHC.Compact.Serialized( import GHC.Prim import GHC.Types import GHC.Word (Word8) +import GHC.IO (unIO) import GHC.Ptr (Ptr(..), plusPtr) @@ -74,12 +75,6 @@ mkBlockList buffer = compactGetFirstBlock buffer >>= go rest <- go next return $ item : rest --- We MUST mark withSerializedCompact as NOINLINE --- Otherwise the compiler will eliminate the call to touch# --- causing the Compact# to be potentially GCed too eagerly, --- before func had a chance to copy everything into its own --- buffers/sockets/whatever - -- | Serialize the 'Compact', and call the provided function with -- with the 'Compact' serialized representation. It is not safe -- to return the pointer from the action and use it after @@ -89,7 +84,6 @@ mkBlockList buffer = compactGetFirstBlock buffer >>= go -- unsound to use 'unsafeInterleaveIO' to lazily construct -- a lazy bytestring from the 'Ptr'. -- -{-# NOINLINE withSerializedCompact #-} withSerializedCompact :: Compact a -> (SerializedCompact a -> IO c) -> IO c withSerializedCompact (Compact buffer root lock) func = withMVar lock $ \_ -> do @@ -97,9 +91,7 @@ withSerializedCompact (Compact buffer root lock) func = withMVar lock $ \_ -> do (# s', rootAddr #) -> (# s', Ptr rootAddr #) ) blockList <- mkBlockList buffer let serialized = SerializedCompact blockList rootPtr - r <- func serialized - IO (\s -> case touch# buffer s of - s' -> (# s', r #) ) + IO $ \s -> keepAlive# buffer s (unIO $ func serialized) fixupPointers :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Maybe (Compact a) #) ===================================== testsuite/tests/ghci/should_fail/T15055.stderr ===================================== @@ -1,6 +1,9 @@ : error: Could not load module ‘GHC’ - It is a member of the hidden package ‘ghc-8.5’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) ===================================== testsuite/tests/package/package06e.stderr ===================================== @@ -1,14 +1,20 @@ package06e.hs:2:1: error: Could not load module ‘GHC.Hs.Type’ - It is a member of the hidden package ‘ghc-8.7’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package06e.hs:3:1: error: Could not load module ‘GHC.Types.Unique.FM’ - It is a member of the hidden package ‘ghc-8.7’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. ===================================== testsuite/tests/package/package07e.stderr ===================================== @@ -2,27 +2,37 @@ package07e.hs:2:1: error: Could not find module ‘GHC.Hs.MyTypes’ Perhaps you meant - GHC.Hs.Type (needs flag -package-id ghc-8.11.0.20200401) - GHC.Tc.Types (needs flag -package-id ghc-8.11.0.20200401) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201120) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201022) + GHC.Tc.Types (needs flag -package-id ghc-9.1.0.20201120) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:3:1: error: Could not load module ‘GHC.Hs.Type’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:4:1: error: Could not load module ‘GHC.Hs.Utils’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:5:1: error: Could not load module ‘GHC.Types.Unique.FM’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. ===================================== testsuite/tests/package/package08e.stderr ===================================== @@ -2,27 +2,37 @@ package08e.hs:2:1: error: Could not find module ‘GHC.Hs.MyTypes’ Perhaps you meant - GHC.Hs.Type (needs flag -package-id ghc-8.11.0.20200401) - GHC.Tc.Types (needs flag -package-id ghc-8.11.0.20200401) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201120) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201022) + GHC.Tc.Types (needs flag -package-id ghc-9.1.0.20201120) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:3:1: error: Could not load module ‘GHC.Hs.Type’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:4:1: error: Could not load module ‘GHC.Hs.Utils’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:5:1: error: Could not load module ‘GHC.Types.Unique.FM’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. ===================================== testsuite/tests/parser/should_run/CountParserDeps.stdout ===================================== @@ -1,4 +1,4 @@ -Found 235 parser module dependencies +Found 236 parser module dependencies GHC.Builtin.Names GHC.Builtin.PrimOps GHC.Builtin.Types @@ -62,6 +62,7 @@ GHC.Core.Utils GHC.CoreToIface GHC.Data.Bag GHC.Data.BooleanFormula +GHC.Data.ByteArray GHC.Data.EnumSet GHC.Data.FastMutInt GHC.Data.FastString ===================================== utils/genprimopcode/Main.hs ===================================== @@ -503,6 +503,7 @@ gen_latex_doc (Info defaults entries) tvars = tvars_of typ tbinds [] = ". " tbinds ("o":tbs) = "(o::?) " ++ (tbinds tbs) + tbinds ("p":tbs) = "(p::?) " ++ (tbinds tbs) tbinds (tv:tbs) = tv ++ " " ++ (tbinds tbs) tvars_of (TyF t1 t2) = tvars_of t1 `union` tvars_of t2 tvars_of (TyC t1 t2) = tvars_of t1 `union` tvars_of t2 @@ -852,6 +853,7 @@ ppTyVar "b" = "betaTyVar" ppTyVar "c" = "gammaTyVar" ppTyVar "s" = "deltaTyVar" ppTyVar "o" = "runtimeRep1TyVar, openAlphaTyVar" +ppTyVar "p" = "runtimeRep2TyVar, openBetaTyVar" ppTyVar _ = error "Unknown type var" ppType :: Ty -> String @@ -885,6 +887,7 @@ ppType (TyVar "b") = "betaTy" ppType (TyVar "c") = "gammaTy" ppType (TyVar "s") = "deltaTy" ppType (TyVar "o") = "openAlphaTy" +ppType (TyVar "p") = "openBetaTy" ppType (TyApp (TyCon "State#") [x]) = "mkStatePrimTy " ++ ppType x ppType (TyApp (TyCon "MutVar#") [x,y]) = "mkMutVarPrimTy " ++ ppType x ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 25fa8fde84701c010fa466c2648f8f6d10265e8f +Subproject commit 81dcb5545c88a6113777c6d87cd687278356d3a3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2e809f72c7f900da77b48df397463d6c95f0b1d6...c80bd7791960c8cc28021aa89726996d524bbb9f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2e809f72c7f900da77b48df397463d6c95f0b1d6...c80bd7791960c8cc28021aa89726996d524bbb9f 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 Wed Nov 25 02:15:53 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 21:15:53 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] Fix and enable object unloading in GHCi Message-ID: <5fbdbe5929e8c_86cfd752bc119760@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 80066117 by Ömer Sinan Ağacan at 2020-11-24T21:15:36-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 25 changed files: - compiler/ghci/Linker.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/linker_error.c Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1134,14 +1134,15 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do where unloadObjs :: Linkable -> IO () unloadObjs lnk + -- The RTS's PEi386 linker currently doesn't support unloading. + | isWindowsHost = return () + | dynamicGhc = return () -- We don't do any cleanup when linking objects with the -- dynamic linker. Doing so introduces extra complexity for -- not much benefit. - -- Code unloading currently disabled due to instability. - -- See #16841. - | False -- otherwise + | otherwise = mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk] -- The components of a BCO linkable may contain -- dot-o files. Which is very confusing. @@ -1149,7 +1150,6 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do -- But the BCO parts can be unlinked just by -- letting go of them (plus of course depopulating -- the symbol table which is done in the main body) - | otherwise = return () -- see #16841 {- ********************************************************************** ===================================== rts/CheckUnload.c ===================================== @@ -17,43 +17,99 @@ #include "CheckUnload.h" #include "sm/Storage.h" #include "sm/GCThread.h" +#include "sm/HeapUtils.h" // -// Code that we unload may be referenced from: -// - info pointers in heap objects and stack frames -// - pointers to static objects from the heap -// - StablePtrs to static objects -// - pointers to cost centres from the cost centre tree +// Note [Object unloading] +// ~~~~~~~~~~~~~~~~~~~~~~~ // -// We can find live static objects after a major GC, so we don't have -// to look at every closure pointer in the heap. However, we do have -// to look at every info pointer. So this is like a heap census -// traversal: we look at the header of every object, but not its -// contents. +// Overview of object unloading: // -// On the assumption that there aren't many different info pointers in -// a typical heap, we insert addresses into a hash table. The -// first time we see an address, we check it against the pending -// unloadable objects and if it lies within any of them, we mark that -// object as referenced so that it won't get unloaded in this round. +// - In a major GC, for every static object we mark the object's object code and +// its dependencies as 'live'. This is done by `markObjectCode`, called by +// `evacuate`. // - -// Note [Speeding up checkUnload] -// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -// In certain circumstances, there may be a lot of unloaded ObjectCode structs -// chained in `unloaded_objects` (such as when users `:load` a module in a very -// big repo in GHCi). To speed up checking whether an address lies within any of -// these objects, we populate the addresses of their mapped sections in -// an array sorted by their `start` address and do binary search for our address -// on that array. Note that this works because the sections are mapped to mutual -// exclusive memory regions, so we can simply find the largest lower bound among -// the `start` addresses of the sections and then check if our address is inside -// that section. In particular, we store the start address and end address of -// each mapped section in a OCSectionIndex, arrange them all on a contiguous -// memory range and then sort by start address. We then put this array in an -// OCSectionIndices struct to be passed into `checkAddress` to do binary search -// on. +// - Marking object code is done using a global "section index table" +// (global_s_indices below). When we load an object code we add its section +// indices to the table. `markObjectCode` does binary search on this table to +// find object code for the marked object, and mark it and its dependencies. +// +// Dependency of an object code is simply other object code that the object +// code refers to in its code. We know these dependencies by the relocations +// present in the referent. This is recorded by lookupSymbolDependent. +// +// - global_s_indices is updated as we load and unload objects. When we load an +// object code we add its section indices to the table, we remove those +// indices when we unload. +// +// The table is sorted and old indices are removed in `checkUnload`, instead +// on every load/unload, to avoid quadratic behavior when we load a list of +// objects. +// +// - After a major GC `checkUnload` unloads objects that are (1) explicitly +// asked for unloading (via `unloadObj`) and (2) are not marked during GC. +// +// Note that, crucially, we don't unload an object code even if it's not +// reachable from the heap, unless it's explicitly asked for unloading (via +// `unloadObj`). This is a feature and not a but! Two use cases: +// +// - The user might request a symbol from a loaded object at any point with +// lookupSymbol (e.g. GHCi might do this). +// +// - Sometimes we load objects that are not Haskell objects. +// +// To avoid unloading objects that are unreachable but are not asked for +// unloading we maintain a "root set" of object code, `loaded_objects` below. +// `loadObj` adds the loaded objects (and its dependencies) to the list. +// `unloadObj` removes. After a major GC, `checkUnload` first marks the root set +// (`loaded_objects`) to avoid unloading objects that are not asked for +// unloading. +// +// Two other lists `objects` and `old_objects` are similar to large object lists +// in GC. Before a major GC we move `objects` to `old_objects`, and move marked +// objects back to `objects` during evacuation and when marking roots in +// `checkUnload`. Any objects in `old_objects` after that is unloaded. +// +// TODO: We currently don't unload objects when non-moving GC is enabled. The +// implementation would be similar to `nonmovingGcCafs`: +// +// - Maintain a "snapshot": +// +// - Copy `loaded_objects` as the root set of the snapshot +// +// - Stash `objects` to `old_objects` as the snapshot. We don't need a new +// list for this as `old_objects` won't be used by any other code when +// non-moving GC is enabled. +// +// - Copy `global_s_indices` table to be able to mark objects while mutators +// call `loadObj_` and `unloadObj_` concurrently. +// +// - Don't mark object code in `evacuate`, marking will be done in the +// non-moving collector. // +// - After preparation, bump the object code mark bit (`object_code_mark_bit` +// below) and mark static objects using a version of `markObjectCode` that +// basically does the same thing but: +// +// - Needs to update `objects` list in a thread-safe way, as mutators will be +// concurrently calling `loadObj_` and add new stuff to `objects`. +// (alternatively we could have a new list for non-moving GC's objects list, +// and then merge it to the global list in the pause before moving to +// concurrent sweep phase) +// +// - Needs to use the copied `global_s_indices` +// +// - After marking anything left in `old_objects` are unreachable objects within +// the snapshot, unload those. The unload loop will be the same as in +// `checkUnload`. This step needs to happen in the final sync (before sweep +// begins) to avoid races when updating `global_s_indices`. +// +// - NOTE: We don't need write barriers in loadObj/unloadObj as we don't +// introduce a dependency from an already-loaded object to a newly loaded +// object and we don't delete existing dependencies. +// + +uint8_t object_code_mark_bit = 0; typedef struct { W_ start; @@ -62,20 +118,85 @@ typedef struct { } OCSectionIndex; typedef struct { + int capacity; // Doubled on resize int n_sections; + bool sorted; // Invalidated on insertion. Sorted in checkUnload. + bool unloaded; // Whether we removed anything from the table in + // removeOCSectionIndices. If this is set we "compact" the + // table (remove unused entries) in `sortOCSectionIndices. OCSectionIndex *indices; } OCSectionIndices; -static OCSectionIndices *createOCSectionIndices(int n_sections) +// List of currently live objects. Moved to `old_objects` before unload check. +// Marked objects moved back to this list in `markObjectLive`. Remaining objects +// are freed at the end of `checkUnload`. +// +// Double-linked list to be able to remove marked objects. List formed with +// `next` and `prev` fields of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *objects = NULL; + +// `objects` list is moved here before unload check. Marked objects are moved +// back to `objects`. Remaining objects are freed. +static ObjectCode *old_objects = NULL; + +// Number of objects that we want to unload. When this value is 0 we skip static +// object marking during GC and `checkUnload`. +// +// Not static: we use this value to skip static object marking in evacuate when +// this is 0. +// +// Incremented in `unloadObj_`, decremented as we unload objects in +// `checkUnload`. +int n_unloaded_objects = 0; + +// List of objects that we don't want to unload (i.e. we haven't called +// unloadObj on these yet). Used as root set for unload check in checkUnload. +// Objects are added with loadObj_ and removed with unloadObj_. +// +// List formed with `next_loaded_object` field of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *loaded_objects; + +// Section index table for currently loaded objects. New indices are added by +// `loadObj_`, indices of unloaded objects are removed in `checkUnload`. Used to +// map static closures to their ObjectCode. +static OCSectionIndices *global_s_indices = NULL; + +static OCSectionIndices *createOCSectionIndices(void) { - OCSectionIndices *s_indices; - s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); - s_indices->n_sections = n_sections; - s_indices->indices = stgMallocBytes(n_sections*sizeof(OCSectionIndex), + // TODO (osa): Maybe initialize as empty (without allocation) and allocate + // on first insertion? + OCSectionIndices *s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); + int capacity = 1024; + s_indices->capacity = capacity; + s_indices->n_sections = 0; + s_indices->sorted = true; + s_indices->unloaded = false; + s_indices->indices = stgMallocBytes(capacity * sizeof(OCSectionIndex), "OCSectionIndices::indices"); return s_indices; } +static void freeOCSectionIndices(OCSectionIndices *s_indices) +{ + free(s_indices->indices); + free(s_indices); +} + +void initUnloadCheck() +{ + global_s_indices = createOCSectionIndices(); +} + +void exitUnloadCheck() +{ + freeOCSectionIndices(global_s_indices); + global_s_indices = NULL; +} + static int cmpSectionIndex(const void* indexa, const void *indexb) { W_ s1 = ((OCSectionIndex*)indexa)->start; @@ -88,44 +209,124 @@ static int cmpSectionIndex(const void* indexa, const void *indexb) return 0; } -static OCSectionIndices* buildOCSectionIndices(ObjectCode *ocs) +static void reserveOCSectionIndices(OCSectionIndices *s_indices, int len) { - int cnt_sections = 0; - ObjectCode *oc; - for (oc = ocs; oc; oc = oc->next) { - cnt_sections += oc->n_sections; + int current_capacity = s_indices->capacity; + int current_len = s_indices->n_sections; + if (current_capacity - current_len >= len) { + return; + } + + // Round up to nearest power of 2 + int new_capacity = 1 << (int)ceil(log2(current_len + len)); + + OCSectionIndex *old_indices = s_indices->indices; + OCSectionIndex *new_indices = stgMallocBytes(new_capacity * sizeof(OCSectionIndex), + "reserveOCSectionIndices"); + + for (int i = 0; i < current_len; ++i) { + new_indices[i] = old_indices[i]; } - OCSectionIndices* s_indices = createOCSectionIndices(cnt_sections); - int s_i = 0, i; - for (oc = ocs; oc; oc = oc->next) { - for (i = 0; i < oc->n_sections; i++) { - if (oc->sections[i].kind != SECTIONKIND_OTHER) { - s_indices->indices[s_i].start = (W_)oc->sections[i].start; - s_indices->indices[s_i].end = (W_)oc->sections[i].start - + oc->sections[i].size; - s_indices->indices[s_i].oc = oc; - s_i++; + + s_indices->capacity = new_capacity; + s_indices->indices = new_indices; + + free(old_indices); +} + +// Insert object section indices of a single ObjectCode. Invalidates 'sorted' +// state. +void insertOCSectionIndices(ObjectCode *oc) +{ + reserveOCSectionIndices(global_s_indices, oc->n_sections); + global_s_indices->sorted = false; + + int s_i = global_s_indices->n_sections; + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + global_s_indices->indices[s_i].start = (W_)oc->sections[i].start; + global_s_indices->indices[s_i].end = (W_)oc->sections[i].start + + oc->sections[i].size; + global_s_indices->indices[s_i].oc = oc; + s_i++; + } + } + + global_s_indices->n_sections = s_i; + + // Add object to 'objects' list + if (objects != NULL) { + objects->prev = oc; + } + oc->next = objects; + objects = oc; +} + +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr); + +static void removeOCSectionIndices(OCSectionIndices *s_indices, ObjectCode *oc) +{ + // To avoid quadratic behavior in checkUnload we set `oc` fields of indices + // of unloaded objects NULL here. Removing unused entries is done in + // `sortOCSectionIndices`. + + s_indices->unloaded = true; + + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + int section_idx = findSectionIdx(s_indices, oc->sections[i].start); + if (section_idx != -1) { + s_indices->indices[section_idx].oc = NULL; } } } - s_indices->n_sections = s_i; +} + +static void sortOCSectionIndices(OCSectionIndices *s_indices) { + if (s_indices->sorted) { + return; + } + qsort(s_indices->indices, s_indices->n_sections, sizeof(OCSectionIndex), cmpSectionIndex); - return s_indices; + + s_indices->sorted = true; } -static void freeOCSectionIndices(OCSectionIndices *section_indices) -{ - free(section_indices->indices); - free(section_indices); +static void removeRemovedOCSections(OCSectionIndices *s_indices) { + if (!s_indices->unloaded) { + return; + } + + int next_free_idx = 0; + for (int i = 0; i < s_indices->n_sections; ++i) { + if (s_indices->indices[i].oc == NULL) { + // free entry, skip + } else if (i == next_free_idx) { + ++next_free_idx; + } else { + s_indices->indices[next_free_idx] = s_indices->indices[i]; + ++next_free_idx; + } + } + + s_indices->n_sections = next_free_idx; + s_indices->unloaded = true; } -static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { +// Returns -1 if not found +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr) { + ASSERT(s_indices->sorted); + W_ w_addr = (W_)addr; - if (s_indices->n_sections <= 0) return NULL; - if (w_addr < s_indices->indices[0].start) return NULL; + if (s_indices->n_sections <= 0) { + return -1; + } + if (w_addr < s_indices->indices[0].start) { + return -1; + } int left = 0, right = s_indices->n_sections; while (left + 1 < right) { @@ -139,330 +340,125 @@ static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { } ASSERT(w_addr >= s_indices->indices[left].start); if (w_addr < s_indices->indices[left].end) { - return s_indices->indices[left].oc; + return left; } - return NULL; + return -1; } -static void checkAddress (HashTable *addrs, const void *addr, - OCSectionIndices *s_indices) -{ - ObjectCode *oc; - - if (!lookupHashTable(addrs, (W_)addr)) { - insertHashTable(addrs, (W_)addr, addr); +static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { + int oc_idx = findSectionIdx(s_indices, addr); - oc = findOC(s_indices, addr); - if (oc != NULL) { - oc->referenced = 1; - return; - } + if (oc_idx == -1) { + return NULL; } + + return s_indices->indices[oc_idx].oc; } -static void searchStackChunk (HashTable *addrs, StgPtr sp, StgPtr stack_end, - OCSectionIndices *s_indices) -{ - StgPtr p; - const StgRetInfoTable *info; +static bool markObjectLive(void *data STG_UNUSED, StgWord key, const void *value STG_UNUSED) { + ObjectCode *oc = (ObjectCode*)key; + if (oc->mark == object_code_mark_bit) { + return true; // for hash table iteration + } + + oc->mark = object_code_mark_bit; + // Remove from 'old_objects' list + if (oc->prev != NULL) { + // TODO(osa): Maybe 'prev' should be a pointer to the referencing + // *field* ? (instead of referencing *object*) + oc->prev->next = oc->next; + } else { + old_objects = oc->next; + } + if (oc->next != NULL) { + oc->next->prev = oc->prev; + } - p = sp; - while (p < stack_end) { - info = get_ret_itbl((StgClosure *)p); + // Add it to 'objects' list + oc->prev = NULL; + oc->next = objects; + if (objects != NULL) { + objects->prev = oc; + } + objects = oc; - switch (info->i.type) { - case RET_SMALL: - case RET_BIG: - checkAddress(addrs, (const void*)info, s_indices); - break; + // Mark its dependencies + iterHashTable(oc->dependencies, NULL, markObjectLive); - default: - break; - } + return true; // for hash table iteration +} + +void markObjectCode(const void *addr) +{ + if (global_s_indices == NULL) { + return; + } - p += stack_frame_sizeW((StgClosure*)p); + // This should be checked at the call site + ASSERT(!HEAP_ALLOCED(addr)); + + ObjectCode *oc = findOC(global_s_indices, addr); + if (oc != NULL) { + // Mark the object code and its dependencies + markObjectLive(NULL, (W_)oc, NULL); } } - -static void searchHeapBlocks (HashTable *addrs, bdescr *bd, - OCSectionIndices *s_indices) +// Returns whether or not the GC that follows needs to mark code for potential +// unloading. +bool prepareUnloadCheck() { - StgPtr p; - const StgInfoTable *info; - uint32_t size; - bool prim; + if (global_s_indices == NULL) { + return false; + } - for (; bd != NULL; bd = bd->link) { + removeRemovedOCSections(global_s_indices); + sortOCSectionIndices(global_s_indices); - if (bd->flags & BF_PINNED) { - // Assume that objects in PINNED blocks cannot refer to - continue; - } + ASSERT(old_objects == NULL); - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); - prim = false; - - switch (info->type) { - - case THUNK: - size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case FUN: - case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR: - case CONSTR_NOCAF: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case BLACKHOLE: - case BLOCKING_QUEUE: - prim = true; - size = sizeW_fromITBL(info); - break; - - case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. - prim = true; - size = BLACKHOLE_sizeW(); - break; - - case BCO: - prim = true; - size = bco_sizeW((StgBCO *)p); - break; - - case MVAR_CLEAN: - case MVAR_DIRTY: - case TVAR: - case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = true; - size = sizeW_fromITBL(info); - break; - - case AP: - prim = true; - size = ap_sizeW((StgAP *)p); - break; - - case PAP: - prim = true; - size = pap_sizeW((StgPAP *)p); - break; - - case AP_STACK: - { - StgAP_STACK *ap = (StgAP_STACK *)p; - prim = true; - size = ap_stack_sizeW(ap); - searchStackChunk(addrs, (StgPtr)ap->payload, - (StgPtr)ap->payload + ap->size, s_indices); - break; - } + object_code_mark_bit = ~object_code_mark_bit; + old_objects = objects; + objects = NULL; + return true; +} - case ARR_WORDS: - prim = true; - size = arr_words_sizeW((StgArrBytes*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN_CLEAN: - case MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = true; - size = sizeofW(StgTSO); - break; - - case STACK: { - StgStack *stack = (StgStack*)p; - prim = true; - searchStackChunk(addrs, stack->sp, - stack->stack + stack->stack_size, s_indices); - size = stack_sizeW(stack); - break; - } +void checkUnload() +{ + if (global_s_indices == NULL) { + return; + } - case TREC_CHUNK: - prim = true; - size = sizeofW(StgTRecChunk); - break; + // At this point we've marked all dynamically loaded static objects + // (including their dependencies) during GC, but not the root set of object + // code (loaded_objects). Mark the roots first, then unload any unmarked + // objects. - default: - barf("searchHeapBlocks, unknown object: %d", info->type); - } + OCSectionIndices *s_indices = global_s_indices; + ASSERT(s_indices->sorted); - if (!prim) { - checkAddress(addrs,info, s_indices); - } - - p += size; - } + // Mark roots + for (ObjectCode *oc = loaded_objects; oc != NULL; oc = oc->next_loaded_object) { + markObjectLive(NULL, (W_)oc, NULL); } -} -#if defined(PROFILING) -// -// Do not unload the object if the CCS tree refers to a CCS or CC which -// originates in the object. -// -static void searchCostCentres (HashTable *addrs, CostCentreStack *ccs, - OCSectionIndices* s_indices) -{ - IndexTable *i; + // Free unmarked objects + ObjectCode *next = NULL; + for (ObjectCode *oc = old_objects; oc != NULL; oc = next) { + next = oc->next; - checkAddress(addrs, ccs, s_indices); - checkAddress(addrs, ccs->cc, s_indices); - for (i = ccs->indexTable; i != NULL; i = i->next) { - if (!i->back_edge) { - searchCostCentres(addrs, i->ccs, s_indices); - } + removeOCSectionIndices(s_indices, oc); + + // Symbols should be removed by unloadObj_. + // NB (osa): If this assertion doesn't hold then freeObjectCode below + // will corrupt symhash as keys of that table live in ObjectCodes. If + // you see a segfault in a hash table operation in linker (in non-debug + // RTS) then it's probably becuse this assertion did not hold. + ASSERT(oc->symbols == NULL); + + freeObjectCode(oc); + n_unloaded_objects -= 1; } -} -#endif -// -// Check whether we can unload any object code. This is called at the -// appropriate point during a GC, where all the heap data is nice and -// packed together and we have a linked list of the static objects. -// -// The check involves a complete heap traversal, but you only pay for -// this (a) when you have called unloadObj(), and (b) at a major GC, -// which is much more expensive than the traversal we're doing here. -// -void checkUnload (StgClosure *static_objects) -{ - uint32_t g, n; - HashTable *addrs; - StgClosure* p; - const StgInfoTable *info; - ObjectCode *oc, *prev, *next; - gen_workspace *ws; - StgClosure* link; - - if (unloaded_objects == NULL) return; - - ACQUIRE_LOCK(&linker_unloaded_mutex); - - OCSectionIndices *s_indices = buildOCSectionIndices(unloaded_objects); - // Mark every unloadable object as unreferenced initially - for (oc = unloaded_objects; oc; oc = oc->next) { - IF_DEBUG(linker, debugBelch("Checking whether to unload %" PATH_FMT "\n", - oc->fileName)); - oc->referenced = false; - } - - addrs = allocHashTable(); - - for (p = static_objects; p != END_OF_STATIC_OBJECT_LIST; p = link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - info = get_itbl(p); - checkAddress(addrs, info, s_indices); - link = *STATIC_LINK(info, p); - } - - // CAFs on revertible_caf_list are not on static_objects - for (p = (StgClosure*)revertible_caf_list; - p != END_OF_CAF_LIST; - p = ((StgIndStatic *)p)->static_link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - } - - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - searchHeapBlocks (addrs, generations[g].blocks, s_indices); - searchHeapBlocks (addrs, generations[g].large_objects, s_indices); - - for (n = 0; n < n_capabilities; n++) { - ws = &gc_threads[n]->gens[g]; - searchHeapBlocks(addrs, ws->todo_bd, s_indices); - searchHeapBlocks(addrs, ws->part_list, s_indices); - searchHeapBlocks(addrs, ws->scavd_list, s_indices); - } - } - -#if defined(PROFILING) - /* Traverse the cost centre tree, calling checkAddress on each CCS/CC */ - searchCostCentres(addrs, CCS_MAIN, s_indices); - - /* Also check each cost centre in the CC_LIST */ - CostCentre *cc; - for (cc = CC_LIST; cc != NULL; cc = cc->link) { - checkAddress(addrs, cc, s_indices); - } -#endif /* PROFILING */ - - freeOCSectionIndices(s_indices); - // Look through the unloadable objects, and any object that is still - // marked as unreferenced can be physically unloaded, because we - // have no references to it. - prev = NULL; - for (oc = unloaded_objects; oc; oc = next) { - next = oc->next; - if (oc->referenced == 0) { - if (prev == NULL) { - unloaded_objects = oc->next; - } else { - prev->next = oc->next; - } - IF_DEBUG(linker, debugBelch("Unloading object file %" PATH_FMT "\n", - oc->fileName)); - freeObjectCode(oc); - } else { - IF_DEBUG(linker, debugBelch("Object file still in use: %" - PATH_FMT "\n", oc->fileName)); - prev = oc; - } - } - - freeHashTable(addrs, NULL); - - RELEASE_LOCK(&linker_unloaded_mutex); + old_objects = NULL; } ===================================== rts/CheckUnload.h ===================================== @@ -12,6 +12,34 @@ #include "BeginPrivate.h" -void checkUnload (StgClosure *static_objects); +#include "LinkerInternals.h" + +// Currently live objects +extern ObjectCode *objects; + +// Root set for object collection +extern ObjectCode *loaded_objects; + +// Mark bit for live objects +extern uint8_t object_code_mark_bit; + +// Number of object code currently marked for unloading. See the definition in +// CheckUnload.c for details. +extern int n_unloaded_objects; + +void initUnloadCheck(void); +void exitUnloadCheck(void); + +// Call before major GC to prepare section index table for marking +bool prepareUnloadCheck(void); + +// Mark object code of a static closure address as 'live' +void markObjectCode(const void *addr); + +// Call after major GC to unload unused and unmarked object code +void checkUnload(void); + +// Call on loaded object code +void insertOCSectionIndices(ObjectCode *oc); #include "EndPrivate.h" ===================================== rts/Hash.c ===================================== @@ -400,6 +400,27 @@ mapHashTable(HashTable *table, void *data, MapHashFn fn) } } +void +iterHashTable(HashTable *table, void *data, IterHashFn fn) +{ + /* The last bucket with something in it is table->max + table->split - 1 */ + long segment = (table->max + table->split - 1) / HSEGSIZE; + long index = (table->max + table->split - 1) % HSEGSIZE; + + while (segment >= 0) { + while (index >= 0) { + for (HashList *hl = table->dir[segment][index]; hl != NULL; hl = hl->next) { + if (!fn(data, hl->key, hl->data)) { + return; + } + } + index--; + } + segment--; + index = HSEGSIZE - 1; + } +} + /* ----------------------------------------------------------------------------- * When we initialize a hash table, we set up the first segment as well, * initializing all of the first segment's hash buckets to NULL. @@ -444,12 +465,6 @@ allocStrHashTable(void) return allocHashTable_(hashStr, compareStr); } -void -exitHashTable(void) -{ - /* nothing to do */ -} - int keyCountHashTable (HashTable *table) { return table->kcount; ===================================== rts/Hash.h ===================================== @@ -33,8 +33,11 @@ int keyCountHashTable (HashTable *table); int keysHashTable(HashTable *table, StgWord keys[], int szKeys); typedef void (*MapHashFn)(void *data, StgWord key, const void *value); +// Return true -> continue; false -> stop +typedef bool (*IterHashFn)(void *data, StgWord key, const void *value); void mapHashTable(HashTable *table, void *data, MapHashFn fn); +void iterHashTable(HashTable *table, void *data, IterHashFn); /* Hash table access where the keys are C strings (the strings are * assumed to be allocated by the caller, and mustn't be deallocated @@ -62,6 +65,32 @@ int hashStr(const HashTable *table, StgWord key); */ void freeHashTable ( HashTable *table, void (*freeDataFun)(void *) ); -void exitHashTable ( void ); +INLINE_HEADER void freeStrHashTable ( HashTable *table, void (*freeDataFun)(void *) ) +{ + freeHashTable((HashTable*)table, freeDataFun); +} + +/* + * Hash set API + * + * A hash set is bascially a hash table where values are NULL. + */ + +typedef struct hashtable HashSet; + +INLINE_HEADER HashSet *allocHashSet ( void ) +{ + return (HashSet*)allocHashTable(); +} + +INLINE_HEADER void freeHashSet ( HashSet *set ) +{ + freeHashTable((HashTable*)set, NULL); +} + +INLINE_HEADER void insertHashSet ( HashSet *set, StgWord key ) +{ + insertHashTable((HashTable*)set, key, NULL); +} #include "EndPrivate.h" ===================================== rts/Linker.c ===================================== @@ -32,6 +32,7 @@ #include "linker/CacheFlush.h" #include "linker/SymbolExtras.h" #include "PathUtils.h" +#include "CheckUnload.h" // createOCSectionIndices #if !defined(mingw32_HOST_OS) #include "posix/Signals.h" @@ -161,23 +162,9 @@ */ /*Str*/HashTable *symhash; -/* List of currently loaded objects */ -ObjectCode *objects = NULL; /* initially empty */ - -/* List of objects that have been unloaded via unloadObj(), but are waiting - to be actually freed via checkUnload() */ -ObjectCode *unloaded_objects = NULL; /* initially empty */ - #if defined(THREADED_RTS) -/* This protects all the Linker's global state except unloaded_objects */ +/* This protects all the Linker's global state */ Mutex linker_mutex; -/* - * This protects unloaded_objects. We have a separate mutex for this, because - * the GC needs to access unloaded_objects in checkUnload, while the linker only - * needs to access unloaded_objects in unloadObj(), so this allows most linker - * operations proceed concurrently with the GC. - */ -Mutex linker_unloaded_mutex; #endif /* Generic wrapper function to try and Resolve and RunInit oc files */ @@ -447,12 +434,10 @@ initLinker_ (int retain_cafs) linker_init_done = 1; } - objects = NULL; - unloaded_objects = NULL; + initUnloadCheck(); #if defined(THREADED_RTS) initMutex(&linker_mutex); - initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -538,6 +523,7 @@ exitLinker( void ) { #endif if (linker_init_done == 1) { freeHashTable(symhash, free); + exitUnloadCheck(); } #if defined(THREADED_RTS) closeMutex(&linker_mutex); @@ -864,18 +850,24 @@ HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data) } /* ----------------------------------------------------------------------------- - * lookup a symbol in the hash table + * Lookup a symbol in the hash table + * + * When 'dependent' is not NULL, adds it as a dependent to the owner of the + * symbol. */ #if defined(OBJFORMAT_PEi386) -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + (void)dependent; // TODO + ASSERT_LOCK_HELD(&linker_mutex); return lookupSymbol_PEi386(lbl); } #else -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + ASSERT_LOCK_HELD(&linker_mutex); IF_DEBUG(linker, debugBelch("lookupSymbol: looking up '%s'\n", lbl)); ASSERT(symhash != NULL); @@ -900,10 +892,18 @@ SymbolAddr* lookupSymbol_ (SymbolName* lbl) return internal_dlsym(lbl + 1); # else - ASSERT(2+2 == 5); + ASSERT(false); return NULL; # endif } else { + if (dependent) { + // Add dependent as symbol's owner's dependency + ObjectCode *owner = pinfo->owner; + if (owner) { + // TODO: what does it mean for a symbol to not have an owner? + insertHashSet(dependent->dependencies, (W_)owner); + } + } return loadSymbol(lbl, pinfo); } } @@ -942,7 +942,7 @@ SymbolAddr* loadSymbol(SymbolName *lbl, RtsSymbolInfo *pinfo) { SymbolAddr* lookupSymbol( SymbolName* lbl ) { ACQUIRE_LOCK(&linker_mutex); - SymbolAddr* r = lookupSymbol_(lbl); + SymbolAddr* r = lookupDependentSymbol(lbl, NULL); if (!r) { errorBelch("^^ Could not load '%s', dependency unresolved. " "See top entry above.\n", lbl); @@ -1342,6 +1342,8 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->fileName); stgFree(oc->archiveMemberName); + freeHashSet(oc->dependencies); + stgFree(oc); } @@ -1403,6 +1405,10 @@ mkOc( pathchar *path, char *image, int imageSize, /* chain it onto the list of objects */ oc->next = NULL; + oc->prev = NULL; + oc->next_loaded_object = NULL; + oc->mark = object_code_mark_bit; + oc->dependencies = allocHashSet(); #if RTS_LINKER_USE_MMAP oc->rw_m32 = m32_allocator_new(false); @@ -1421,9 +1427,9 @@ mkOc( pathchar *path, char *image, int imageSize, HsInt isAlreadyLoaded( pathchar *path ) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path) + && o->status != OBJECT_UNLOADED) { return 1; /* already loaded */ } } @@ -1557,21 +1563,16 @@ preloadObjectFile (pathchar *path) */ static HsInt loadObj_ (pathchar *path) { - ObjectCode* oc; - IF_DEBUG(linker, debugBelch("loadObj: %" PATH_FMT "\n", path)); - - /* debugBelch("loadObj %s\n", path ); */ - - /* Check that we haven't already loaded this object. - Ignore requests to load multiple times */ + // Check that we haven't already loaded this object. + // Ignore requests to load multiple times if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); - return 1; /* success */ + return 1; // success } - oc = preloadObjectFile(path); + ObjectCode *oc = preloadObjectFile(path); if (oc == NULL) return 0; if (! loadOc(oc)) { @@ -1582,8 +1583,10 @@ static HsInt loadObj_ (pathchar *path) return 0; } - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); + + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; return 1; } @@ -1778,15 +1781,15 @@ int ocTryLoad (ObjectCode* oc) { */ static HsInt resolveObjs_ (void) { - ObjectCode *oc; - int r; - IF_DEBUG(linker, debugBelch("resolveObjs: start\n")); - for (oc = objects; oc; oc = oc->next) { - r = ocTryLoad(oc); + for (ObjectCode *oc = objects; oc; oc = oc->next) { + int r = ocTryLoad(oc); if (!r) { + errorBelch("Could not load Object Code %" PATH_FMT ".\n", OC_INFORMATIVE_FILENAME(oc)); + IF_DEBUG(linker, printLoadedObjects()); + fflush(stderr); return r; } } @@ -1813,45 +1816,35 @@ HsInt resolveObjs (void) */ static HsInt unloadObj_ (pathchar *path, bool just_purge) { - ObjectCode *oc, *prev, *next; - HsBool unloadedAnyObj = HS_BOOL_FALSE; - ASSERT(symhash != NULL); ASSERT(objects != NULL); IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); - prev = NULL; - for (oc = objects; oc; oc = next) { - next = oc->next; // oc might be freed - - if (!pathcmp(oc->fileName,path)) { + bool unloadedAnyObj = false; + ObjectCode *prev = NULL; + // NOTE (osa): There may be more than one object with the same file name + // (happens when loading archive files) so we don't stop after unloading one + for (ObjectCode *oc = loaded_objects; oc; oc = oc->next_loaded_object) { + if (pathcmp(oc->fileName,path) == 0) { + oc->status = OBJECT_UNLOADED; - // these are both idempotent, so in just_purge mode we can - // later call unloadObj() to really unload the object. + // These are both idempotent, so in just_purge mode we can later + // call unloadObj() to really unload the object. removeOcSymbols(oc); freeOcStablePtrs(oc); + unloadedAnyObj = true; + if (!just_purge) { + n_unloaded_objects += 1; + // Remove object code from root set if (prev == NULL) { - objects = oc->next; + loaded_objects = oc->next_loaded_object; } else { - prev->next = oc->next; + prev->next_loaded_object = oc->next_loaded_object; } - ACQUIRE_LOCK(&linker_unloaded_mutex); - oc->next = unloaded_objects; - unloaded_objects = oc; - oc->status = OBJECT_UNLOADED; - RELEASE_LOCK(&linker_unloaded_mutex); - // We do not own oc any more; it can be released at any time by - // the GC in checkUnload(). - } else { - prev = oc; } - - /* This could be a member of an archive so continue - * unloading other members. */ - unloadedAnyObj = HS_BOOL_TRUE; } else { prev = oc; } @@ -1859,8 +1852,7 @@ static HsInt unloadObj_ (pathchar *path, bool just_purge) if (unloadedAnyObj) { return 1; - } - else { + } else { errorBelch("unloadObj: can't find `%" PATH_FMT "' to unload", path); return 0; } @@ -1884,13 +1876,7 @@ HsInt purgeObj (pathchar *path) static OStatus getObjectLoadStatus_ (pathchar *path) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } - } - for (o = unloaded_objects; o; o = o->next) { + for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { return o->status; } ===================================== rts/LinkerInternals.h ===================================== @@ -191,9 +191,6 @@ typedef struct _ObjectCode { /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; - /* flag used when deciding whether to unload an object file */ - int referenced; - /* record by how much image has been deliberately misaligned after allocation, so that we can use realloc */ int misalignment; @@ -205,8 +202,37 @@ typedef struct _ObjectCode { int n_segments; Segment *segments; - /* Allow a chain of these things */ - struct _ObjectCode * next; + // + // Garbage collection fields + // + + // Next object in `objects` list + struct _ObjectCode *next; + + // Previous object in `objects` list + struct _ObjectCode *prev; + + // Next object in `loaded_objects` list + struct _ObjectCode *next_loaded_object; + + // Mark bit + uint8_t mark; + + // Set of dependencies (ObjectCode*) of the object file. Traverse + // dependencies using `iterHashTable`. + // + // New entries are added as we resolve symbols in an object file, in + // `lookupDependentSymbol`. When an object file uses multiple symbols from + // another object file we add the dependent multiple times, so we use a + // `HashTable` here rather than a list/array to avoid copies. + // + // Used when unloading object files. See Note [Object unloading] in + // CheckUnload.c. + HashSet *dependencies; + + // + // End of garbage collection fields + // /* SANITY CHECK ONLY: a list of the only memory regions which may safely be prodded during relocation. Any attempt to prod @@ -250,12 +276,8 @@ typedef struct _ObjectCode { (OC)->fileName \ ) -extern ObjectCode *objects; -extern ObjectCode *unloaded_objects; - #if defined(THREADED_RTS) extern Mutex linker_mutex; -extern Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -306,8 +328,9 @@ int ghciInsertSymbolTable( HsBool weak, ObjectCode *owner); -/* lock-free version of lookupSymbol */ -SymbolAddr* lookupSymbol_ (SymbolName* lbl); +/* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a + * dependent to the owner of the symbol. */ +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent); extern /*Str*/HashTable *symhash; ===================================== rts/RtsStartup.c ===================================== @@ -512,9 +512,6 @@ hs_exit_(bool wait_foreign) shutdownAsyncIO(wait_foreign); #endif - /* free hash table storage */ - exitHashTable(); - // Finally, free all our storage. However, we only free the heap // memory if we have waited for foreign calls to complete; // otherwise a foreign call in progress may still be referencing ===================================== rts/linker/Elf.c ===================================== @@ -1099,7 +1099,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) { S = (Elf_Addr)symbol->addr; } else { - S_tmp = lookupSymbol_( symbol->name ); + S_tmp = lookupDependentSymbol( symbol->name, oc ); S = (Elf_Addr)S_tmp; } if (!S) { @@ -1519,7 +1519,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } else { /* No, so look up the name in our global table. */ symbol = strtab + sym.st_name; - S_tmp = lookupSymbol_( symbol ); + S_tmp = lookupDependentSymbol( symbol, oc ); S = (Elf_Addr)S_tmp; } if (!S) { ===================================== rts/linker/LoadArchive.c ===================================== @@ -5,6 +5,7 @@ #include "sm/OSMem.h" #include "RtsUtils.h" #include "LinkerInternals.h" +#include "CheckUnload.h" // loaded_objects, insertOCSectionIndices #include "linker/M32Alloc.h" /* Platform specific headers */ @@ -241,7 +242,6 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, static HsInt loadArchive_ (pathchar *path) { - ObjectCode* oc = NULL; char *image = NULL; HsInt retcode = 0; int memberSize; @@ -520,8 +520,8 @@ static HsInt loadArchive_ (pathchar *path) sprintf(archiveMemberName, "%" PATH_FMT "(%.*s)", path, (int)thisFileNameSize, fileName); - oc = mkOc(path, image, memberSize, false, archiveMemberName - , misalignment); + ObjectCode *oc = mkOc(path, image, memberSize, false, archiveMemberName, + misalignment); #if defined(OBJFORMAT_MACHO) ocInit_MachO( oc ); #endif @@ -536,8 +536,9 @@ static HsInt loadArchive_ (pathchar *path) fclose(f); return 0; } else { - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); // also adds the object to `objects` list + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; } } else if (isGnuIndex) { ===================================== rts/linker/MachO.c ===================================== @@ -242,7 +242,7 @@ resolveImports( addr = (SymbolAddr*) (symbol->nlist->n_value); IF_DEBUG(linker, debugBelch("resolveImports: undefined external %s has value %p\n", symbol->name, addr)); } else { - addr = lookupSymbol_(symbol->name); + addr = lookupDependentSymbol(symbol->name, oc); IF_DEBUG(linker, debugBelch("resolveImports: looking up %s, %p\n", symbol->name, addr)); } @@ -564,12 +564,12 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { /* external symbols should be able to be - * looked up via the lookupSymbol_ function. + * looked up via the lookupDependentSymbol function. * Either through the global symbol hashmap * or asking the system, if not found * in the symbol hashmap */ - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -609,7 +609,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -784,7 +784,7 @@ relocateSection(ObjectCode* oc, int curSection) // symtab, or it is undefined, meaning dlsym must be used // to resolve it. - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); IF_DEBUG(linker, debugBelch("relocateSection: looked up %s, " "external X86_64_RELOC_GOT or X86_64_RELOC_GOT_LOAD\n" " : addr = %p\n", nm, addr)); @@ -845,7 +845,7 @@ relocateSection(ObjectCode* oc, int curSection) nm, (void *)value)); } else { - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); if (addr == NULL) { errorBelch("\nlookupSymbol failed in relocateSection (relocate external)\n" @@ -1345,7 +1345,7 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->nlist[i].n_type & N_EXT) { if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) - && lookupSymbol_(nm)) { + && lookupDependentSymbol(nm, oc)) { // weak definition, and we already have a definition IF_DEBUG(linker, debugBelch(" weak: %s\n", nm)); } @@ -1497,7 +1497,7 @@ ocResolve_MachO(ObjectCode* oc) * have the address. */ if(NULL == symbol->addr) { - symbol->addr = lookupSymbol_((char*)symbol->name); + symbol->addr = lookupDependentSymbol((char*)symbol->name, oc); if(NULL == symbol->addr) barf("Failed to lookup symbol: %s", symbol->name); } else { ===================================== rts/linker/PEi386.c ===================================== @@ -185,6 +185,7 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" #include "GetEnv.h" +#include "CheckUnload.h" #include "linker/PEi386.h" #include "linker/PEi386Types.h" #include "linker/SymbolExtras.h" @@ -1894,7 +1895,7 @@ ocResolve_PEi386 ( ObjectCode* oc ) } else { copyName ( getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1 ); - S = (size_t) lookupSymbol_( (char*)symbol ); + S = (size_t) lookupDependentSymbol( (char*)symbol, oc ); if ((void*)S == NULL) { errorBelch(" | %" PATH_FMT ": unknown symbol `%s'", oc->fileName, symbol); releaseOcInfo (oc); ===================================== rts/linker/elf_got.c ===================================== @@ -88,7 +88,7 @@ fillGot(ObjectCode * oc) { if( STT_NOTYPE == ELF_ST_TYPE(symbol->elf_sym->st_info) || STB_WEAK == ELF_ST_BIND(symbol->elf_sym->st_info)) { if(0x0 == symbol->addr) { - symbol->addr = lookupSymbol_(symbol->name); + symbol->addr = lookupDependentSymbol(symbol->name, oc); if(0x0 == symbol->addr) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; ===================================== rts/sm/Evac.c ===================================== @@ -28,6 +28,7 @@ #include "CNF.h" #include "Scav.h" #include "NonMoving.h" +#include "CheckUnload.h" // n_unloaded_objects and markObjectCode #if defined(THREADED_RTS) && !defined(PARALLEL_GC) #define evacuate(p) evacuate1(p) @@ -593,6 +594,11 @@ loop: if (!HEAP_ALLOCED_GC(q)) { if (!major_gc) return; + // Note [Object unloading] in CheckUnload.c + if (RTS_UNLIKELY(unload_mark_needed)) { + markObjectCode(q); + } + info = get_itbl(q); switch (info->type) { ===================================== rts/sm/GC.c ===================================== @@ -97,6 +97,13 @@ * See also: Note [STATIC_LINK fields] in Storage.h. */ +/* Hot GC globals + * ~~~~~~~~~~~~~~ + * The globals below are quite hot during GC but read-only, initialized during + * the beginning of collection. It is important that they reside in the same + * cache-line to minimize unnecessary cache misses. + */ + /* N is the oldest generation being collected, where the generations * are numbered starting at 0. A major GC (indicated by the major_gc * flag) is when we're collecting all generations. We only attempt to @@ -105,6 +112,7 @@ uint32_t N; bool major_gc; bool deadlock_detect_gc; +bool unload_mark_needed; /* Data used for allocation area sizing. */ @@ -297,6 +305,12 @@ GarbageCollect (uint32_t collect_gen, static_flag == STATIC_FLAG_A ? STATIC_FLAG_B : STATIC_FLAG_A; } + if (major_gc) { + unload_mark_needed = prepareUnloadCheck(); + } else { + unload_mark_needed = false; + } + #if defined(THREADED_RTS) work_stealing = RtsFlags.ParFlags.parGcLoadBalancingEnabled && N >= RtsFlags.ParFlags.parGcLoadBalancingGen; @@ -810,9 +824,12 @@ GarbageCollect (uint32_t collect_gen, resetNurseries(); - // mark the garbage collected CAFs as dead #if defined(DEBUG) - if (major_gc && !RtsFlags.GcFlags.useNonmoving) { gcCAFs(); } + // Mark the garbage collected CAFs as dead. Done in `nonmovingGcCafs()` when + // non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + gcCAFs(); + } #endif // Update the stable name hash table @@ -823,9 +840,14 @@ GarbageCollect (uint32_t collect_gen, // hs_free_stable_ptr(), both of which access the StablePtr table. stablePtrUnlock(); - // Must be after stablePtrUnlock(), because it might free stable ptrs. - if (major_gc) { - checkUnload (gct->scavenged_static_objects); + // Unload dynamically-loaded object code after a major GC. + // See Note [Object unloading] in CheckUnload.c for details. + // + // TODO: Similar to `nonmovingGcCafs` non-moving GC should have its own + // collector for these objects, but that's currently not implemented, so we + // simply don't unload object code when non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + checkUnload(); } #if defined(PROFILING) ===================================== rts/sm/GC.h ===================================== @@ -35,6 +35,7 @@ extern uint32_t N; extern bool major_gc; /* See Note [Deadlock detection under nonmoving collector]. */ extern bool deadlock_detect_gc; +extern bool unload_mark_needed; extern bdescr *mark_stack_bd; extern bdescr *mark_stack_top_bd; ===================================== testsuite/tests/ghci/T16525a/T16525a.script ===================================== @@ -1,6 +1,10 @@ :set -fobject-code :load A import Control.Concurrent -_ <- forkIO $ threadDelay 1000000 >> (print (map v1 value)) +_ <- forkIO $ threadDelay 500000 >> print (map v1 value) :l [] System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC ===================================== testsuite/tests/ghci/T16525a/T16525a.stdout ===================================== @@ -0,0 +1 @@ +["a;lskdfa;lszkfsd;alkfjas"] ===================================== testsuite/tests/ghci/T16525a/all.T ===================================== @@ -1,6 +1,3 @@ test('T16525a', - [extra_files(['A.hs', 'B.hs', ]), - when(compiler_debugged(), extra_run_opts('+RTS -DS -RTS')), - # We don't support unloading with the dynamic linker - when(ghc_dynamic(), skip), ], + [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525a.script']) ===================================== testsuite/tests/ghci/T16525b/A.hs ===================================== @@ -0,0 +1,6 @@ +module A (a) where + +import B + +a :: () -> IO Int +a x = b x ===================================== testsuite/tests/ghci/T16525b/B.hs ===================================== @@ -0,0 +1,5 @@ +module B (b) where + +{-# NOINLINE b #-} +b :: () -> IO Int +b () = return 999999999 ===================================== testsuite/tests/ghci/T16525b/T16525b.script ===================================== @@ -0,0 +1,22 @@ +:set -fobject-code +:load A +import Control.Concurrent +import Control.Monad +:{ +_ <- forkIO $ do + replicateM_ 3 (a () >>= print >> threadDelay 500000) + putStrLn "===== THREAD DONE =====" +:} +:l [] +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 ===================================== testsuite/tests/ghci/T16525b/T16525b.stdout ===================================== @@ -0,0 +1,4 @@ +999999999 +999999999 +999999999 +===== THREAD DONE ===== ===================================== testsuite/tests/ghci/T16525b/all.T ===================================== @@ -0,0 +1,2 @@ +# Tests unloading an object file which is in use in a thread +test('T16525b', [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525b.script']) ===================================== testsuite/tests/rts/linker/linker_error.c ===================================== @@ -57,7 +57,10 @@ int main (int argc, char *argv[]) r = resolveObjs(); if (!r) { debugBelch("resolveObjs failed\n"); + // Mark the object as unloadable: unloadObj(obj); + // Actually unload it: + performMajorGC(); continue; } errorBelch("loading succeeded"); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/800661172eab061c778c3517d00d521bb828c7fa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/800661172eab061c778c3517d00d521bb828c7fa 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 Wed Nov 25 02:22:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 21:22:12 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-8.10] rts/Stats: Reintroduce mut_user_time Message-ID: <5fbdbfd487a8d_86c158da350120060@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: 51d95b56 by Ben Gamari at 2020-11-24T21:22:03-05:00 rts/Stats: Reintroduce mut_user_time Fix the previous backport; this function was dead code in master but is still needed due to ProfHeap.c in ghc-8.10. - - - - - 2 changed files: - rts/Stats.c - rts/Stats.h Changes: ===================================== rts/Stats.c ===================================== @@ -86,6 +86,27 @@ Time stat_getElapsedTime(void) Measure the current MUT time, for profiling ------------------------------------------------------------------------ */ +static double +mut_user_time_until( Time t ) +{ + ACQUIRE_LOCK(&stats_mutex); + double ret = TimeToSecondsDbl(t - stats.gc_cpu_ns - stats.nonmoving_gc_cpu_ns); + RELEASE_LOCK(&stats_mutex); + return ret; + // heapCensus() time is included in GC_tot_cpu, so we don't need + // to subtract it here. + + // TODO: This seems wrong to me. Surely we should be subtracting + // (at least) start_init_cpu? +} + +double +mut_user_time( void ) +{ + Time cpu = getProcessCPUTime(); + return mut_user_time_until(cpu); +} + #if defined(PROFILING) /* mut_user_time_during_RP() returns the MUT time during retainer profiling. ===================================== rts/Stats.h ===================================== @@ -66,6 +66,8 @@ void initStats0(void); void initStats1(void); void resetChildProcessStats(void); +double mut_user_time(void); + void statDescribeGens( void ); Time stat_getElapsedGCTime(void); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/51d95b564fa7319719c1c810df4faeb983f281bb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/51d95b564fa7319719c1c810df4faeb983f281bb 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 Wed Nov 25 02:26:11 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 21:26:11 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/tsan-ghc-9.0 Message-ID: <5fbdc0c3cd293_86cfd752bc12210@gitlab.mail> Ben Gamari deleted branch wip/tsan-ghc-9.0 at Glasgow Haskell Compiler / GHC -- 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 Wed Nov 25 02:26:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Tue, 24 Nov 2020 21:26:12 -0500 Subject: [Git][ghc/ghc][ghc-9.0] 78 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fbdc0c47a461_86cbee25901223e4@gitlab.mail> Ben Gamari pushed to branch ghc-9.0 at Glasgow Haskell Compiler / GHC Commits: 08d75467 by Ben Gamari at 2020-11-24T12:03:00-05:00 SMP.h: Add C11-style atomic operations - - - - - 9f6d3341 by Ben Gamari at 2020-11-24T12:03:00-05:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - 8b5e7dc7 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 67c0f410 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - 829a72cd by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/Task: Make comments proper Notes - - - - - c19ee6d5 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - 5ed8139a by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 3c35c588 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts/ClosureMaros: Use relaxed atomics - - - - - 83e759a7 by Ben Gamari at 2020-11-24T12:03:01-05:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - 7d846a79 by Ben Gamari at 2020-11-24T12:03:01-05:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - 37886925 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 5541b8ea by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 12c8702a by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Annotate benign race in waitForCapability - - - - - 3eb46f2e by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Clarify locking behavior of releaseCapability_ - - - - - e052a812 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Add assertions for task ownership of capabilities - - - - - 2b1da3d8 by Ben Gamari at 2020-11-24T12:03:01-05:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 053d3c5b by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Mitigate races in capability interruption logic - - - - - 7ebad34c by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - 67716ed3 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 5615aac8 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 677988d5 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 7ce38423 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Eliminate data races on pending_sync - - - - - 05f59c23 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - 6417288c by Ben Gamari at 2020-11-24T12:03:02-05:00 rts: Avoid data races in message handling - - - - - dba1771b by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - 1727bc57 by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/ThreadPaused: Avoid data races - - - - - 3e36d9ee by Ben Gamari at 2020-11-24T12:03:02-05:00 rts/Schedule: Eliminate data races in run queue management - - - - - 7b856fcd by Ben Gamari at 2020-11-24T12:03:03-05:00 rts: Eliminate shutdown data race on task counters - - - - - 04a19bfc by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 1f5dded6 by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/Messages: Annotate benign race - - - - - 852eb2cc by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/RaiseAsync: Synchronize what_next read - - - - - d9b6eb31 by Ben Gamari at 2020-11-24T12:03:03-05:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - 1bcc9cd0 by Ben Gamari at 2020-11-24T12:03:03-05:00 Disable flawed assertion - - - - - 2e76a631 by Ben Gamari at 2020-11-24T12:03:03-05:00 Document schedulePushWork race - - - - - 718a46db by Ben Gamari at 2020-11-24T12:03:03-05:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - 588a950b by Ben Gamari at 2020-11-24T12:03:03-05:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 853ef5e1 by Ben Gamari at 2020-11-24T12:03:03-05:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 5bcda8ba by GHC GitLab CI at 2020-11-24T12:03:03-05:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - e78d90e3 by GHC GitLab CI at 2020-11-24T12:03:03-05:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - a99f05ef by Ben Gamari at 2020-11-24T12:03:03-05:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - 02d2e42b by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - fba38edf by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 0215ff52 by Ben Gamari at 2020-11-24T12:03:04-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - e191eb78 by Ben Gamari at 2020-11-24T12:03:04-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - a31bccca by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - 7aba9e54 by Ben Gamari at 2020-11-24T12:03:04-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 23a30a3b by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/BlockAlloc: Use relaxed operations - - - - - 4139b672 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - 33b7b375 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 725dfd75 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Storage: Use atomics - - - - - 240bb1b4 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Updates: Use proper atomic operations - - - - - b7b0f3ae by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - 20787589 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/GC: Use atomics - - - - - b15db127 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - 49c8049e by Ben Gamari at 2020-11-24T12:03:04-05:00 rts/Storage: Accept races on heap size counters - - - - - 89864d46 by Ben Gamari at 2020-11-24T12:03:04-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - 31669bd3 by GHC GitLab CI at 2020-11-24T12:03:04-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 7e968942 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - acef7fd3 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Use relaxed ordering on spinlock counters - - - - - 53920304 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 0ca2beeb by Ben Gamari at 2020-11-24T12:03:05-05:00 Strengthen ordering in releaseGCThreads - - - - - 7d3d0f13 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - c29b1a83 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 55b252f2 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - d9e82a56 by GHC GitLab CI at 2020-11-24T12:03:05-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - d9ed5a62 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 219f6496 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - cf99c5e5 by Ben Gamari at 2020-11-24T12:03:05-05:00 Mitigate data races in event manager startup/shutdown - - - - - d7655654 by Ben Gamari at 2020-11-24T12:03:05-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - 389c92df by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Accept benign races in Proftimer - - - - - b4ced846 by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 9116b39a by Ben Gamari at 2020-11-24T12:03:05-05:00 Fix #17289 - - - - - 75b8c066 by Ben Gamari at 2020-11-24T12:03:05-05:00 suppress #17289 (ticker) race - - - - - dcea5aef by Ben Gamari at 2020-11-24T12:03:05-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - 16d3ea21 by Ben Gamari at 2020-11-24T12:03:06-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - da69341b by Ben Gamari at 2020-11-24T12:03:06-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - f65a5c9e by Ben Gamari at 2020-11-24T12:03:06-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 543ad4f3 by Ben Gamari at 2020-11-24T12:03:06-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - 30 changed files: - .gitlab-ci.yml - configure.ac - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - + hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/Rts.h - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - + includes/rts/TSANUtils.h - includes/rts/storage/ClosureMacros.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - + rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Schedule.h - rts/Sparks.c - + rts/SpinLock.c - rts/StablePtr.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4483f7b81dc7bd3d246fc22728a1ec86570e6e8...543ad4f3f8320c17be0029078a1cbe832f5b6f56 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d4483f7b81dc7bd3d246fc22728a1ec86570e6e8...543ad4f3f8320c17be0029078a1cbe832f5b6f56 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 Wed Nov 25 02:39:46 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 24 Nov 2020 21:39:46 -0500 Subject: [Git][ghc/ghc][wip/backport/9.0/T18857] CmmToLlvm: Declare signature for memcmp Message-ID: <5fbdc3f2d5718_86c113a5b2c12356e@gitlab.mail> Moritz Angermann pushed to branch wip/backport/9.0/T18857 at Glasgow Haskell Compiler / GHC Commits: a3e195ae by Moritz Angermann at 2020-11-25T10:38:45+08:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 4 changed files: - compiler/GHC/CmmToLlvm/Base.hs - rts/linker/Elf.c - rts/linker/elf_reloc_aarch64.c - testsuite/driver/testlib.py Changes: ===================================== compiler/GHC/CmmToLlvm/Base.hs ===================================== @@ -475,14 +475,17 @@ getUniqMeta s = getEnv (flip lookupUFM s . envUniqMeta) ghcInternalFunctions :: LlvmM () ghcInternalFunctions = do platform <- getPlatform + dflags <- getDynFlags let w = llvmWord platform + cint = LMInt $ widthInBits $ cIntWidth dflags + mk "memcmp" cint [i8Ptr, i8Ptr, w] mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w] mk "memmove" i8Ptr [i8Ptr, i8Ptr, w] mk "memset" i8Ptr [i8Ptr, w, w] mk "newSpark" w [i8Ptr, i8Ptr] where mk n ret args = do - let n' = llvmDefLabel $ fsLit n + let n' = fsLit n decl = LlvmFunctionDecl n' ExternallyVisible CC_Ccc ret FixedArgs (tysToParams args) Nothing renderLlvm $ ppLlvmFunctionDecl decl @@ -515,7 +518,10 @@ getGlobalPtr llvmLbl = do let mkGlbVar lbl ty = LMGlobalVar lbl (LMPointer ty) Private Nothing Nothing case m_ty of -- Directly reference if we have seen it already - Just ty -> return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global + Just ty -> do + if llvmLbl `elem` (map fsLit ["newSpark", "memmove", "memcpy", "memcmp", "memset"]) + then return $ mkGlbVar (llvmLbl) ty Global + else return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global -- Otherwise use a forward alias of it Nothing -> do saveAlias llvmLbl ===================================== rts/linker/Elf.c ===================================== @@ -780,7 +780,12 @@ ocGetNames_ELF ( ObjectCode* oc ) else if (!oc->imageMapped || size < getPageSize() / 3) { bool executable = kind == SECTIONKIND_CODE_OR_RODATA; m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32; - start = m32_alloc(allocator, size, 8); + // align on 16 bytes. The reason being that llvm will emit see + // paddq statements for x86_64 under optimisation and load from + // RODATA sections. Specifically .rodata.cst16. However we don't + // handle the cst part in any way what so ever, so 16 seems + // better than 8. + start = m32_alloc(allocator, size, 16); if (start == NULL) goto fail; memcpy(start, oc->image + offset, size); alloc = SECTION_M32; @@ -915,7 +920,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1842,6 +1847,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1915,6 +1921,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== testsuite/driver/testlib.py ===================================== @@ -2189,6 +2189,13 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + + # filter out nix garbage, that just keeps on showing up as errors on darwin + s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2259,6 +2266,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3e195ae70c569e1a140e22175220d28d8be35c0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a3e195ae70c569e1a140e22175220d28d8be35c0 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 Wed Nov 25 02:42:07 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Tue, 24 Nov 2020 21:42:07 -0500 Subject: [Git][ghc/ghc][wip/backport/8.10/T18857] CmmToLlvm: Declare signature for memcmp Message-ID: <5fbdc47f50823_86c113a5b2c12424f@gitlab.mail> Moritz Angermann pushed to branch wip/backport/8.10/T18857 at Glasgow Haskell Compiler / GHC Commits: 70ac4ed8 by Moritz Angermann at 2020-11-25T10:41:34+08:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 4 changed files: - compiler/llvmGen/LlvmCodeGen/Base.hs - rts/linker/Elf.c - rts/linker/elf_reloc_aarch64.c - testsuite/driver/testlib.py Changes: ===================================== compiler/llvmGen/LlvmCodeGen/Base.hs ===================================== @@ -475,13 +475,16 @@ getUniqMeta s = getEnv (flip lookupUFM s . envUniqMeta) ghcInternalFunctions :: LlvmM () ghcInternalFunctions = do dflags <- getDynFlags - mk "memcpy" i8Ptr [i8Ptr, i8Ptr, llvmWord dflags] - mk "memmove" i8Ptr [i8Ptr, i8Ptr, llvmWord dflags] - mk "memset" i8Ptr [i8Ptr, llvmWord dflags, llvmWord dflags] - mk "newSpark" (llvmWord dflags) [i8Ptr, i8Ptr] + let w = llvmWord dflags + cint = LMInt $ widthInBits $ cIntWidth dflags + mk "memcmp" cint [i8Ptr, i8Ptr, w] + mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w] + mk "memmove" i8Ptr [i8Ptr, i8Ptr, w] + mk "memset" i8Ptr [i8Ptr, w, w] + mk "newSpark" w [i8Ptr, i8Ptr] where mk n ret args = do - let n' = llvmDefLabel $ fsLit n + let n' = fsLit n decl = LlvmFunctionDecl n' ExternallyVisible CC_Ccc ret FixedArgs (tysToParams args) Nothing renderLlvm $ ppLlvmFunctionDecl decl @@ -538,7 +541,10 @@ getGlobalPtr llvmLbl = do let mkGlbVar lbl ty = LMGlobalVar lbl (LMPointer ty) Private Nothing Nothing case m_ty of -- Directly reference if we have seen it already - Just ty -> return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global + Just ty -> do + if llvmLbl `elem` (map fsLit ["newSpark", "memmove", "memcpy", "memcmp", "memset"]) + then return $ mkGlbVar (llvmLbl) ty Global + else return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global -- Otherwise use a forward alias of it Nothing -> do saveAlias llvmLbl ===================================== rts/linker/Elf.c ===================================== @@ -781,7 +781,12 @@ ocGetNames_ELF ( ObjectCode* oc ) else if (!oc->imageMapped || size < getPageSize() / 3) { bool executable = kind == SECTIONKIND_CODE_OR_RODATA; m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32; - start = m32_alloc(allocator, size, 8); + // align on 16 bytes. The reason being that llvm will emit see + // paddq statements for x86_64 under optimisation and load from + // RODATA sections. Specifically .rodata.cst16. However we don't + // handle the cst part in any way what so ever, so 16 seems + // better than 8. + start = m32_alloc(allocator, size, 16); if (start == NULL) goto fail; memcpy(start, oc->image + offset, size); alloc = SECTION_M32; @@ -940,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1866,6 +1871,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1939,6 +1945,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== testsuite/driver/testlib.py ===================================== @@ -2113,6 +2113,13 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + + # filter out nix garbage, that just keeps on showing up as errors on darwin + s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2183,6 +2190,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/70ac4ed84f4e95f3b3772242368582cf911e50c4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/70ac4ed84f4e95f3b3772242368582cf911e50c4 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 Wed Nov 25 04:21:23 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Tue, 24 Nov 2020 23:21:23 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 90 commits: Move core flattening algorithm to Core.Unify Message-ID: <5fbddbc3ded66_86cfd752bc1259d1@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: ea4662fc by Richard Eisenberg at 2020-11-24T23:19:55-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into GHC.Core.Map.Type and GHC.Core.Map.Expr, in order to avoid module import cycles with GHC.Core. - - - - - 91fa4b47 by Richard Eisenberg at 2020-11-24T23:20:17-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - 25bc67ab by Richard Eisenberg at 2020-11-24T23:20:17-05:00 Start of work in simplifying flattening - - - - - c3806e5a by Richard Eisenberg at 2020-11-24T23:20:17-05:00 Much work toward simplifying CFunEqCan - - - - - 3dface62 by Richard Eisenberg at 2020-11-24T23:20:17-05:00 Canonicalized function equalities. Now, onto interactions. - - - - - 7d254133 by Richard Eisenberg at 2020-11-24T23:20:17-05:00 CEqCan, and canonicalization for it - - - - - a22102d9 by Richard Eisenberg at 2020-11-24T23:20:17-05:00 Main changes done. Now to delete code. - - - - - dee0c256 by Richard Eisenberg at 2020-11-24T23:20:18-05:00 Kill off CFunEqCan and CTyEqCan - - - - - a3e0f6cf by Richard Eisenberg at 2020-11-24T23:20:18-05:00 It compiles. - - - - - 75893891 by Richard Eisenberg at 2020-11-24T23:20:18-05:00 Some bugfixing - - - - - 56ee9cee by Richard Eisenberg at 2020-11-24T23:20:18-05:00 Lots of bug fixing - - - - - b59b65bc by Richard Eisenberg at 2020-11-24T23:20:18-05:00 Expand synonyms that mention families, obvs - - - - - 920855a2 by Richard Eisenberg at 2020-11-24T23:20:18-05:00 Super skolems are really super. - - - - - 06cb3183 by Richard Eisenberg at 2020-11-24T23:20:19-05:00 Another bug bites the dust. - - - - - f362ea5a by Richard Eisenberg at 2020-11-24T23:20:19-05:00 Put variable on left only when it will unify - - - - - 3ec0aaa1 by Richard Eisenberg at 2020-11-24T23:20:19-05:00 Tiny little changes - - - - - d2a3edb4 by Richard Eisenberg at 2020-11-24T23:20:19-05:00 Use built-in axioms for injectivity - - - - - 449e25ef by Richard Eisenberg at 2020-11-24T23:20:19-05:00 Stop loop in solver due to blocked hetero eqs - - - - - 83b162bb by Richard Eisenberg at 2020-11-24T23:20:20-05:00 Note [Runaway Derived rewriting] - - - - - 0e087f2e by Richard Eisenberg at 2020-11-24T23:20:20-05:00 Still need to check tyvar/funeq orientation - - - - - 67c8acfe by Richard Eisenberg at 2020-11-24T23:20:49-05:00 More bugfixing - - - - - 22711aa3 by Richard Eisenberg at 2020-11-24T23:20:52-05:00 Orient FunEq/FunEq correctly wrt occurs-check - - - - - bf1eb58c by Richard Eisenberg at 2020-11-24T23:20:53-05:00 Fix import - - - - - 287e969c by Richard Eisenberg at 2020-11-24T23:20:53-05:00 Note [Type variable cycles in Givens] - - - - - 4f629ab2 by Richard Eisenberg at 2020-11-24T23:20:53-05:00 Handle obscure corner case in canonicalize - - - - - 72556f8f by Richard Eisenberg at 2020-11-24T23:20:53-05:00 Handle (=>) specially in pure unifier - - - - - 51418692 by Richard Eisenberg at 2020-11-24T23:20:53-05:00 Start deleting stuff. Hooray! - - - - - ac4b7d52 by Richard Eisenberg at 2020-11-24T23:20:53-05:00 Fix test output - - - - - ec2cd9c7 by Richard Eisenberg at 2020-11-24T23:20:54-05:00 Delete delete delete !! - - - - - ab084222 by Richard Eisenberg at 2020-11-24T23:20:54-05:00 More deleting. Checkpoint before removing FlattenMode - - - - - 3281640b by Richard Eisenberg at 2020-11-24T23:20:54-05:00 Remove FlattenMode - - - - - a1727684 by Richard Eisenberg at 2020-11-24T23:20:54-05:00 Stopped bumping ctLocDepth in runFlatten - - - - - d30ff3ef by Richard Eisenberg at 2020-11-24T23:20:54-05:00 Finished deleting. - - - - - 79084542 by Richard Eisenberg at 2020-11-24T23:20:55-05:00 A few error message wibbles - - - - - 86c7462d by Richard Eisenberg at 2020-11-24T23:20:55-05:00 Some small changes, mostly comments. - - - - - d989a125 by Richard Eisenberg at 2020-11-24T23:20:55-05:00 Fix #18875 by breaking type variable cycles. - - - - - a6437cf9 by Richard Eisenberg at 2020-11-24T23:20:55-05:00 Actually add test files - - - - - 9bd983b7 by Richard Eisenberg at 2020-11-24T23:20:55-05:00 Add Detail (7) to the Note - - - - - c7fc940b by Richard Eisenberg at 2020-11-24T23:20:55-05:00 A few error wibbles - - - - - 1391322f by Richard Eisenberg at 2020-11-24T23:20:56-05:00 Don't simplify extra-constraint holes - - - - - 9464e344 by Richard Eisenberg at 2020-11-24T23:20:56-05:00 Subtleties in Note [Instance and Given overlap] - - - - - fc073a19 by Richard Eisenberg at 2020-11-24T23:20:56-05:00 Update Note [TyVar/TyVar orientation] - - - - - 61d2cfda by Richard Eisenberg at 2020-11-24T23:20:56-05:00 Actually add tests - - - - - 285d8d29 by Richard Eisenberg at 2020-11-24T23:20:56-05:00 Do mightMatchLater correctlier. - - - - - 1fd7947a by Richard Eisenberg at 2020-11-24T23:20:57-05:00 Simplify getNoGivenEqs - - - - - a6e126bd by Richard Eisenberg at 2020-11-24T23:20:57-05:00 Simplify code a bit - - - - - a827fbd1 by Richard Eisenberg at 2020-11-24T23:20:57-05:00 Introduce 3-way for ic_given_eqs - - - - - 73c055c6 by Richard Eisenberg at 2020-11-24T23:20:57-05:00 test LocalGivenEqs - - - - - 3fdaeadf by Richard Eisenberg at 2020-11-24T23:20:57-05:00 Update commentary about HasGivenEqs - - - - - e12e6e13 by Richard Eisenberg at 2020-11-24T23:20:57-05:00 Update notes. - - - - - aa1abe28 by Richard Eisenberg at 2020-11-24T23:20:58-05:00 More documentation around LocalGivenEqs - - - - - c52b30e2 by Richard Eisenberg at 2020-11-24T23:20:58-05:00 Rename the flat-cache. Document it, too. - - - - - cf01300a by Richard Eisenberg at 2020-11-24T23:20:58-05:00 Make EqualCtList into a newtype with NonEmpty - - - - - 210414e3 by Richard Eisenberg at 2020-11-24T23:20:58-05:00 Remove Note [No FunEq improvement for Givens] - - - - - 1d494b14 by Richard Eisenberg at 2020-11-24T23:20:58-05:00 Fix compilation errors from rebasing - - - - - 36f7db05 by Richard Eisenberg at 2020-11-24T23:20:58-05:00 Use DTyConEnv for TcAppMap instead of UDFM - - - - - 405cd093 by Richard Eisenberg at 2020-11-24T23:20:59-05:00 Remove mention of CFunEqCan from rebasing - - - - - 8ba8d46a by Richard Eisenberg at 2020-11-24T23:20:59-05:00 Fix error output - - - - - 25b82e52 by Richard Eisenberg at 2020-11-24T23:20:59-05:00 Reimplement flatten_exact_fam_app Hopefully will be faster? - - - - - 0a013b3b by Richard Eisenberg at 2020-11-24T23:20:59-05:00 Improve performance - - - - - fcc45013 by Richard Eisenberg at 2020-11-24T23:20:59-05:00 Don't fail eagerly on runaway Derived instances - - - - - ed274fcb by Richard Eisenberg at 2020-11-24T23:20:59-05:00 Improve some comments - - - - - 9f373dc4 by Richard Eisenberg at 2020-11-24T23:21:00-05:00 Checkpoint before adding filterTM - - - - - d76dc2f9 by Richard Eisenberg at 2020-11-24T23:21:00-05:00 remove stale givens from famapp-cache - - - - - 81efda55 by Richard Eisenberg at 2020-11-24T23:21:00-05:00 Remove unused parameter - - - - - 0b2ea8c4 by Richard Eisenberg at 2020-11-24T23:21:00-05:00 Address points from Hécate. - - - - - 546c58cb by Richard Eisenberg at 2020-11-24T23:21:00-05:00 Reviews on GitLab - - - - - c576c273 by Richard Eisenberg at 2020-11-24T23:21:01-05:00 Use tcSplitTyConApp_maybe in can_eq_nc' - - - - - bb7a7ce0 by Richard Eisenberg at 2020-11-24T23:21:01-05:00 Try removing (2b). Let's see what the testsuite says - - - - - b1599c78 by Richard Eisenberg at 2020-11-24T23:21:01-05:00 Really remove (2b) - - - - - 70637438 by Richard Eisenberg at 2020-11-24T23:21:01-05:00 More reactions to reviews - - - - - 1e4e66f7 by Richard Eisenberg at 2020-11-24T23:21:01-05:00 Revisit [Prevent unification with type families] - - - - - bde84897 by Richard Eisenberg at 2020-11-24T23:21:01-05:00 Don't flatten during instance lookup - - - - - 081c00ad by Richard Eisenberg at 2020-11-24T23:21:02-05:00 Comments, etc., from Friday - - - - - d5d8ce80 by Richard Eisenberg at 2020-11-24T23:21:02-05:00 Make the fast path work without roles - - - - - 48963372 by Richard Eisenberg at 2020-11-24T23:21:02-05:00 Use MCo - - - - - d1c1600f by Richard Eisenberg at 2020-11-24T23:21:02-05:00 Remove unused parameter - - - - - 2036eecc by Richard Eisenberg at 2020-11-24T23:21:02-05:00 Add test case - - - - - 5fd9c466 by Richard Eisenberg at 2020-11-24T23:21:03-05:00 s/flatten/rewrite` - - - - - bb01cdb7 by Richard Eisenberg at 2020-11-24T23:21:03-05:00 inline finish - - - - - e00f2ebd by Richard Eisenberg at 2020-11-24T23:21:03-05:00 Use a flag on `finish` - - - - - 5adfd0ec by Richard Eisenberg at 2020-11-24T23:21:03-05:00 Don't avoid adding inerts to cache - - - - - 8623f3bb by Richard Eisenberg at 2020-11-24T23:21:03-05:00 Kill off Note [Unification with skolems] - - - - - dee56d9f by Richard Eisenberg at 2020-11-24T23:21:03-05:00 Introduce canNC - - - - - 6df1bfd6 by Richard Eisenberg at 2020-11-24T23:21:04-05:00 Remove isTyVarHead - - - - - 7efceb85 by Richard Eisenberg at 2020-11-24T23:21:04-05:00 Accommodate #18987 - - - - - d3d30796 by Richard Eisenberg at 2020-11-24T23:21:04-05:00 let-bound skolems - - - - - 853dd86b by Richard Eisenberg at 2020-11-24T23:21:04-05:00 More comments on HasGivenEqs - - - - - 0bb0e32a by Richard Eisenberg at 2020-11-24T23:21:04-05:00 Fix error output - - - - - c417aa24 by Richard Eisenberg at 2020-11-24T23:21:04-05:00 Some comments - - - - - 30 changed files: - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - + compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map.hs → compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Ext/Utils.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Gen/Bind.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2b7af3cd500bb587736ff455645fb4cd5ff986f3...c417aa249c71e29dfb3f976076d722be88c05fe6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2b7af3cd500bb587736ff455645fb4cd5ff986f3...c417aa249c71e29dfb3f976076d722be88c05fe6 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 Wed Nov 25 11:34:50 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Wed, 25 Nov 2020 06:34:50 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18987 Message-ID: <5fbe415a3f7fe_86cbee25901591f4@gitlab.mail> Simon Peyton Jones pushed new branch wip/T18987 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18987 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 Wed Nov 25 12:30:36 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Wed, 25 Nov 2020 07:30:36 -0500 Subject: [Git][ghc/ghc][wip/T18891] Fix kind inference for data types. Again. Message-ID: <5fbe4e6cf2d8b_86c3fc6ab4f115c1637cd@gitlab.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: cbf62337 by Simon Peyton Jones at 2020-11-25T12:29:21+00:00 Fix kind inference for data types. Again. This patch improves kcConDecls, when we are inferring the kind of a data type decl. Specifically * In kcConDecls/kcConDecl make it clear that the tc_res_kind argument is only used in the H98 case; and in that case there is not result kind signature; and hence no need for the disgusting splitPiTys in kcConDecls (now thankfully gone). The GADT case is a bit different to before, and much nicer. This is what fixes #18891. See Note [kcConDecls: kind-checking data type decls] * Do not look at the constructor decls of a data/newtype instance in tcDataFamInstanceHeader. See new Note [Kind inference for data family instances] This causes a few knock-on effects in the tests suite, because we require more information than before in the instance /header/ * Minor improvement in kcTyClDecl, combining GADT and H98 case. Fixes #18891 - - - - - 20 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/deriving/should_compile/T11416.hs - testsuite/tests/deriving/should_compile/T9359.hs - testsuite/tests/patsyn/should_fail/T15685.stderr - testsuite/tests/polykinds/T13659.stderr - testsuite/tests/polykinds/T16221a.stderr - testsuite/tests/th/T9692.hs - + testsuite/tests/typecheck/should_compile/T18891.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/T18891a.hs - + testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2981,7 +2981,7 @@ bindOuterSigTKBndrs_Tv_M :: TcTyMode -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) -- Do not push level; do not make implication constraint; use Tvs -- Two major clients of this "bind-only" path are: --- Note [Kind-checking for GADTs] in TyCl +-- Note [Using TyVarTvs for kind-checking GADTs] in TyCl -- Note [Checking partial type signatures] bindOuterSigTKBndrs_Tv_M mode = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = True @@ -3294,8 +3294,8 @@ When we /must/ clone. When kind-checking T, we give (a :: kappa1). Then: - In kcConDecl we make a TyVarTv unification variable kappa2 for k2 - (as described in Note [Kind-checking for GADTs], even though this - example is an existential) + (as described in Note [Using TyVarTvs for kind-checking GADTs], + even though this example is an existential) - So we get (b :: kappa2) via bindExplicitTKBndrs_Tv - We end up unifying kappa1 := kappa2, because of the (SameKind a b) ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -1529,27 +1529,16 @@ kcTyClDecl :: TyClDecl GhcRn -> TcTyCon -> TcM () -- result kind signature have already been dealt with -- by inferInitialKind, so we can ignore them here. -kcTyClDecl (DataDecl { tcdLName = (L _ name) - , tcdDataDefn = defn }) tyCon - | HsDataDefn { dd_cons = cons@((L _ (ConDeclGADT {})) : _) - , dd_ctxt = (L _ []) - , dd_ND = new_or_data } <- defn - = -- See Note [Implementation of UnliftedNewtypes] STEP 2 - kcConDecls new_or_data (tyConResKind tyCon) cons - - -- hs_tvs and dd_kindSig already dealt with in inferInitialKind - -- This must be a GADT-style decl, - -- (see invariants of DataDefn declaration) - -- so (a) we don't need to bring the hs_tvs into scope, because the - -- ConDecls bind all their own variables - -- (b) dd_ctxt is not allowed for GADT-style decls, so we can ignore it - - | HsDataDefn { dd_ctxt = ctxt - , dd_cons = cons - , dd_ND = new_or_data } <- defn +kcTyClDecl (DataDecl { tcdLName = (L _ name), tcdDataDefn = defn }) tycon + | HsDataDefn { dd_ctxt = ctxt, dd_cons = cons, dd_ND = new_or_data } <- defn = bindTyClTyVars name $ \ _ _ _ -> - do { _ <- tcHsContext ctxt - ; kcConDecls new_or_data (tyConResKind tyCon) cons + -- NB: binding these tyvars isn't necessary for GADTs, but it does no + -- harm. For GADTs, each data con brings its own tyvars into scope, + -- and the ones from this bindTyClTyVars are either not mentioned or + -- (conceivably) shadowed. + do { traceTc "kcTyClDecl" (ppr tycon $$ ppr (tyConTyVars tycon) $$ ppr (tyConResKind tycon)) + ; _ <- tcHsContext ctxt + ; kcConDecls new_or_data (tyConResKind tycon) cons } kcTyClDecl (SynDecl { tcdLName = L _ name, tcdRhs = rhs }) _tycon @@ -1606,13 +1595,12 @@ kcConGADTArgs new_or_data res_kind con_args = case con_args of kcConDecls :: NewOrData -> Kind -- The result kind signature + -- Used only in H98 case -> [LConDecl GhcRn] -- The data constructors -> TcM () -kcConDecls new_or_data res_kind cons - = mapM_ (wrapLocM_ (kcConDecl new_or_data final_res_kind)) cons - where - (_, final_res_kind) = splitPiTys res_kind - -- See Note [kcConDecls result kind] +-- See Note [kcConDecls: kind-checking data type decls] +kcConDecls new_or_data tc_res_kind cons + = mapM_ (wrapLocM_ (kcConDecl new_or_data tc_res_kind)) cons -- Kind check a data constructor. In additional to the data constructor, -- we also need to know about whether or not its corresponding type was @@ -1623,82 +1611,69 @@ kcConDecl :: NewOrData -> Kind -- Result kind of the type constructor -- Usually Type but can be TYPE UnliftedRep -- or even TYPE r, in the case of unlifted newtype + -- Used only in H98 case -> ConDecl GhcRn -> TcM () -kcConDecl new_or_data res_kind (ConDeclH98 +kcConDecl new_or_data tc_res_kind (ConDeclH98 { con_name = name, con_ex_tvs = ex_tvs , con_mb_cxt = ex_ctxt, con_args = args }) = addErrCtxt (dataConCtxtName [name]) $ discardResult $ bindExplicitTKBndrs_Tv ex_tvs $ do { _ <- tcHsMbContext ex_ctxt - ; kcConH98Args new_or_data res_kind args + ; kcConH98Args new_or_data tc_res_kind args -- We don't need to check the telescope here, -- because that's done in tcConDecl } -kcConDecl new_or_data res_kind (ConDeclGADT +kcConDecl new_or_data + _tc_res_kind -- Not used in GADT case (and doesn't make sense) + (ConDeclGADT { con_names = names, con_bndrs = L _ outer_bndrs, con_mb_cxt = cxt , con_g_args = args, con_res_ty = res_ty }) - = -- Even though the GADT-style data constructor's type is closed, - -- we must still kind-check the type, because that may influence - -- the inferred kind of the /type/ constructor. Example: - -- data T f a where - -- MkT :: f a -> T f a - -- If we don't look at MkT we won't get the correct kind - -- for the type constructor T + = -- See Note [kcConDecls: kind-checking data type decls] addErrCtxt (dataConCtxtName names) $ discardResult $ bindOuterSigTKBndrs_Tv outer_bndrs $ - -- Why "_Tv"? See Note [Kind-checking for GADTs] + -- Why "_Tv"? See Note [Using TyVarTvs for kind-checking GADTs] do { _ <- tcHsMbContext cxt - ; kcConGADTArgs new_or_data res_kind args - ; _ <- tcHsOpenType res_ty + ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty) + ; con_res_kind <- newOpenTypeKind + ; _ <- tcCheckLHsType res_ty (TheKind con_res_kind) + ; kcConGADTArgs new_or_data con_res_kind args + ; traceTc "kcConDecl:GADT }" (ppr names $$ ppr con_res_kind) ; return () } -{- Note [kcConDecls result kind] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We might have e.g. - data T a :: Type -> Type where ... -or - newtype instance N a :: Type -> Type where .. -in which case, the 'res_kind' passed to kcConDecls will be - Type->Type - -We must look past those arrows, or even foralls, to the Type in the -corner, to pass to kcConDecl c.f. #16828. Hence the splitPiTys here. - -I am a bit concerned about tycons with a declaration like - data T a :: Type -> forall k. k -> Type where ... - -It does not have a CUSK, so kcInferDeclHeader will make a TcTyCon -with tyConResKind of Type -> forall k. k -> Type. Even that is fine: -the splitPiTys will look past the forall. But I'm bothered about -what if the type "in the corner" mentions k? This is incredibly -obscure but something like this could be bad: - data T a :: Type -> foral k. k -> TYPE (F k) where ... - -I bet we are not quite right here, but my brain suffered a buffer -overflow and I thought it best to nail the common cases right now. - -Note [Recursion and promoting data constructors] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We don't want to allow promotion in a strongly connected component -when kind checking. - -Consider: - data T f = K (f (K Any)) - -When kind checking the `data T' declaration the local env contains the -mappings: - T -> ATcTyCon - K -> APromotionErr - -APromotionErr is only used for DataCons, and only used during type checking -in tcTyClGroup. - -Note [Kind-checking for GADTs] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [kcConDecls: kind-checking data type decls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +kcConDecls is used when we are inferring the kind of the type +constructor in a data type declaration. E.g. + data T f a = MkT (f a) +we want to infer the kind of 'f' and 'a'. The basic plan is described +in Note [Inferring kinds for type declarations]; here are doing Step 2. + +In the H98 case, for unlifted newtypes only, we need the result kind of +the TyCon, to unify with the argument kind. The tycon's result kind +is not used at all in the GADT case. + +In the GADT case we may have this: + data T f a where + MkT :: forall g b. g b -> T g b +Notice that the variables f,a, and g,b are quite distinct. +Nevertheless, this decl must still influence the kind T (which is, +remember Step 1, something like T :: kappa1 -> kappa2 -> Type), otherwise +we'd infer the bogus kind T :: forall k1 k2. k1 -> k2 -> Type. + +The data constructor type influences the kind of T simply by +kind-checking the result type (T g b), which will force 'f' and 'g' to +have the same kinds. This is the call to + tcCheckLHsType res_ty (TheKind con_res_kind) +Because this is the result type of an arrow, we know the kind must be +of form (TYPE rr), and we get better error messages if we enforce that +here (e.g. test gadt10). + +Note [Using TyVarTvs for kind-checking GADTs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider data Proxy a where @@ -1708,26 +1683,27 @@ Consider It seems reasonable that this should be accepted. But something very strange is going on here: when we're kind-checking this declaration, we need to unify the kind of `a` with k and j -- even though k and j's scopes are local to the type of -MkProxy{1,2}. The best approach we've come up with is to use TyVarTvs during -the kind-checking pass. First off, note that it's OK if the kind-checking pass -is too permissive: we'll snag the problems in the type-checking pass later. -(This extra permissiveness might happen with something like +MkProxy{1,2}. + +In effect, we are simply gathering constraints on the shape of Proxy's +kind, with no skolemisation or implication constraints involved at all. + +The best approach we've come up with is to use TyVarTvs during the +kind-checking pass, rather than ordinary skolems. This is why we use +the "_Tv" variant, bindOuterSigTKBndrs_Tv. + +Our only goal is to gather constraints on the kind of the type constructor; +we do not certify that the data declaration is well-kinded. For example: data SameKind :: k -> k -> Type data Bad a where MkBad :: forall k1 k2 (a :: k1) (b :: k2). Bad (SameKind a b) -which would be accepted if k1 and k2 were TyVarTvs. This is correctly rejected -in the second pass, though. Test case: polykinds/TyVarTvKinds3) -Recall that the kind-checking pass exists solely to collect constraints -on the kinds and to power unification. - -To achieve the use of TyVarTvs, we must be careful to use specialized functions -that produce TyVarTvs, not ordinary skolems. This is why we need -kcExplicitTKBndrs and kcImplicitTKBndrs in GHC.Tc.Gen.HsType, separate from their -tc... variants. +which would be accepted by kcConDecl because k1 and k2 are +TyVarTvs. It is correctly rejected in the second pass, tcConDecl. Test +case: polykinds/TyVarTvKinds3) -The drawback of this approach is sometimes it will accept a definition that +One drawback of this approach is sometimes it will accept a definition that a (hypothetical) declarative specification would likely reject. As a general rule, we don't want to allow polymorphic recursion without a CUSK. Indeed, the whole point of CUSKs is to allow polymorphic recursion. Yet, the TyVarTvs @@ -1746,6 +1722,23 @@ be rejected (without a CUSK). However, the accepted definitions are indeed well-kinded and any rejected definitions would be accepted with a CUSK, and so this wrinkle need not cause anyone to lose sleep. +Note [Recursion and promoting data constructors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We don't want to allow promotion in a strongly connected component +when kind checking. + +Consider: + data T f = K (f (K Any)) + +When kind checking the `data T' declaration the local env contains the +mappings: + T -> ATcTyCon + K -> APromotionErr + +APromotionErr is only used for DataCons, and only used during type checking +in tcTyClGroup. + + ************************************************************************ * * \subsection{Type checking} @@ -3214,7 +3207,7 @@ tcConDecl :: KnotTied TyCon -- Representation tycon. Knot-tied! -> ConDecl GhcRn -> TcM [DataCon] -tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs res_kind res_tmpl new_or_data (ConDeclH98 { con_name = lname@(L _ name) , con_ex_tvs = explicit_tkv_nms , con_mb_cxt = hs_ctxt @@ -3224,7 +3217,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Get hold of the existential type variables -- e.g. data T a = forall k (b::k) f. MkT a (f b) - -- Here tmpl_bndrs = {a} + -- Here tc_bndrs = {a} -- hs_qvars = HsQTvs { hsq_implicit = {k} -- , hsq_explicit = {f,b} } @@ -3242,29 +3235,35 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data } - ; let tmpl_tvs = binderVars tmpl_bndrs - ; let fake_ty = mkSpecForAllTys tmpl_tvs $ + ; let tc_tvs = binderVars tc_bndrs + fake_ty = mkSpecForAllTys tc_tvs $ mkInvisForAllTys exp_tvbndrs $ mkPhiTy ctxt $ mkVisFunTys arg_tys $ unitTy -- That type is a lie, of course. (It shouldn't end in ()!) -- And we could construct a proper result type from the info - -- at hand. But the result would mention only the tmpl_tvs, + -- at hand. But the result would mention only the univ_tvs, -- and so it just creates more work to do it right. Really, -- we're only doing this to find the right kind variables to -- quantify over, and this type is fine for that purpose. - -- exp_tvs have explicit, user-written binding sites + -- exp_tvbndrs have explicit, user-written binding sites -- the kvs below are those kind variables entirely unmentioned by the user -- and discovered only by generalization ; kvs <- kindGeneralizeAll fake_ty - ; let skol_tvs = kvs ++ tmpl_tvs + ; let skol_tvs = tc_tvs ++ kvs ++ binderVars exp_tvbndrs ; reportUnsolvedEqualities skol_info skol_tvs tclvl wanted - - -- Zonk to Types + -- The skol_info claims that all the variables are bound + -- by the data constructor decl, whereas actually the + -- univ_tvs are bound by the data type decl itself. It + -- would be better to have a doubly-nested implication. + -- But that just doesn't seem worth it. + -- See test dependent/should_fail/T13780a + + -- Zonk to Types ; (ze, qkvs) <- zonkTyBndrs kvs ; (ze, user_qtvbndrs) <- zonkTyVarBindersX ze exp_tvbndrs ; arg_tys <- zonkScaledTcTypesToTypesX ze arg_tys @@ -3272,15 +3271,13 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Can't print univ_tvs, arg_tys etc, because we are inside the knot here ; traceTc "tcConDecl 2" (ppr name $$ ppr field_lbls) - ; let - univ_tvbs = tyConInvisTVBinders tmpl_bndrs - univ_tvs = binderVars univ_tvbs - ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs - ex_tvs = binderVars ex_tvbs - -- For H98 datatypes, the user-written tyvar binders are precisely - -- the universals followed by the existentials. - -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. - user_tvbs = univ_tvbs ++ ex_tvbs + ; let univ_tvbs = tyConInvisTVBinders tc_bndrs + ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs + ex_tvs = binderVars ex_tvbs + -- For H98 datatypes, the user-written tyvar binders are precisely + -- the universals followed by the existentials. + -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. + user_tvbs = univ_tvbs ++ ex_tvbs ; traceTc "tcConDecl 2" (ppr name) ; is_infix <- tcConIsInfixH98 name hs_args @@ -3288,7 +3285,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data ; fam_envs <- tcGetFamInstEnvs ; dc <- buildDataCon fam_envs name is_infix rep_nm stricts Nothing field_lbls - univ_tvs ex_tvs user_tvbs + tc_tvs ex_tvs user_tvbs [{- no eq_preds -}] ctxt arg_tys res_tmpl rep_tycon tag_map -- NB: we put data_tc, the type constructor gotten from the @@ -3299,7 +3296,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data where skol_info = DataConSkol name -tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs _res_kind res_tmpl new_or_data -- NB: don't use res_kind here, as it's ill-scoped. Instead, -- we get the res_kind by typechecking the result type. (ConDeclGADT { con_names = names @@ -3344,7 +3341,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data ; res_ty <- zonkTcTypeToTypeX ze res_ty ; let (univ_tvs, ex_tvs, tvbndrs', eq_preds, arg_subst) - = rejigConRes tmpl_bndrs res_tmpl tvbndrs res_ty + = rejigConRes tc_bndrs res_tmpl tvbndrs res_ty -- See Note [Checking GADT return types] ctxt' = substTys arg_subst ctxt @@ -3532,9 +3529,9 @@ errors reported in one pass. See #7175, and #10836. -- TI :: forall b1 c1. (b1 ~ c1) => b1 -> :R7T b1 c1 -- In this case orig_res_ty = T (e,e) -rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result type; e.g. - -- data instance T [a] b c ... - -- gives template ([a,b,c], T [a] b c) +rejigConRes :: [KnotTied TyConBinder] -- Template for result type; e.g. + -> KnotTied Type -- data instance T [a] b c ... + -- gives template ([a,b,c], T [a] b c) -> [InvisTVBinder] -- The constructor's type variables (both inferred and user-written) -> KnotTied Type -- res_ty -> ([TyVar], -- Universal @@ -3546,10 +3543,10 @@ rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result -- We don't check that the TyCon given in the ResTy is -- the same as the parent tycon, because checkValidDataCon will do it -- NB: All arguments may potentially be knot-tied -rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty +rejigConRes tc_tvbndrs res_tmpl dc_tvbndrs res_ty -- E.g. data T [a] b c where -- MkT :: forall x y z. T [(x,y)] z z - -- The {a,b,c} are the tmpl_tvs, and the {x,y,z} are the dc_tvs + -- The {a,b,c} are the tc_tvs, and the {x,y,z} are the dc_tvs -- (NB: unlike the H98 case, the dc_tvs are not all existential) -- Then we generate -- Univ tyvars Eq-spec @@ -3564,7 +3561,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- , [], [x,y,z] -- , [a~(x,y),b~z], ) | Just subst <- tcMatchTy res_tmpl res_ty - = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tmpl_tvs dc_tvs subst + = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tc_tvs dc_tvs subst raw_ex_tvs = dc_tvs `minusList` univ_tvs (arg_subst, substed_ex_tvs) = substTyVarBndrs kind_subst raw_ex_tvs @@ -3591,10 +3588,10 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- albeit bogus, relying on checkValidDataCon to check the -- bad-result-type error before seeing that the other fields look odd -- See Note [Checking GADT return types] - = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, dc_tvbndrs, [], emptyTCvSubst) + = (tc_tvs, dc_tvs `minusList` tc_tvs, dc_tvbndrs, [], emptyTCvSubst) where - dc_tvs = binderVars dc_tvbndrs - tmpl_tvs = binderVars tmpl_bndrs + dc_tvs = binderVars dc_tvbndrs + tc_tvs = binderVars tc_tvbndrs {- Note [mkGADTVars] ~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -688,9 +688,8 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env -- Do /not/ check that the number of patterns = tyConArity fam_tc -- See [Arity of data families] in GHC.Core.FamInstEnv ; (qtvs, pats, res_kind, stupid_theta) - <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs - fixity hs_ctxt hs_pats m_ksig hs_cons - new_or_data + <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity + hs_ctxt hs_pats m_ksig new_or_data -- Eta-reduce the axiom if possible -- Quite tricky: see Note [Implementing eta reduction for data families] @@ -857,7 +856,7 @@ TyVarEnv will simply be empty, and there is nothing to worry about. tcDataFamInstHeader :: AssocInstInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn -> LexicalFixity -> LHsContext GhcRn - -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> [LConDecl GhcRn] + -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> NewOrData -> TcM ([TyVar], [Type], Kind, ThetaType) -- The "header" of a data family instance is the part other than @@ -865,7 +864,7 @@ tcDataFamInstHeader -- e.g. data instance D [a] :: * -> * where ... -- Here the "header" is the bit before the "where" tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity - hs_ctxt hs_pats m_ksig hs_cons new_or_data + hs_ctxt hs_pats m_ksig new_or_data = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (scoped_tvs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ @@ -884,8 +883,8 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity -- Add constraints from the result signature ; res_kind <- tc_kind_sig m_ksig - -- Add constraints from the data constructors - ; kcConDecls new_or_data res_kind hs_cons + -- Do not add constraints from the data constructors + -- See Note [Kind inference for data family instances] -- Check that the result kind of the TyCon applied to its args -- is compatible with the explicit signature (or Type, if there @@ -1049,6 +1048,81 @@ however, so this Note aims to describe these subtleties: themselves. Heavy sigh. But not truly hard; that's what tcbVisibilities does. +Note [Kind inference for data family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this GADT-style data type declaration, where I have used +fresh variables in the data constructor's type, to stress that c,d are +quite distinct from a,b. + data T a b where + MkT :: forall c d. c d -> T c d + +Following Note [Inferring kinds for type declarations] in GHC.Tc.TyCl, +to infer T's kind, we initially give T :: kappa, a monomorpic kind, +gather constraints from the header and data constructors, and conclude + T :: (kappa1 -> type) -> kappa1 -> Type +Then we generalise, giving + T :: forall k. (k->Type) -> k -> Type + +Now what about a data /instance/ decl + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p Int where ... + +No doubt here! The poly-kinded T is instantiated with k=Type, so the +header really looks like + data instance T @Type (p :: Type->Type) Int where ... + +But what about this? + data instance T p q where + MkT :: forall r. r Int -> T r Int + +So what kind do 'p' and 'q' have? No clues from the header, but from +the data constructor we can clearly see that (r :: Type->Type). Does +that mean that the the /entire data instance/ is instantiated at Type, +like this? + data instance T @Type (p :: Type->Type) (q :: Type) where + ... + +Not at all! This is a /GADT/-style decl, so the kind argument might +be specialised in this particular data constructor, thus: + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall (r :: Type -> Type). + r Int -> T @Type r Int +(and perhaps specialised differently in some other data +constructor MkT2). + +The key difference in this case and 'data T' at the top of this Note +is that we have no known kind for 'data T'. We thus forbid different +specialisations of T in its constructors, in an attempt to avoid +inferring polymorphic recursion. In data family T, however, there is +no problem with polymorphic recursion: we already /fully know/ T's +kind -- that came from the family declaration, and is not influenced +by the data instances -- and hence we /can/ specialise T's kind +differently in different GADT data constructors. + +SHORT SUMMARY: in a data instance decl, it's not clear whether kind +constraints arising from the data constructors should be considered +local to the (GADT) data /constructor/ or should apply to the entire +data instance. + +DESIGN CHOICE: in data/newtype family instance declarations, we ignore +the /data constructor/ declarations altogether, looking only at the +data instance /header/. + +Observations: +* This choice is simple to describe, as well as simple to implment. + For a data/newtype instance decl, the instance kinds are influenced + /only/ by the header. + +* We could treat Haskell-98 style data-instance decls differently, by + taking the data constructors into account, since there are no GADT + issues. + +* Ditto newtypes, since again you can't have newtype GADTs. + +But for now at least, we keep the simplest choice. See #18891 and !4419 +for more discussion of this issue.a + -} ===================================== testsuite/tests/dependent/should_fail/T13780a.stderr ===================================== @@ -3,7 +3,7 @@ T13780a.hs:9:40: error: • Couldn't match kind ‘a’ with ‘Bool’ Expected kind ‘Foo a’, but ‘MkFoo’ has kind ‘Foo Bool’ ‘a’ is a rigid type variable bound by - a family instance declaration + the data constructor ‘SMkFoo’ at T13780a.hs:9:20-31 • In the second argument of ‘(~)’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ ===================================== testsuite/tests/deriving/should_compile/T11416.hs ===================================== @@ -12,9 +12,11 @@ newtype T f (a :: ConstantT Type f) = T (f a) deriving Functor data family TFam1 (f :: k1) (a :: k2) -newtype instance TFam1 f (ConstantT a f) = TFam1 (f a) +newtype instance TFam1 (f :: k -> Type) (ConstantT (a :: k) f) + = TFam1 (f a) deriving Functor data family TFam2 (f :: k1) (a :: k2) -newtype instance TFam2 f (a :: ConstantT Type f) = TFam2 (f a) +newtype instance TFam2 (f :: Type -> Type) (a :: ConstantT Type f) + = TFam2 (f a) deriving Functor ===================================== testsuite/tests/deriving/should_compile/T9359.hs ===================================== @@ -5,10 +5,12 @@ import Data.Kind (Type) data Cmp a where Sup :: Cmp a - V :: a -> Cmp a - deriving (Show, Eq) +-- V :: a -> Cmp a +-- deriving (Show, Eq) +{- data family CmpInterval (a :: Cmp k) (b :: Cmp k) :: Type data instance CmpInterval (V c) Sup = Starting c deriving( Show ) +-} \ No newline at end of file ===================================== testsuite/tests/patsyn/should_fail/T15685.stderr ===================================== @@ -1,13 +1,13 @@ T15685.hs:13:24: error: - • Could not deduce: a ~ [k0] - from the context: as ~ (a1 : as1) + • Could not deduce: k ~ [k0] + from the context: as ~ (a : as1) bound by a pattern with constructor: - Here :: forall {a1} (f :: a1 -> *) (a2 :: a1) (as :: [a1]). - f a2 -> NS f (a2 : as), + Here :: forall {k} (f :: k -> *) (a :: k) (as :: [k]). + f a -> NS f (a : as), in a pattern synonym declaration at T15685.hs:13:19-26 - ‘a’ is a rigid type variable bound by + ‘k’ is a rigid type variable bound by the inferred type of HereNil :: NS f as at T15685.hs:13:9-15 Possible fix: add a type signature for ‘HereNil’ ===================================== testsuite/tests/polykinds/T13659.stderr ===================================== @@ -1,6 +1,6 @@ -T13659.hs:14:27: error: - • Expected a type, but ‘a’ has kind ‘[*]’ - • In the first argument of ‘Format’, namely ‘'[Int, a]’ - In the type ‘Format '[Int, a]’ +T13659.hs:14:15: error: + • Expected kind ‘[*]’, but ‘a’ has kind ‘*’ + • In the first argument of ‘Format’, namely ‘a’ + In the type ‘Format a’ In the definition of data constructor ‘I’ ===================================== testsuite/tests/polykinds/T16221a.stderr ===================================== @@ -1,7 +1,7 @@ T16221a.hs:6:49: error: - • Expected kind ‘k’, but ‘b’ has kind ‘k1’ - ‘k1’ is a rigid type variable bound by + • Expected kind ‘k’, but ‘b’ has kind ‘k2’ + ‘k2’ is a rigid type variable bound by an explicit forall k (b :: k) at T16221a.hs:6:20 ‘k’ is a rigid type variable bound by ===================================== testsuite/tests/th/T9692.hs ===================================== @@ -12,7 +12,7 @@ class C a where data F a (b :: k) :: Type instance C Int where - data F Int x = FInt x + data F Int (x :: Type) = FInt x $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info ===================================== testsuite/tests/typecheck/should_compile/T18891.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +data family T2 (a :: k) +data instance T2 a where + MkT2 :: T2 Maybe + +newtype N3 :: forall k -> TYPE k where + MkN3 :: N3 m -> N3 m + +type N4 :: forall k -> TYPE k +newtype N4 :: forall k -> TYPE k where + MkN4 :: N4 m -> N4 m ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs ===================================== @@ -4,6 +4,8 @@ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} module UnliftedNewtypesUnassociatedFamily where @@ -20,7 +22,16 @@ newtype instance DFT ('TupleRep '[ 'IntRep, 'WordRep]) data instance DFT 'LiftedRep = MkDFT4 | MkDFT5 data family DF :: TYPE (r :: RuntimeRep) -newtype instance DF = MkDF1 Int# -newtype instance DF = MkDF2 Word# -newtype instance DF = MkDF3 (# Int#, Word# #) + +-- Use a type application +newtype instance DF @IntRep = MkDF1 Int# + +-- Use a kind signature +newtype instance DF :: TYPE 'WordRep where + MkDF2 :: Word# -> DF + +-- Also uses a kind signature +newtype instance DF :: TYPE ('TupleRep '[ 'IntRep, 'WordRep ]) where + MkDF3 :: (# Int#, Word# #) -> DF + data instance DF = MkDF4 | MkDF5 ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs ===================================== @@ -10,14 +10,14 @@ module UnliftedNewtypesUnassociatedFamily where import GHC.Int (Int(I#)) -import GHC.Exts (Int#,Word#,RuntimeRep(IntRep)) +import GHC.Exts (Int#,Word#,RuntimeRep(IntRep, WordRep)) import GHC.Exts (TYPE) type KindOf (a :: TYPE k) = k data family D (a :: TYPE r) :: TYPE r -newtype instance D a = MkWordD Word# +newtype instance D (a :: TYPE 'WordRep) = MkWordD Word# -newtype instance D a :: TYPE (KindOf a) where - MkIntD :: forall (a :: TYPE 'IntRep). Int# -> D a +newtype instance D (a :: TYPE 'IntRep) :: TYPE (KindOf a) where + MkIntD :: forall (b :: TYPE 'IntRep). Int# -> D b ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,5 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) +test('T18891', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T18891a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +newtype N1 :: forall k. TYPE k where + MkN1 :: N1 -> N1 + +type N2 :: forall k. TYPE k +newtype N2 :: forall k. TYPE k where + MkN2 :: N2 -> N2 + ===================================== testsuite/tests/typecheck/should_fail/T18891a.stderr ===================================== @@ -0,0 +1,12 @@ + +T18891a.hs:8:4: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN1 :: N1 -> N1 + • In the definition of data constructor ‘MkN1’ + In the newtype declaration for ‘N1’ + +T18891a.hs:12:3: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN2 :: N2 -> N2 + • In the definition of data constructor ‘MkN2’ + In the newtype declaration for ‘N2’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr ===================================== @@ -1,11 +1,5 @@ -UnliftedNewtypesFamilyKindFail2.hs:12:20: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the newtype instance declaration for ‘F’ - -UnliftedNewtypesFamilyKindFail2.hs:12:31: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the type ‘(F 5)’ - In the definition of data constructor ‘MkF’ +UnliftedNewtypesFamilyKindFail2.hs:12:20: error: + • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ + • In the first argument of ‘F’, namely ‘5’ + In the newtype instance declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} + +module UnliftedNewtypesUnassociatedFamily where + +import GHC.Int (Int(I#)) +import GHC.Word (Word(W#)) +import GHC.Exts (Int#,Word#) +import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep)) + +data family DF :: TYPE (r :: RuntimeRep) + +-- All these fail: see #18891 and !4419 +-- See Note [Kind inference for data family instances] +-- in GHC.Tc.TyCl.Instance +newtype instance DF = MkDF1a Int# +newtype instance DF = MkDF2a Word# +newtype instance DF = MkDF3a (# Int#, Word# #) ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr ===================================== @@ -0,0 +1,18 @@ + +UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error: + • Expecting a lifted type, but ‘Int#’ is unlifted + • In the type ‘Int#’ + In the definition of data constructor ‘MkDF1a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error: + • Expecting a lifted type, but ‘Word#’ is unlifted + • In the type ‘Word#’ + In the definition of data constructor ‘MkDF2a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error: + • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted + • In the type ‘(# Int#, Word# #)’ + In the definition of data constructor ‘MkDF3a’ + In the newtype instance declaration for ‘DF’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKind', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, ['']) test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, ['']) +test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, ['']) test('T13834', normal, compile_fail, ['']) test('T17077', normal, compile_fail, ['']) test('T16512a', normal, compile_fail, ['']) @@ -589,3 +590,4 @@ test('T18640b', normal, compile_fail, ['']) test('T18640c', normal, compile_fail, ['']) test('T10709', normal, compile_fail, ['']) test('T10709b', normal, compile_fail, ['']) +test('T18891a', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cbf62337b8d72a0c689a300863ab897aa1f77b6d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cbf62337b8d72a0c689a300863ab897aa1f77b6d 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 Wed Nov 25 12:51:26 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Wed, 25 Nov 2020 07:51:26 -0500 Subject: [Git][ghc/ghc][wip/T18891] Fix kind inference for data types. Again. Message-ID: <5fbe534eb3f49_86ce89fc5c16850@gitlab.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: 6f6cd8b0 by Simon Peyton Jones at 2020-11-25T12:49:58+00:00 Fix kind inference for data types. Again. This patch improves kcConDecls, when we are inferring the kind of a data type decl. Specifically * In kcConDecls/kcConDecl make it clear that the tc_res_kind argument is only used in the H98 case; and in that case there is not result kind signature; and hence no need for the disgusting splitPiTys in kcConDecls (now thankfully gone). The GADT case is a bit different to before, and much nicer. This is what fixes #18891. See Note [kcConDecls: kind-checking data type decls] * Do not look at the constructor decls of a data/newtype instance in tcDataFamInstanceHeader. See new Note [Kind inference for data family instances] This causes a few knock-on effects in the tests suite, because we require more information than before in the instance /header/. New user-manual material about this in "Kind inference in data type declarations" and "Kind inference for data/newtype instance declarations". * Minor improvement in kcTyClDecl, combining GADT and H98 case. Fixes #18891 - - - - - 21 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - docs/users_guide/exts/poly_kinds.rst - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/deriving/should_compile/T11416.hs - testsuite/tests/deriving/should_compile/T9359.hs - testsuite/tests/patsyn/should_fail/T15685.stderr - testsuite/tests/polykinds/T13659.stderr - testsuite/tests/polykinds/T16221a.stderr - testsuite/tests/th/T9692.hs - + testsuite/tests/typecheck/should_compile/T18891.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/T18891a.hs - + testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2981,7 +2981,7 @@ bindOuterSigTKBndrs_Tv_M :: TcTyMode -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) -- Do not push level; do not make implication constraint; use Tvs -- Two major clients of this "bind-only" path are: --- Note [Kind-checking for GADTs] in TyCl +-- Note [Using TyVarTvs for kind-checking GADTs] in TyCl -- Note [Checking partial type signatures] bindOuterSigTKBndrs_Tv_M mode = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = True @@ -3294,8 +3294,8 @@ When we /must/ clone. When kind-checking T, we give (a :: kappa1). Then: - In kcConDecl we make a TyVarTv unification variable kappa2 for k2 - (as described in Note [Kind-checking for GADTs], even though this - example is an existential) + (as described in Note [Using TyVarTvs for kind-checking GADTs], + even though this example is an existential) - So we get (b :: kappa2) via bindExplicitTKBndrs_Tv - We end up unifying kappa1 := kappa2, because of the (SameKind a b) ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -1529,27 +1529,16 @@ kcTyClDecl :: TyClDecl GhcRn -> TcTyCon -> TcM () -- result kind signature have already been dealt with -- by inferInitialKind, so we can ignore them here. -kcTyClDecl (DataDecl { tcdLName = (L _ name) - , tcdDataDefn = defn }) tyCon - | HsDataDefn { dd_cons = cons@((L _ (ConDeclGADT {})) : _) - , dd_ctxt = (L _ []) - , dd_ND = new_or_data } <- defn - = -- See Note [Implementation of UnliftedNewtypes] STEP 2 - kcConDecls new_or_data (tyConResKind tyCon) cons - - -- hs_tvs and dd_kindSig already dealt with in inferInitialKind - -- This must be a GADT-style decl, - -- (see invariants of DataDefn declaration) - -- so (a) we don't need to bring the hs_tvs into scope, because the - -- ConDecls bind all their own variables - -- (b) dd_ctxt is not allowed for GADT-style decls, so we can ignore it - - | HsDataDefn { dd_ctxt = ctxt - , dd_cons = cons - , dd_ND = new_or_data } <- defn +kcTyClDecl (DataDecl { tcdLName = (L _ name), tcdDataDefn = defn }) tycon + | HsDataDefn { dd_ctxt = ctxt, dd_cons = cons, dd_ND = new_or_data } <- defn = bindTyClTyVars name $ \ _ _ _ -> - do { _ <- tcHsContext ctxt - ; kcConDecls new_or_data (tyConResKind tyCon) cons + -- NB: binding these tyvars isn't necessary for GADTs, but it does no + -- harm. For GADTs, each data con brings its own tyvars into scope, + -- and the ones from this bindTyClTyVars are either not mentioned or + -- (conceivably) shadowed. + do { traceTc "kcTyClDecl" (ppr tycon $$ ppr (tyConTyVars tycon) $$ ppr (tyConResKind tycon)) + ; _ <- tcHsContext ctxt + ; kcConDecls new_or_data (tyConResKind tycon) cons } kcTyClDecl (SynDecl { tcdLName = L _ name, tcdRhs = rhs }) _tycon @@ -1606,13 +1595,12 @@ kcConGADTArgs new_or_data res_kind con_args = case con_args of kcConDecls :: NewOrData -> Kind -- The result kind signature + -- Used only in H98 case -> [LConDecl GhcRn] -- The data constructors -> TcM () -kcConDecls new_or_data res_kind cons - = mapM_ (wrapLocM_ (kcConDecl new_or_data final_res_kind)) cons - where - (_, final_res_kind) = splitPiTys res_kind - -- See Note [kcConDecls result kind] +-- See Note [kcConDecls: kind-checking data type decls] +kcConDecls new_or_data tc_res_kind cons + = mapM_ (wrapLocM_ (kcConDecl new_or_data tc_res_kind)) cons -- Kind check a data constructor. In additional to the data constructor, -- we also need to know about whether or not its corresponding type was @@ -1623,82 +1611,69 @@ kcConDecl :: NewOrData -> Kind -- Result kind of the type constructor -- Usually Type but can be TYPE UnliftedRep -- or even TYPE r, in the case of unlifted newtype + -- Used only in H98 case -> ConDecl GhcRn -> TcM () -kcConDecl new_or_data res_kind (ConDeclH98 +kcConDecl new_or_data tc_res_kind (ConDeclH98 { con_name = name, con_ex_tvs = ex_tvs , con_mb_cxt = ex_ctxt, con_args = args }) = addErrCtxt (dataConCtxtName [name]) $ discardResult $ bindExplicitTKBndrs_Tv ex_tvs $ do { _ <- tcHsMbContext ex_ctxt - ; kcConH98Args new_or_data res_kind args + ; kcConH98Args new_or_data tc_res_kind args -- We don't need to check the telescope here, -- because that's done in tcConDecl } -kcConDecl new_or_data res_kind (ConDeclGADT +kcConDecl new_or_data + _tc_res_kind -- Not used in GADT case (and doesn't make sense) + (ConDeclGADT { con_names = names, con_bndrs = L _ outer_bndrs, con_mb_cxt = cxt , con_g_args = args, con_res_ty = res_ty }) - = -- Even though the GADT-style data constructor's type is closed, - -- we must still kind-check the type, because that may influence - -- the inferred kind of the /type/ constructor. Example: - -- data T f a where - -- MkT :: f a -> T f a - -- If we don't look at MkT we won't get the correct kind - -- for the type constructor T + = -- See Note [kcConDecls: kind-checking data type decls] addErrCtxt (dataConCtxtName names) $ discardResult $ bindOuterSigTKBndrs_Tv outer_bndrs $ - -- Why "_Tv"? See Note [Kind-checking for GADTs] + -- Why "_Tv"? See Note [Using TyVarTvs for kind-checking GADTs] do { _ <- tcHsMbContext cxt - ; kcConGADTArgs new_or_data res_kind args - ; _ <- tcHsOpenType res_ty + ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty) + ; con_res_kind <- newOpenTypeKind + ; _ <- tcCheckLHsType res_ty (TheKind con_res_kind) + ; kcConGADTArgs new_or_data con_res_kind args + ; traceTc "kcConDecl:GADT }" (ppr names $$ ppr con_res_kind) ; return () } -{- Note [kcConDecls result kind] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We might have e.g. - data T a :: Type -> Type where ... -or - newtype instance N a :: Type -> Type where .. -in which case, the 'res_kind' passed to kcConDecls will be - Type->Type - -We must look past those arrows, or even foralls, to the Type in the -corner, to pass to kcConDecl c.f. #16828. Hence the splitPiTys here. - -I am a bit concerned about tycons with a declaration like - data T a :: Type -> forall k. k -> Type where ... - -It does not have a CUSK, so kcInferDeclHeader will make a TcTyCon -with tyConResKind of Type -> forall k. k -> Type. Even that is fine: -the splitPiTys will look past the forall. But I'm bothered about -what if the type "in the corner" mentions k? This is incredibly -obscure but something like this could be bad: - data T a :: Type -> foral k. k -> TYPE (F k) where ... - -I bet we are not quite right here, but my brain suffered a buffer -overflow and I thought it best to nail the common cases right now. - -Note [Recursion and promoting data constructors] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We don't want to allow promotion in a strongly connected component -when kind checking. - -Consider: - data T f = K (f (K Any)) - -When kind checking the `data T' declaration the local env contains the -mappings: - T -> ATcTyCon - K -> APromotionErr - -APromotionErr is only used for DataCons, and only used during type checking -in tcTyClGroup. - -Note [Kind-checking for GADTs] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [kcConDecls: kind-checking data type decls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +kcConDecls is used when we are inferring the kind of the type +constructor in a data type declaration. E.g. + data T f a = MkT (f a) +we want to infer the kind of 'f' and 'a'. The basic plan is described +in Note [Inferring kinds for type declarations]; here are doing Step 2. + +In the H98 case, for unlifted newtypes only, we need the result kind of +the TyCon, to unify with the argument kind. The tycon's result kind +is not used at all in the GADT case. + +In the GADT case we may have this: + data T f a where + MkT :: forall g b. g b -> T g b +Notice that the variables f,a, and g,b are quite distinct. +Nevertheless, this decl must still influence the kind T (which is, +remember Step 1, something like T :: kappa1 -> kappa2 -> Type), otherwise +we'd infer the bogus kind T :: forall k1 k2. k1 -> k2 -> Type. + +The data constructor type influences the kind of T simply by +kind-checking the result type (T g b), which will force 'f' and 'g' to +have the same kinds. This is the call to + tcCheckLHsType res_ty (TheKind con_res_kind) +Because this is the result type of an arrow, we know the kind must be +of form (TYPE rr), and we get better error messages if we enforce that +here (e.g. test gadt10). + +Note [Using TyVarTvs for kind-checking GADTs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider data Proxy a where @@ -1708,26 +1683,27 @@ Consider It seems reasonable that this should be accepted. But something very strange is going on here: when we're kind-checking this declaration, we need to unify the kind of `a` with k and j -- even though k and j's scopes are local to the type of -MkProxy{1,2}. The best approach we've come up with is to use TyVarTvs during -the kind-checking pass. First off, note that it's OK if the kind-checking pass -is too permissive: we'll snag the problems in the type-checking pass later. -(This extra permissiveness might happen with something like +MkProxy{1,2}. + +In effect, we are simply gathering constraints on the shape of Proxy's +kind, with no skolemisation or implication constraints involved at all. + +The best approach we've come up with is to use TyVarTvs during the +kind-checking pass, rather than ordinary skolems. This is why we use +the "_Tv" variant, bindOuterSigTKBndrs_Tv. + +Our only goal is to gather constraints on the kind of the type constructor; +we do not certify that the data declaration is well-kinded. For example: data SameKind :: k -> k -> Type data Bad a where MkBad :: forall k1 k2 (a :: k1) (b :: k2). Bad (SameKind a b) -which would be accepted if k1 and k2 were TyVarTvs. This is correctly rejected -in the second pass, though. Test case: polykinds/TyVarTvKinds3) -Recall that the kind-checking pass exists solely to collect constraints -on the kinds and to power unification. - -To achieve the use of TyVarTvs, we must be careful to use specialized functions -that produce TyVarTvs, not ordinary skolems. This is why we need -kcExplicitTKBndrs and kcImplicitTKBndrs in GHC.Tc.Gen.HsType, separate from their -tc... variants. +which would be accepted by kcConDecl because k1 and k2 are +TyVarTvs. It is correctly rejected in the second pass, tcConDecl. Test +case: polykinds/TyVarTvKinds3) -The drawback of this approach is sometimes it will accept a definition that +One drawback of this approach is sometimes it will accept a definition that a (hypothetical) declarative specification would likely reject. As a general rule, we don't want to allow polymorphic recursion without a CUSK. Indeed, the whole point of CUSKs is to allow polymorphic recursion. Yet, the TyVarTvs @@ -1746,6 +1722,23 @@ be rejected (without a CUSK). However, the accepted definitions are indeed well-kinded and any rejected definitions would be accepted with a CUSK, and so this wrinkle need not cause anyone to lose sleep. +Note [Recursion and promoting data constructors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We don't want to allow promotion in a strongly connected component +when kind checking. + +Consider: + data T f = K (f (K Any)) + +When kind checking the `data T' declaration the local env contains the +mappings: + T -> ATcTyCon + K -> APromotionErr + +APromotionErr is only used for DataCons, and only used during type checking +in tcTyClGroup. + + ************************************************************************ * * \subsection{Type checking} @@ -3214,7 +3207,7 @@ tcConDecl :: KnotTied TyCon -- Representation tycon. Knot-tied! -> ConDecl GhcRn -> TcM [DataCon] -tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs res_kind res_tmpl new_or_data (ConDeclH98 { con_name = lname@(L _ name) , con_ex_tvs = explicit_tkv_nms , con_mb_cxt = hs_ctxt @@ -3224,7 +3217,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Get hold of the existential type variables -- e.g. data T a = forall k (b::k) f. MkT a (f b) - -- Here tmpl_bndrs = {a} + -- Here tc_bndrs = {a} -- hs_qvars = HsQTvs { hsq_implicit = {k} -- , hsq_explicit = {f,b} } @@ -3242,29 +3235,35 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data } - ; let tmpl_tvs = binderVars tmpl_bndrs - ; let fake_ty = mkSpecForAllTys tmpl_tvs $ + ; let tc_tvs = binderVars tc_bndrs + fake_ty = mkSpecForAllTys tc_tvs $ mkInvisForAllTys exp_tvbndrs $ mkPhiTy ctxt $ mkVisFunTys arg_tys $ unitTy -- That type is a lie, of course. (It shouldn't end in ()!) -- And we could construct a proper result type from the info - -- at hand. But the result would mention only the tmpl_tvs, + -- at hand. But the result would mention only the univ_tvs, -- and so it just creates more work to do it right. Really, -- we're only doing this to find the right kind variables to -- quantify over, and this type is fine for that purpose. - -- exp_tvs have explicit, user-written binding sites + -- exp_tvbndrs have explicit, user-written binding sites -- the kvs below are those kind variables entirely unmentioned by the user -- and discovered only by generalization ; kvs <- kindGeneralizeAll fake_ty - ; let skol_tvs = kvs ++ tmpl_tvs + ; let skol_tvs = tc_tvs ++ kvs ++ binderVars exp_tvbndrs ; reportUnsolvedEqualities skol_info skol_tvs tclvl wanted - - -- Zonk to Types + -- The skol_info claims that all the variables are bound + -- by the data constructor decl, whereas actually the + -- univ_tvs are bound by the data type decl itself. It + -- would be better to have a doubly-nested implication. + -- But that just doesn't seem worth it. + -- See test dependent/should_fail/T13780a + + -- Zonk to Types ; (ze, qkvs) <- zonkTyBndrs kvs ; (ze, user_qtvbndrs) <- zonkTyVarBindersX ze exp_tvbndrs ; arg_tys <- zonkScaledTcTypesToTypesX ze arg_tys @@ -3272,15 +3271,13 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Can't print univ_tvs, arg_tys etc, because we are inside the knot here ; traceTc "tcConDecl 2" (ppr name $$ ppr field_lbls) - ; let - univ_tvbs = tyConInvisTVBinders tmpl_bndrs - univ_tvs = binderVars univ_tvbs - ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs - ex_tvs = binderVars ex_tvbs - -- For H98 datatypes, the user-written tyvar binders are precisely - -- the universals followed by the existentials. - -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. - user_tvbs = univ_tvbs ++ ex_tvbs + ; let univ_tvbs = tyConInvisTVBinders tc_bndrs + ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs + ex_tvs = binderVars ex_tvbs + -- For H98 datatypes, the user-written tyvar binders are precisely + -- the universals followed by the existentials. + -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. + user_tvbs = univ_tvbs ++ ex_tvbs ; traceTc "tcConDecl 2" (ppr name) ; is_infix <- tcConIsInfixH98 name hs_args @@ -3288,7 +3285,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data ; fam_envs <- tcGetFamInstEnvs ; dc <- buildDataCon fam_envs name is_infix rep_nm stricts Nothing field_lbls - univ_tvs ex_tvs user_tvbs + tc_tvs ex_tvs user_tvbs [{- no eq_preds -}] ctxt arg_tys res_tmpl rep_tycon tag_map -- NB: we put data_tc, the type constructor gotten from the @@ -3299,7 +3296,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data where skol_info = DataConSkol name -tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs _res_kind res_tmpl new_or_data -- NB: don't use res_kind here, as it's ill-scoped. Instead, -- we get the res_kind by typechecking the result type. (ConDeclGADT { con_names = names @@ -3344,7 +3341,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data ; res_ty <- zonkTcTypeToTypeX ze res_ty ; let (univ_tvs, ex_tvs, tvbndrs', eq_preds, arg_subst) - = rejigConRes tmpl_bndrs res_tmpl tvbndrs res_ty + = rejigConRes tc_bndrs res_tmpl tvbndrs res_ty -- See Note [Checking GADT return types] ctxt' = substTys arg_subst ctxt @@ -3532,9 +3529,9 @@ errors reported in one pass. See #7175, and #10836. -- TI :: forall b1 c1. (b1 ~ c1) => b1 -> :R7T b1 c1 -- In this case orig_res_ty = T (e,e) -rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result type; e.g. - -- data instance T [a] b c ... - -- gives template ([a,b,c], T [a] b c) +rejigConRes :: [KnotTied TyConBinder] -- Template for result type; e.g. + -> KnotTied Type -- data instance T [a] b c ... + -- gives template ([a,b,c], T [a] b c) -> [InvisTVBinder] -- The constructor's type variables (both inferred and user-written) -> KnotTied Type -- res_ty -> ([TyVar], -- Universal @@ -3546,10 +3543,10 @@ rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result -- We don't check that the TyCon given in the ResTy is -- the same as the parent tycon, because checkValidDataCon will do it -- NB: All arguments may potentially be knot-tied -rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty +rejigConRes tc_tvbndrs res_tmpl dc_tvbndrs res_ty -- E.g. data T [a] b c where -- MkT :: forall x y z. T [(x,y)] z z - -- The {a,b,c} are the tmpl_tvs, and the {x,y,z} are the dc_tvs + -- The {a,b,c} are the tc_tvs, and the {x,y,z} are the dc_tvs -- (NB: unlike the H98 case, the dc_tvs are not all existential) -- Then we generate -- Univ tyvars Eq-spec @@ -3564,7 +3561,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- , [], [x,y,z] -- , [a~(x,y),b~z], ) | Just subst <- tcMatchTy res_tmpl res_ty - = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tmpl_tvs dc_tvs subst + = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tc_tvs dc_tvs subst raw_ex_tvs = dc_tvs `minusList` univ_tvs (arg_subst, substed_ex_tvs) = substTyVarBndrs kind_subst raw_ex_tvs @@ -3591,10 +3588,10 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- albeit bogus, relying on checkValidDataCon to check the -- bad-result-type error before seeing that the other fields look odd -- See Note [Checking GADT return types] - = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, dc_tvbndrs, [], emptyTCvSubst) + = (tc_tvs, dc_tvs `minusList` tc_tvs, dc_tvbndrs, [], emptyTCvSubst) where - dc_tvs = binderVars dc_tvbndrs - tmpl_tvs = binderVars tmpl_bndrs + dc_tvs = binderVars dc_tvbndrs + tc_tvs = binderVars tc_tvbndrs {- Note [mkGADTVars] ~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -688,9 +688,8 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env -- Do /not/ check that the number of patterns = tyConArity fam_tc -- See [Arity of data families] in GHC.Core.FamInstEnv ; (qtvs, pats, res_kind, stupid_theta) - <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs - fixity hs_ctxt hs_pats m_ksig hs_cons - new_or_data + <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity + hs_ctxt hs_pats m_ksig new_or_data -- Eta-reduce the axiom if possible -- Quite tricky: see Note [Implementing eta reduction for data families] @@ -857,7 +856,7 @@ TyVarEnv will simply be empty, and there is nothing to worry about. tcDataFamInstHeader :: AssocInstInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn -> LexicalFixity -> LHsContext GhcRn - -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> [LConDecl GhcRn] + -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> NewOrData -> TcM ([TyVar], [Type], Kind, ThetaType) -- The "header" of a data family instance is the part other than @@ -865,7 +864,7 @@ tcDataFamInstHeader -- e.g. data instance D [a] :: * -> * where ... -- Here the "header" is the bit before the "where" tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity - hs_ctxt hs_pats m_ksig hs_cons new_or_data + hs_ctxt hs_pats m_ksig new_or_data = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (scoped_tvs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ @@ -884,8 +883,8 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity -- Add constraints from the result signature ; res_kind <- tc_kind_sig m_ksig - -- Add constraints from the data constructors - ; kcConDecls new_or_data res_kind hs_cons + -- Do not add constraints from the data constructors + -- See Note [Kind inference for data family instances] -- Check that the result kind of the TyCon applied to its args -- is compatible with the explicit signature (or Type, if there @@ -1049,6 +1048,81 @@ however, so this Note aims to describe these subtleties: themselves. Heavy sigh. But not truly hard; that's what tcbVisibilities does. +Note [Kind inference for data family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this GADT-style data type declaration, where I have used +fresh variables in the data constructor's type, to stress that c,d are +quite distinct from a,b. + data T a b where + MkT :: forall c d. c d -> T c d + +Following Note [Inferring kinds for type declarations] in GHC.Tc.TyCl, +to infer T's kind, we initially give T :: kappa, a monomorpic kind, +gather constraints from the header and data constructors, and conclude + T :: (kappa1 -> type) -> kappa1 -> Type +Then we generalise, giving + T :: forall k. (k->Type) -> k -> Type + +Now what about a data /instance/ decl + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p Int where ... + +No doubt here! The poly-kinded T is instantiated with k=Type, so the +header really looks like + data instance T @Type (p :: Type->Type) Int where ... + +But what about this? + data instance T p q where + MkT :: forall r. r Int -> T r Int + +So what kind do 'p' and 'q' have? No clues from the header, but from +the data constructor we can clearly see that (r :: Type->Type). Does +that mean that the the /entire data instance/ is instantiated at Type, +like this? + data instance T @Type (p :: Type->Type) (q :: Type) where + ... + +Not at all! This is a /GADT/-style decl, so the kind argument might +be specialised in this particular data constructor, thus: + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall (r :: Type -> Type). + r Int -> T @Type r Int +(and perhaps specialised differently in some other data +constructor MkT2). + +The key difference in this case and 'data T' at the top of this Note +is that we have no known kind for 'data T'. We thus forbid different +specialisations of T in its constructors, in an attempt to avoid +inferring polymorphic recursion. In data family T, however, there is +no problem with polymorphic recursion: we already /fully know/ T's +kind -- that came from the family declaration, and is not influenced +by the data instances -- and hence we /can/ specialise T's kind +differently in different GADT data constructors. + +SHORT SUMMARY: in a data instance decl, it's not clear whether kind +constraints arising from the data constructors should be considered +local to the (GADT) data /constructor/ or should apply to the entire +data instance. + +DESIGN CHOICE: in data/newtype family instance declarations, we ignore +the /data constructor/ declarations altogether, looking only at the +data instance /header/. + +Observations: +* This choice is simple to describe, as well as simple to implment. + For a data/newtype instance decl, the instance kinds are influenced + /only/ by the header. + +* We could treat Haskell-98 style data-instance decls differently, by + taking the data constructors into account, since there are no GADT + issues. + +* Ditto newtypes, since again you can't have newtype GADTs. + +But for now at least, we keep the simplest choice. See #18891 and !4419 +for more discussion of this issue.a + -} ===================================== docs/users_guide/exts/poly_kinds.rst ===================================== @@ -130,8 +130,45 @@ This rule has occasionally-surprising consequences (see The kind-polymorphism from the class declaration makes ``D1`` kind-polymorphic, but not so ``D2``; and similarly ``F1``, ``F2``. +Kind inference in type signatures +--------------------------------- + +When kind-checking a type, GHC considers only what is written in that +type when figuring out how to generalise the type's kind. + +For example, +consider these definitions (with :extension:`ScopedTypeVariables`): :: + + data Proxy a -- Proxy :: forall k. k -> Type + p :: forall a. Proxy a + p = Proxy :: Proxy (a :: Type) + +GHC reports an error, saying that the kind of ``a`` should be a kind variable +``k``, not ``Type``. This is because, by looking at the type signature +``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not +restricted to be ``Type``. The function definition is then rejected for being +more specific than its type signature. + +.. _explicit-kind-quantification: + +Explicit kind quantification +---------------------------- + +Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, +as in these examples: :: + + data Proxy :: forall k. k -> Type + f :: (forall k (a :: k). Proxy a -> ()) -> Int + +Note that the second example has a ``forall`` that binds both a kind ``k`` and +a type variable ``a`` of kind ``k``. In general, there is no limit to how +deeply nested this sort of dependency can work. However, the dependency must +be well-scoped: ``forall (a :: k) k. ...`` is an error. + + .. _inferring-variable-order: + Inferring the order of variables in a type/class declaration ------------------------------------------------------------ @@ -490,41 +527,74 @@ This also applies to GADT-style data instances: :: -- • In the data instance declaration for ‘T’ -Kind inference in closed type families --------------------------------------- +Kind inference in data type declarations +---------------------------------------- -Although all open type families are considered to have a complete -user-supplied kind signature, we can relax this condition for closed -type families, where we have equations on which to perform kind -inference. GHC will infer kinds for the arguments and result types of a -closed type family. +Consider the declaration :: -GHC supports *kind-indexed* type families, where the family matches both -on the kind and type. GHC will *not* infer this behaviour without a -complete user-supplied kind signature, as doing so would sometimes infer -non-principal types. Indeed, we can see kind-indexing as a form -of polymorphic recursion, where a type is used at a kind other than -its most general in its own definition. + data T1 f a = MkT1 (f a) + data T2 f a where + MkT2 :: f a -> T f a -For example: :: +In both cases GHC looks at the data constructor declarations to +give constraints on the kind of ``T``, yielding :: - type family F1 a where - F1 True = False - F1 False = True - F1 x = x - -- F1 fails to compile: kind-indexing is not inferred + T1, T2 :: forall k. (k -> Type) -> k -> Typ - type family F2 (a :: k) where - F2 True = False - F2 False = True - F2 x = x - -- F2 fails to compile: no complete signature +Consider the type :: + + data G (a :: k) where + GInt :: G Int + GMaybe :: G Maybe + +This datatype ``G`` is GADT-like in both its kind and its type. Suppose you +have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that +``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and +``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` +be in effect, but pattern-matching on ``G`` requires no extension beyond +:extension:`GADTs`. That this works is actually a straightforward extension +of regular GADTs and a consequence of the fact that kinds and types are the +same. + +Note that the datatype ``G`` is used at different kinds in its body, and +therefore that kind-indexed GADTs use a form of polymorphic recursion. +It is thus only possible to use this feature if you have provided a +complete user-supplied kind signature +for the datatype (:ref:`complete-kind-signatures`), or a standalone +kind signature (:ref:`standalone-kind-signatures`); +in the case of ``G`` we have a CUSK. +A more explicit declaration that fills in the invisible kind arguments would be :: + + data G @k (a :: k) where + GInt :: G @Type Int + GMaybe :: G @(Type->Type) Maybe + +where you can see the GADT-like nature of the two constructors. + +Kind inference for data/newtype instance declarations +----------------------------------------------------- + +Consider these declarations :: + + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p q where + MkT :: forall r. r Int -> T r Int + +Here ``T`` has an invisible kind argument; and perhaps it is instantiated +to ``(Type->Type)`` in the instance, thus :: + + data instance T @(Type->Type) p q where + MkT :: forall r. r Int -> T r Int + +This latter form is accepted, but the former is not: in data/newtype +instance declararations (unlike ordinary data/newtype declarations) +we do *not* look at the constructor declarations. The principle is +that *the instantiation of the data instance should be apparent from the header alone*. +This principle makes the program easier to understand; but it also +avoids a swamp of complexity about which type specialisation comes from the +data instance, and which from the individual GADT data constructors. - type family F3 (a :: k) :: k where - F3 True = False - F3 False = True - F3 x = x - -- OK Kind inference in class instance declarations --------------------------------------------- @@ -555,43 +625,8 @@ infrastructure, and it's not clear the payoff is worth it. If you want to restrict ``b``\ 's kind in the instance above, just use a kind signature in the instance head. -Kind inference in type signatures ---------------------------------- - -When kind-checking a type, GHC considers only what is written in that -type when figuring out how to generalise the type's kind. - -For example, -consider these definitions (with :extension:`ScopedTypeVariables`): :: - - data Proxy a -- Proxy :: forall k. k -> Type - p :: forall a. Proxy a - p = Proxy :: Proxy (a :: Type) - -GHC reports an error, saying that the kind of ``a`` should be a kind variable -``k``, not ``Type``. This is because, by looking at the type signature -``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not -restricted to be ``Type``. The function definition is then rejected for being -more specific than its type signature. - -.. _explicit-kind-quantification: - -Explicit kind quantification ----------------------------- - -Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, -as in these examples: :: - - data Proxy :: forall k. k -> Type - f :: (forall k (a :: k). Proxy a -> ()) -> Int - -Note that the second example has a ``forall`` that binds both a kind ``k`` and -a type variable ``a`` of kind ``k``. In general, there is no limit to how -deeply nested this sort of dependency can work. However, the dependency must -be well-scoped: ``forall (a :: k) k. ...`` is an error. - -Implicit quantification in type synonyms and type family instances ------------------------------------------------------------------- +Kind inference in type synonyms and type family instances +--------------------------------------------------------- Consider the scoping rules for type synonyms and type family instances, such as these:: @@ -706,29 +741,41 @@ kinds. Consequently, visible dependent quantifiers are rejected in any context that is unambiguously the type of a term. They are also rejected in the types of data constructors. -Kind-indexed GADTs ------------------- +Kind inference in closed type families +-------------------------------------- -Consider the type :: +Although all open type families are considered to have a complete +user-supplied kind signature, we can relax this condition for closed +type families, where we have equations on which to perform kind +inference. GHC will infer kinds for the arguments and result types of a +closed type family. - data G (a :: k) where - GInt :: G Int - GMaybe :: G Maybe +GHC supports *kind-indexed* type families, where the family matches both +on the kind and type. GHC will *not* infer this behaviour without a +complete user-supplied kind signature, as doing so would sometimes infer +non-principal types. Indeed, we can see kind-indexing as a form +of polymorphic recursion, where a type is used at a kind other than +its most general in its own definition. -This datatype ``G`` is GADT-like in both its kind and its type. Suppose you -have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that -``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and -``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` -be in effect, but pattern-matching on ``G`` requires no extension beyond -:extension:`GADTs`. That this works is actually a straightforward extension -of regular GADTs and a consequence of the fact that kinds and types are the -same. +For example: :: -Note that the datatype ``G`` is used at different kinds in its body, and -therefore that kind-indexed GADTs use a form of polymorphic recursion. -It is thus only possible to use this feature if you have provided a -complete user-supplied kind signature -for the datatype (:ref:`complete-kind-signatures`). + type family F1 a where + F1 True = False + F1 False = True + F1 x = x + -- F1 fails to compile: kind-indexing is not inferred + + type family F2 (a :: k) where + F2 True = False + F2 False = True + F2 x = x + -- F2 fails to compile: no complete signature + + type family F3 (a :: k) :: k where + F3 True = False + F3 False = True + F3 x = x + -- OK Higher-rank kinds ----------------- ===================================== testsuite/tests/dependent/should_fail/T13780a.stderr ===================================== @@ -3,7 +3,7 @@ T13780a.hs:9:40: error: • Couldn't match kind ‘a’ with ‘Bool’ Expected kind ‘Foo a’, but ‘MkFoo’ has kind ‘Foo Bool’ ‘a’ is a rigid type variable bound by - a family instance declaration + the data constructor ‘SMkFoo’ at T13780a.hs:9:20-31 • In the second argument of ‘(~)’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ ===================================== testsuite/tests/deriving/should_compile/T11416.hs ===================================== @@ -12,9 +12,11 @@ newtype T f (a :: ConstantT Type f) = T (f a) deriving Functor data family TFam1 (f :: k1) (a :: k2) -newtype instance TFam1 f (ConstantT a f) = TFam1 (f a) +newtype instance TFam1 (f :: k -> Type) (ConstantT (a :: k) f) + = TFam1 (f a) deriving Functor data family TFam2 (f :: k1) (a :: k2) -newtype instance TFam2 f (a :: ConstantT Type f) = TFam2 (f a) +newtype instance TFam2 (f :: Type -> Type) (a :: ConstantT Type f) + = TFam2 (f a) deriving Functor ===================================== testsuite/tests/deriving/should_compile/T9359.hs ===================================== @@ -5,10 +5,12 @@ import Data.Kind (Type) data Cmp a where Sup :: Cmp a - V :: a -> Cmp a - deriving (Show, Eq) +-- V :: a -> Cmp a +-- deriving (Show, Eq) +{- data family CmpInterval (a :: Cmp k) (b :: Cmp k) :: Type data instance CmpInterval (V c) Sup = Starting c deriving( Show ) +-} \ No newline at end of file ===================================== testsuite/tests/patsyn/should_fail/T15685.stderr ===================================== @@ -1,13 +1,13 @@ T15685.hs:13:24: error: - • Could not deduce: a ~ [k0] - from the context: as ~ (a1 : as1) + • Could not deduce: k ~ [k0] + from the context: as ~ (a : as1) bound by a pattern with constructor: - Here :: forall {a1} (f :: a1 -> *) (a2 :: a1) (as :: [a1]). - f a2 -> NS f (a2 : as), + Here :: forall {k} (f :: k -> *) (a :: k) (as :: [k]). + f a -> NS f (a : as), in a pattern synonym declaration at T15685.hs:13:19-26 - ‘a’ is a rigid type variable bound by + ‘k’ is a rigid type variable bound by the inferred type of HereNil :: NS f as at T15685.hs:13:9-15 Possible fix: add a type signature for ‘HereNil’ ===================================== testsuite/tests/polykinds/T13659.stderr ===================================== @@ -1,6 +1,6 @@ -T13659.hs:14:27: error: - • Expected a type, but ‘a’ has kind ‘[*]’ - • In the first argument of ‘Format’, namely ‘'[Int, a]’ - In the type ‘Format '[Int, a]’ +T13659.hs:14:15: error: + • Expected kind ‘[*]’, but ‘a’ has kind ‘*’ + • In the first argument of ‘Format’, namely ‘a’ + In the type ‘Format a’ In the definition of data constructor ‘I’ ===================================== testsuite/tests/polykinds/T16221a.stderr ===================================== @@ -1,7 +1,7 @@ T16221a.hs:6:49: error: - • Expected kind ‘k’, but ‘b’ has kind ‘k1’ - ‘k1’ is a rigid type variable bound by + • Expected kind ‘k’, but ‘b’ has kind ‘k2’ + ‘k2’ is a rigid type variable bound by an explicit forall k (b :: k) at T16221a.hs:6:20 ‘k’ is a rigid type variable bound by ===================================== testsuite/tests/th/T9692.hs ===================================== @@ -12,7 +12,7 @@ class C a where data F a (b :: k) :: Type instance C Int where - data F Int x = FInt x + data F Int (x :: Type) = FInt x $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info ===================================== testsuite/tests/typecheck/should_compile/T18891.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +data family T2 (a :: k) +data instance T2 a where + MkT2 :: T2 Maybe + +newtype N3 :: forall k -> TYPE k where + MkN3 :: N3 m -> N3 m + +type N4 :: forall k -> TYPE k +newtype N4 :: forall k -> TYPE k where + MkN4 :: N4 m -> N4 m ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs ===================================== @@ -4,6 +4,8 @@ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} module UnliftedNewtypesUnassociatedFamily where @@ -20,7 +22,16 @@ newtype instance DFT ('TupleRep '[ 'IntRep, 'WordRep]) data instance DFT 'LiftedRep = MkDFT4 | MkDFT5 data family DF :: TYPE (r :: RuntimeRep) -newtype instance DF = MkDF1 Int# -newtype instance DF = MkDF2 Word# -newtype instance DF = MkDF3 (# Int#, Word# #) + +-- Use a type application +newtype instance DF @IntRep = MkDF1 Int# + +-- Use a kind signature +newtype instance DF :: TYPE 'WordRep where + MkDF2 :: Word# -> DF + +-- Also uses a kind signature +newtype instance DF :: TYPE ('TupleRep '[ 'IntRep, 'WordRep ]) where + MkDF3 :: (# Int#, Word# #) -> DF + data instance DF = MkDF4 | MkDF5 ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs ===================================== @@ -10,14 +10,14 @@ module UnliftedNewtypesUnassociatedFamily where import GHC.Int (Int(I#)) -import GHC.Exts (Int#,Word#,RuntimeRep(IntRep)) +import GHC.Exts (Int#,Word#,RuntimeRep(IntRep, WordRep)) import GHC.Exts (TYPE) type KindOf (a :: TYPE k) = k data family D (a :: TYPE r) :: TYPE r -newtype instance D a = MkWordD Word# +newtype instance D (a :: TYPE 'WordRep) = MkWordD Word# -newtype instance D a :: TYPE (KindOf a) where - MkIntD :: forall (a :: TYPE 'IntRep). Int# -> D a +newtype instance D (a :: TYPE 'IntRep) :: TYPE (KindOf a) where + MkIntD :: forall (b :: TYPE 'IntRep). Int# -> D b ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,5 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) +test('T18891', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T18891a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +newtype N1 :: forall k. TYPE k where + MkN1 :: N1 -> N1 + +type N2 :: forall k. TYPE k +newtype N2 :: forall k. TYPE k where + MkN2 :: N2 -> N2 + ===================================== testsuite/tests/typecheck/should_fail/T18891a.stderr ===================================== @@ -0,0 +1,12 @@ + +T18891a.hs:8:4: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN1 :: N1 -> N1 + • In the definition of data constructor ‘MkN1’ + In the newtype declaration for ‘N1’ + +T18891a.hs:12:3: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN2 :: N2 -> N2 + • In the definition of data constructor ‘MkN2’ + In the newtype declaration for ‘N2’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr ===================================== @@ -1,11 +1,5 @@ -UnliftedNewtypesFamilyKindFail2.hs:12:20: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the newtype instance declaration for ‘F’ - -UnliftedNewtypesFamilyKindFail2.hs:12:31: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the type ‘(F 5)’ - In the definition of data constructor ‘MkF’ +UnliftedNewtypesFamilyKindFail2.hs:12:20: error: + • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ + • In the first argument of ‘F’, namely ‘5’ + In the newtype instance declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} + +module UnliftedNewtypesUnassociatedFamily where + +import GHC.Int (Int(I#)) +import GHC.Word (Word(W#)) +import GHC.Exts (Int#,Word#) +import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep)) + +data family DF :: TYPE (r :: RuntimeRep) + +-- All these fail: see #18891 and !4419 +-- See Note [Kind inference for data family instances] +-- in GHC.Tc.TyCl.Instance +newtype instance DF = MkDF1a Int# +newtype instance DF = MkDF2a Word# +newtype instance DF = MkDF3a (# Int#, Word# #) ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr ===================================== @@ -0,0 +1,18 @@ + +UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error: + • Expecting a lifted type, but ‘Int#’ is unlifted + • In the type ‘Int#’ + In the definition of data constructor ‘MkDF1a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error: + • Expecting a lifted type, but ‘Word#’ is unlifted + • In the type ‘Word#’ + In the definition of data constructor ‘MkDF2a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error: + • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted + • In the type ‘(# Int#, Word# #)’ + In the definition of data constructor ‘MkDF3a’ + In the newtype instance declaration for ‘DF’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKind', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, ['']) test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, ['']) +test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, ['']) test('T13834', normal, compile_fail, ['']) test('T17077', normal, compile_fail, ['']) test('T16512a', normal, compile_fail, ['']) @@ -589,3 +590,4 @@ test('T18640b', normal, compile_fail, ['']) test('T18640c', normal, compile_fail, ['']) test('T10709', normal, compile_fail, ['']) test('T10709b', normal, compile_fail, ['']) +test('T18891a', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f6cd8b076e4703436a3b31e4eac4a87c7cb8e7f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f6cd8b076e4703436a3b31e4eac4a87c7cb8e7f 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 Wed Nov 25 14:13:47 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Wed, 25 Nov 2020 09:13:47 -0500 Subject: [Git][ghc/ghc][wip/T18891] Fix kind inference for data types. Again. Message-ID: <5fbe669b2cb81_86c7d592401735a6@gitlab.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: 2f32a597 by Simon Peyton Jones at 2020-11-25T14:12:51+00:00 Fix kind inference for data types. Again. This patch improves kcConDecls, when we are inferring the kind of a data type decl. Specifically * In kcConDecls/kcConDecl make it clear that the tc_res_kind argument is only used in the H98 case; and in that case there is not result kind signature; and hence no need for the disgusting splitPiTys in kcConDecls (now thankfully gone). The GADT case is a bit different to before, and much nicer. This is what fixes #18891. See Note [kcConDecls: kind-checking data type decls] * Do not look at the constructor decls of a data/newtype instance in tcDataFamInstanceHeader. See new Note [Kind inference for data family instances] This causes a few knock-on effects in the tests suite, because we require more information than before in the instance /header/. New user-manual material about this in "Kind inference in data type declarations" and "Kind inference for data/newtype instance declarations". * Minor improvement in kcTyClDecl, combining GADT and H98 case. Fixes #18891 - - - - - 20 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - docs/users_guide/exts/poly_kinds.rst - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/deriving/should_compile/T11416.hs - testsuite/tests/patsyn/should_fail/T15685.stderr - testsuite/tests/polykinds/T13659.stderr - testsuite/tests/polykinds/T16221a.stderr - testsuite/tests/th/T9692.hs - + testsuite/tests/typecheck/should_compile/T18891.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/T18891a.hs - + testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2981,7 +2981,7 @@ bindOuterSigTKBndrs_Tv_M :: TcTyMode -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) -- Do not push level; do not make implication constraint; use Tvs -- Two major clients of this "bind-only" path are: --- Note [Kind-checking for GADTs] in TyCl +-- Note [Using TyVarTvs for kind-checking GADTs] in TyCl -- Note [Checking partial type signatures] bindOuterSigTKBndrs_Tv_M mode = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = True @@ -3294,8 +3294,8 @@ When we /must/ clone. When kind-checking T, we give (a :: kappa1). Then: - In kcConDecl we make a TyVarTv unification variable kappa2 for k2 - (as described in Note [Kind-checking for GADTs], even though this - example is an existential) + (as described in Note [Using TyVarTvs for kind-checking GADTs], + even though this example is an existential) - So we get (b :: kappa2) via bindExplicitTKBndrs_Tv - We end up unifying kappa1 := kappa2, because of the (SameKind a b) ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -1529,27 +1529,16 @@ kcTyClDecl :: TyClDecl GhcRn -> TcTyCon -> TcM () -- result kind signature have already been dealt with -- by inferInitialKind, so we can ignore them here. -kcTyClDecl (DataDecl { tcdLName = (L _ name) - , tcdDataDefn = defn }) tyCon - | HsDataDefn { dd_cons = cons@((L _ (ConDeclGADT {})) : _) - , dd_ctxt = (L _ []) - , dd_ND = new_or_data } <- defn - = -- See Note [Implementation of UnliftedNewtypes] STEP 2 - kcConDecls new_or_data (tyConResKind tyCon) cons - - -- hs_tvs and dd_kindSig already dealt with in inferInitialKind - -- This must be a GADT-style decl, - -- (see invariants of DataDefn declaration) - -- so (a) we don't need to bring the hs_tvs into scope, because the - -- ConDecls bind all their own variables - -- (b) dd_ctxt is not allowed for GADT-style decls, so we can ignore it - - | HsDataDefn { dd_ctxt = ctxt - , dd_cons = cons - , dd_ND = new_or_data } <- defn +kcTyClDecl (DataDecl { tcdLName = (L _ name), tcdDataDefn = defn }) tycon + | HsDataDefn { dd_ctxt = ctxt, dd_cons = cons, dd_ND = new_or_data } <- defn = bindTyClTyVars name $ \ _ _ _ -> - do { _ <- tcHsContext ctxt - ; kcConDecls new_or_data (tyConResKind tyCon) cons + -- NB: binding these tyvars isn't necessary for GADTs, but it does no + -- harm. For GADTs, each data con brings its own tyvars into scope, + -- and the ones from this bindTyClTyVars are either not mentioned or + -- (conceivably) shadowed. + do { traceTc "kcTyClDecl" (ppr tycon $$ ppr (tyConTyVars tycon) $$ ppr (tyConResKind tycon)) + ; _ <- tcHsContext ctxt + ; kcConDecls new_or_data (tyConResKind tycon) cons } kcTyClDecl (SynDecl { tcdLName = L _ name, tcdRhs = rhs }) _tycon @@ -1606,13 +1595,12 @@ kcConGADTArgs new_or_data res_kind con_args = case con_args of kcConDecls :: NewOrData -> Kind -- The result kind signature + -- Used only in H98 case -> [LConDecl GhcRn] -- The data constructors -> TcM () -kcConDecls new_or_data res_kind cons - = mapM_ (wrapLocM_ (kcConDecl new_or_data final_res_kind)) cons - where - (_, final_res_kind) = splitPiTys res_kind - -- See Note [kcConDecls result kind] +-- See Note [kcConDecls: kind-checking data type decls] +kcConDecls new_or_data tc_res_kind cons + = mapM_ (wrapLocM_ (kcConDecl new_or_data tc_res_kind)) cons -- Kind check a data constructor. In additional to the data constructor, -- we also need to know about whether or not its corresponding type was @@ -1623,82 +1611,69 @@ kcConDecl :: NewOrData -> Kind -- Result kind of the type constructor -- Usually Type but can be TYPE UnliftedRep -- or even TYPE r, in the case of unlifted newtype + -- Used only in H98 case -> ConDecl GhcRn -> TcM () -kcConDecl new_or_data res_kind (ConDeclH98 +kcConDecl new_or_data tc_res_kind (ConDeclH98 { con_name = name, con_ex_tvs = ex_tvs , con_mb_cxt = ex_ctxt, con_args = args }) = addErrCtxt (dataConCtxtName [name]) $ discardResult $ bindExplicitTKBndrs_Tv ex_tvs $ do { _ <- tcHsMbContext ex_ctxt - ; kcConH98Args new_or_data res_kind args + ; kcConH98Args new_or_data tc_res_kind args -- We don't need to check the telescope here, -- because that's done in tcConDecl } -kcConDecl new_or_data res_kind (ConDeclGADT +kcConDecl new_or_data + _tc_res_kind -- Not used in GADT case (and doesn't make sense) + (ConDeclGADT { con_names = names, con_bndrs = L _ outer_bndrs, con_mb_cxt = cxt , con_g_args = args, con_res_ty = res_ty }) - = -- Even though the GADT-style data constructor's type is closed, - -- we must still kind-check the type, because that may influence - -- the inferred kind of the /type/ constructor. Example: - -- data T f a where - -- MkT :: f a -> T f a - -- If we don't look at MkT we won't get the correct kind - -- for the type constructor T + = -- See Note [kcConDecls: kind-checking data type decls] addErrCtxt (dataConCtxtName names) $ discardResult $ bindOuterSigTKBndrs_Tv outer_bndrs $ - -- Why "_Tv"? See Note [Kind-checking for GADTs] + -- Why "_Tv"? See Note [Using TyVarTvs for kind-checking GADTs] do { _ <- tcHsMbContext cxt - ; kcConGADTArgs new_or_data res_kind args - ; _ <- tcHsOpenType res_ty + ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty) + ; con_res_kind <- newOpenTypeKind + ; _ <- tcCheckLHsType res_ty (TheKind con_res_kind) + ; kcConGADTArgs new_or_data con_res_kind args + ; traceTc "kcConDecl:GADT }" (ppr names $$ ppr con_res_kind) ; return () } -{- Note [kcConDecls result kind] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We might have e.g. - data T a :: Type -> Type where ... -or - newtype instance N a :: Type -> Type where .. -in which case, the 'res_kind' passed to kcConDecls will be - Type->Type - -We must look past those arrows, or even foralls, to the Type in the -corner, to pass to kcConDecl c.f. #16828. Hence the splitPiTys here. - -I am a bit concerned about tycons with a declaration like - data T a :: Type -> forall k. k -> Type where ... - -It does not have a CUSK, so kcInferDeclHeader will make a TcTyCon -with tyConResKind of Type -> forall k. k -> Type. Even that is fine: -the splitPiTys will look past the forall. But I'm bothered about -what if the type "in the corner" mentions k? This is incredibly -obscure but something like this could be bad: - data T a :: Type -> foral k. k -> TYPE (F k) where ... - -I bet we are not quite right here, but my brain suffered a buffer -overflow and I thought it best to nail the common cases right now. - -Note [Recursion and promoting data constructors] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We don't want to allow promotion in a strongly connected component -when kind checking. - -Consider: - data T f = K (f (K Any)) - -When kind checking the `data T' declaration the local env contains the -mappings: - T -> ATcTyCon - K -> APromotionErr - -APromotionErr is only used for DataCons, and only used during type checking -in tcTyClGroup. - -Note [Kind-checking for GADTs] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [kcConDecls: kind-checking data type decls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +kcConDecls is used when we are inferring the kind of the type +constructor in a data type declaration. E.g. + data T f a = MkT (f a) +we want to infer the kind of 'f' and 'a'. The basic plan is described +in Note [Inferring kinds for type declarations]; here are doing Step 2. + +In the H98 case, for unlifted newtypes only, we need the result kind of +the TyCon, to unify with the argument kind. The tycon's result kind +is not used at all in the GADT case. + +In the GADT case we may have this: + data T f a where + MkT :: forall g b. g b -> T g b +Notice that the variables f,a, and g,b are quite distinct. +Nevertheless, this decl must still influence the kind T (which is, +remember Step 1, something like T :: kappa1 -> kappa2 -> Type), otherwise +we'd infer the bogus kind T :: forall k1 k2. k1 -> k2 -> Type. + +The data constructor type influences the kind of T simply by +kind-checking the result type (T g b), which will force 'f' and 'g' to +have the same kinds. This is the call to + tcCheckLHsType res_ty (TheKind con_res_kind) +Because this is the result type of an arrow, we know the kind must be +of form (TYPE rr), and we get better error messages if we enforce that +here (e.g. test gadt10). + +Note [Using TyVarTvs for kind-checking GADTs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider data Proxy a where @@ -1708,26 +1683,27 @@ Consider It seems reasonable that this should be accepted. But something very strange is going on here: when we're kind-checking this declaration, we need to unify the kind of `a` with k and j -- even though k and j's scopes are local to the type of -MkProxy{1,2}. The best approach we've come up with is to use TyVarTvs during -the kind-checking pass. First off, note that it's OK if the kind-checking pass -is too permissive: we'll snag the problems in the type-checking pass later. -(This extra permissiveness might happen with something like +MkProxy{1,2}. + +In effect, we are simply gathering constraints on the shape of Proxy's +kind, with no skolemisation or implication constraints involved at all. + +The best approach we've come up with is to use TyVarTvs during the +kind-checking pass, rather than ordinary skolems. This is why we use +the "_Tv" variant, bindOuterSigTKBndrs_Tv. + +Our only goal is to gather constraints on the kind of the type constructor; +we do not certify that the data declaration is well-kinded. For example: data SameKind :: k -> k -> Type data Bad a where MkBad :: forall k1 k2 (a :: k1) (b :: k2). Bad (SameKind a b) -which would be accepted if k1 and k2 were TyVarTvs. This is correctly rejected -in the second pass, though. Test case: polykinds/TyVarTvKinds3) -Recall that the kind-checking pass exists solely to collect constraints -on the kinds and to power unification. - -To achieve the use of TyVarTvs, we must be careful to use specialized functions -that produce TyVarTvs, not ordinary skolems. This is why we need -kcExplicitTKBndrs and kcImplicitTKBndrs in GHC.Tc.Gen.HsType, separate from their -tc... variants. +which would be accepted by kcConDecl because k1 and k2 are +TyVarTvs. It is correctly rejected in the second pass, tcConDecl. Test +case: polykinds/TyVarTvKinds3) -The drawback of this approach is sometimes it will accept a definition that +One drawback of this approach is sometimes it will accept a definition that a (hypothetical) declarative specification would likely reject. As a general rule, we don't want to allow polymorphic recursion without a CUSK. Indeed, the whole point of CUSKs is to allow polymorphic recursion. Yet, the TyVarTvs @@ -1746,6 +1722,23 @@ be rejected (without a CUSK). However, the accepted definitions are indeed well-kinded and any rejected definitions would be accepted with a CUSK, and so this wrinkle need not cause anyone to lose sleep. +Note [Recursion and promoting data constructors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We don't want to allow promotion in a strongly connected component +when kind checking. + +Consider: + data T f = K (f (K Any)) + +When kind checking the `data T' declaration the local env contains the +mappings: + T -> ATcTyCon + K -> APromotionErr + +APromotionErr is only used for DataCons, and only used during type checking +in tcTyClGroup. + + ************************************************************************ * * \subsection{Type checking} @@ -3214,7 +3207,7 @@ tcConDecl :: KnotTied TyCon -- Representation tycon. Knot-tied! -> ConDecl GhcRn -> TcM [DataCon] -tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs res_kind res_tmpl new_or_data (ConDeclH98 { con_name = lname@(L _ name) , con_ex_tvs = explicit_tkv_nms , con_mb_cxt = hs_ctxt @@ -3224,7 +3217,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Get hold of the existential type variables -- e.g. data T a = forall k (b::k) f. MkT a (f b) - -- Here tmpl_bndrs = {a} + -- Here tc_bndrs = {a} -- hs_qvars = HsQTvs { hsq_implicit = {k} -- , hsq_explicit = {f,b} } @@ -3242,29 +3235,35 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data } - ; let tmpl_tvs = binderVars tmpl_bndrs - ; let fake_ty = mkSpecForAllTys tmpl_tvs $ + ; let tc_tvs = binderVars tc_bndrs + fake_ty = mkSpecForAllTys tc_tvs $ mkInvisForAllTys exp_tvbndrs $ mkPhiTy ctxt $ mkVisFunTys arg_tys $ unitTy -- That type is a lie, of course. (It shouldn't end in ()!) -- And we could construct a proper result type from the info - -- at hand. But the result would mention only the tmpl_tvs, + -- at hand. But the result would mention only the univ_tvs, -- and so it just creates more work to do it right. Really, -- we're only doing this to find the right kind variables to -- quantify over, and this type is fine for that purpose. - -- exp_tvs have explicit, user-written binding sites + -- exp_tvbndrs have explicit, user-written binding sites -- the kvs below are those kind variables entirely unmentioned by the user -- and discovered only by generalization ; kvs <- kindGeneralizeAll fake_ty - ; let skol_tvs = kvs ++ tmpl_tvs + ; let skol_tvs = tc_tvs ++ kvs ++ binderVars exp_tvbndrs ; reportUnsolvedEqualities skol_info skol_tvs tclvl wanted - - -- Zonk to Types + -- The skol_info claims that all the variables are bound + -- by the data constructor decl, whereas actually the + -- univ_tvs are bound by the data type decl itself. It + -- would be better to have a doubly-nested implication. + -- But that just doesn't seem worth it. + -- See test dependent/should_fail/T13780a + + -- Zonk to Types ; (ze, qkvs) <- zonkTyBndrs kvs ; (ze, user_qtvbndrs) <- zonkTyVarBindersX ze exp_tvbndrs ; arg_tys <- zonkScaledTcTypesToTypesX ze arg_tys @@ -3272,15 +3271,13 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Can't print univ_tvs, arg_tys etc, because we are inside the knot here ; traceTc "tcConDecl 2" (ppr name $$ ppr field_lbls) - ; let - univ_tvbs = tyConInvisTVBinders tmpl_bndrs - univ_tvs = binderVars univ_tvbs - ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs - ex_tvs = binderVars ex_tvbs - -- For H98 datatypes, the user-written tyvar binders are precisely - -- the universals followed by the existentials. - -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. - user_tvbs = univ_tvbs ++ ex_tvbs + ; let univ_tvbs = tyConInvisTVBinders tc_bndrs + ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs + ex_tvs = binderVars ex_tvbs + -- For H98 datatypes, the user-written tyvar binders are precisely + -- the universals followed by the existentials. + -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. + user_tvbs = univ_tvbs ++ ex_tvbs ; traceTc "tcConDecl 2" (ppr name) ; is_infix <- tcConIsInfixH98 name hs_args @@ -3288,7 +3285,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data ; fam_envs <- tcGetFamInstEnvs ; dc <- buildDataCon fam_envs name is_infix rep_nm stricts Nothing field_lbls - univ_tvs ex_tvs user_tvbs + tc_tvs ex_tvs user_tvbs [{- no eq_preds -}] ctxt arg_tys res_tmpl rep_tycon tag_map -- NB: we put data_tc, the type constructor gotten from the @@ -3299,7 +3296,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data where skol_info = DataConSkol name -tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs _res_kind res_tmpl new_or_data -- NB: don't use res_kind here, as it's ill-scoped. Instead, -- we get the res_kind by typechecking the result type. (ConDeclGADT { con_names = names @@ -3344,7 +3341,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data ; res_ty <- zonkTcTypeToTypeX ze res_ty ; let (univ_tvs, ex_tvs, tvbndrs', eq_preds, arg_subst) - = rejigConRes tmpl_bndrs res_tmpl tvbndrs res_ty + = rejigConRes tc_bndrs res_tmpl tvbndrs res_ty -- See Note [Checking GADT return types] ctxt' = substTys arg_subst ctxt @@ -3532,9 +3529,9 @@ errors reported in one pass. See #7175, and #10836. -- TI :: forall b1 c1. (b1 ~ c1) => b1 -> :R7T b1 c1 -- In this case orig_res_ty = T (e,e) -rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result type; e.g. - -- data instance T [a] b c ... - -- gives template ([a,b,c], T [a] b c) +rejigConRes :: [KnotTied TyConBinder] -- Template for result type; e.g. + -> KnotTied Type -- data instance T [a] b c ... + -- gives template ([a,b,c], T [a] b c) -> [InvisTVBinder] -- The constructor's type variables (both inferred and user-written) -> KnotTied Type -- res_ty -> ([TyVar], -- Universal @@ -3546,10 +3543,10 @@ rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result -- We don't check that the TyCon given in the ResTy is -- the same as the parent tycon, because checkValidDataCon will do it -- NB: All arguments may potentially be knot-tied -rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty +rejigConRes tc_tvbndrs res_tmpl dc_tvbndrs res_ty -- E.g. data T [a] b c where -- MkT :: forall x y z. T [(x,y)] z z - -- The {a,b,c} are the tmpl_tvs, and the {x,y,z} are the dc_tvs + -- The {a,b,c} are the tc_tvs, and the {x,y,z} are the dc_tvs -- (NB: unlike the H98 case, the dc_tvs are not all existential) -- Then we generate -- Univ tyvars Eq-spec @@ -3564,7 +3561,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- , [], [x,y,z] -- , [a~(x,y),b~z], ) | Just subst <- tcMatchTy res_tmpl res_ty - = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tmpl_tvs dc_tvs subst + = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tc_tvs dc_tvs subst raw_ex_tvs = dc_tvs `minusList` univ_tvs (arg_subst, substed_ex_tvs) = substTyVarBndrs kind_subst raw_ex_tvs @@ -3591,10 +3588,10 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- albeit bogus, relying on checkValidDataCon to check the -- bad-result-type error before seeing that the other fields look odd -- See Note [Checking GADT return types] - = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, dc_tvbndrs, [], emptyTCvSubst) + = (tc_tvs, dc_tvs `minusList` tc_tvs, dc_tvbndrs, [], emptyTCvSubst) where - dc_tvs = binderVars dc_tvbndrs - tmpl_tvs = binderVars tmpl_bndrs + dc_tvs = binderVars dc_tvbndrs + tc_tvs = binderVars tc_tvbndrs {- Note [mkGADTVars] ~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -688,9 +688,8 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env -- Do /not/ check that the number of patterns = tyConArity fam_tc -- See [Arity of data families] in GHC.Core.FamInstEnv ; (qtvs, pats, res_kind, stupid_theta) - <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs - fixity hs_ctxt hs_pats m_ksig hs_cons - new_or_data + <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity + hs_ctxt hs_pats m_ksig new_or_data -- Eta-reduce the axiom if possible -- Quite tricky: see Note [Implementing eta reduction for data families] @@ -857,7 +856,7 @@ TyVarEnv will simply be empty, and there is nothing to worry about. tcDataFamInstHeader :: AssocInstInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn -> LexicalFixity -> LHsContext GhcRn - -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> [LConDecl GhcRn] + -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> NewOrData -> TcM ([TyVar], [Type], Kind, ThetaType) -- The "header" of a data family instance is the part other than @@ -865,7 +864,7 @@ tcDataFamInstHeader -- e.g. data instance D [a] :: * -> * where ... -- Here the "header" is the bit before the "where" tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity - hs_ctxt hs_pats m_ksig hs_cons new_or_data + hs_ctxt hs_pats m_ksig new_or_data = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (scoped_tvs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ @@ -884,8 +883,8 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity -- Add constraints from the result signature ; res_kind <- tc_kind_sig m_ksig - -- Add constraints from the data constructors - ; kcConDecls new_or_data res_kind hs_cons + -- Do not add constraints from the data constructors + -- See Note [Kind inference for data family instances] -- Check that the result kind of the TyCon applied to its args -- is compatible with the explicit signature (or Type, if there @@ -1049,6 +1048,81 @@ however, so this Note aims to describe these subtleties: themselves. Heavy sigh. But not truly hard; that's what tcbVisibilities does. +Note [Kind inference for data family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this GADT-style data type declaration, where I have used +fresh variables in the data constructor's type, to stress that c,d are +quite distinct from a,b. + data T a b where + MkT :: forall c d. c d -> T c d + +Following Note [Inferring kinds for type declarations] in GHC.Tc.TyCl, +to infer T's kind, we initially give T :: kappa, a monomorpic kind, +gather constraints from the header and data constructors, and conclude + T :: (kappa1 -> type) -> kappa1 -> Type +Then we generalise, giving + T :: forall k. (k->Type) -> k -> Type + +Now what about a data /instance/ decl + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p Int where ... + +No doubt here! The poly-kinded T is instantiated with k=Type, so the +header really looks like + data instance T @Type (p :: Type->Type) Int where ... + +But what about this? + data instance T p q where + MkT :: forall r. r Int -> T r Int + +So what kind do 'p' and 'q' have? No clues from the header, but from +the data constructor we can clearly see that (r :: Type->Type). Does +that mean that the the /entire data instance/ is instantiated at Type, +like this? + data instance T @Type (p :: Type->Type) (q :: Type) where + ... + +Not at all! This is a /GADT/-style decl, so the kind argument might +be specialised in this particular data constructor, thus: + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall (r :: Type -> Type). + r Int -> T @Type r Int +(and perhaps specialised differently in some other data +constructor MkT2). + +The key difference in this case and 'data T' at the top of this Note +is that we have no known kind for 'data T'. We thus forbid different +specialisations of T in its constructors, in an attempt to avoid +inferring polymorphic recursion. In data family T, however, there is +no problem with polymorphic recursion: we already /fully know/ T's +kind -- that came from the family declaration, and is not influenced +by the data instances -- and hence we /can/ specialise T's kind +differently in different GADT data constructors. + +SHORT SUMMARY: in a data instance decl, it's not clear whether kind +constraints arising from the data constructors should be considered +local to the (GADT) data /constructor/ or should apply to the entire +data instance. + +DESIGN CHOICE: in data/newtype family instance declarations, we ignore +the /data constructor/ declarations altogether, looking only at the +data instance /header/. + +Observations: +* This choice is simple to describe, as well as simple to implment. + For a data/newtype instance decl, the instance kinds are influenced + /only/ by the header. + +* We could treat Haskell-98 style data-instance decls differently, by + taking the data constructors into account, since there are no GADT + issues. + +* Ditto newtypes, since again you can't have newtype GADTs. + +But for now at least, we keep the simplest choice. See #18891 and !4419 +for more discussion of this issue.a + -} ===================================== docs/users_guide/exts/poly_kinds.rst ===================================== @@ -130,8 +130,45 @@ This rule has occasionally-surprising consequences (see The kind-polymorphism from the class declaration makes ``D1`` kind-polymorphic, but not so ``D2``; and similarly ``F1``, ``F2``. +Kind inference in type signatures +--------------------------------- + +When kind-checking a type, GHC considers only what is written in that +type when figuring out how to generalise the type's kind. + +For example, +consider these definitions (with :extension:`ScopedTypeVariables`): :: + + data Proxy a -- Proxy :: forall k. k -> Type + p :: forall a. Proxy a + p = Proxy :: Proxy (a :: Type) + +GHC reports an error, saying that the kind of ``a`` should be a kind variable +``k``, not ``Type``. This is because, by looking at the type signature +``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not +restricted to be ``Type``. The function definition is then rejected for being +more specific than its type signature. + +.. _explicit-kind-quantification: + +Explicit kind quantification +---------------------------- + +Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, +as in these examples: :: + + data Proxy :: forall k. k -> Type + f :: (forall k (a :: k). Proxy a -> ()) -> Int + +Note that the second example has a ``forall`` that binds both a kind ``k`` and +a type variable ``a`` of kind ``k``. In general, there is no limit to how +deeply nested this sort of dependency can work. However, the dependency must +be well-scoped: ``forall (a :: k) k. ...`` is an error. + + .. _inferring-variable-order: + Inferring the order of variables in a type/class declaration ------------------------------------------------------------ @@ -490,41 +527,74 @@ This also applies to GADT-style data instances: :: -- • In the data instance declaration for ‘T’ -Kind inference in closed type families --------------------------------------- +Kind inference in data type declarations +---------------------------------------- -Although all open type families are considered to have a complete -user-supplied kind signature, we can relax this condition for closed -type families, where we have equations on which to perform kind -inference. GHC will infer kinds for the arguments and result types of a -closed type family. +Consider the declaration :: -GHC supports *kind-indexed* type families, where the family matches both -on the kind and type. GHC will *not* infer this behaviour without a -complete user-supplied kind signature, as doing so would sometimes infer -non-principal types. Indeed, we can see kind-indexing as a form -of polymorphic recursion, where a type is used at a kind other than -its most general in its own definition. + data T1 f a = MkT1 (f a) + data T2 f a where + MkT2 :: f a -> T f a -For example: :: +In both cases GHC looks at the data constructor declarations to +give constraints on the kind of ``T``, yielding :: - type family F1 a where - F1 True = False - F1 False = True - F1 x = x - -- F1 fails to compile: kind-indexing is not inferred + T1, T2 :: forall k. (k -> Type) -> k -> Typ - type family F2 (a :: k) where - F2 True = False - F2 False = True - F2 x = x - -- F2 fails to compile: no complete signature +Consider the type :: + + data G (a :: k) where + GInt :: G Int + GMaybe :: G Maybe + +This datatype ``G`` is GADT-like in both its kind and its type. Suppose you +have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that +``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and +``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` +be in effect, but pattern-matching on ``G`` requires no extension beyond +:extension:`GADTs`. That this works is actually a straightforward extension +of regular GADTs and a consequence of the fact that kinds and types are the +same. + +Note that the datatype ``G`` is used at different kinds in its body, and +therefore that kind-indexed GADTs use a form of polymorphic recursion. +It is thus only possible to use this feature if you have provided a +complete user-supplied kind signature +for the datatype (:ref:`complete-kind-signatures`), or a standalone +kind signature (:ref:`standalone-kind-signatures`); +in the case of ``G`` we have a CUSK. +A more explicit declaration that fills in the invisible kind arguments would be :: + + data G @k (a :: k) where + GInt :: G @Type Int + GMaybe :: G @(Type->Type) Maybe + +where you can see the GADT-like nature of the two constructors. + +Kind inference for data/newtype instance declarations +----------------------------------------------------- + +Consider these declarations :: + + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p q where + MkT :: forall r. r Int -> T r Int + +Here ``T`` has an invisible kind argument; and perhaps it is instantiated +to ``(Type->Type)`` in the instance, thus :: + + data instance T @(Type->Type) p q where + MkT :: forall r. r Int -> T r Int + +This latter form is accepted, but the former is not: in data/newtype +instance declararations (unlike ordinary data/newtype declarations) +we do *not* look at the constructor declarations. The principle is +that *the instantiation of the data instance should be apparent from the header alone*. +This principle makes the program easier to understand; but it also +avoids a swamp of complexity about which type specialisation comes from the +data instance, and which from the individual GADT data constructors. - type family F3 (a :: k) :: k where - F3 True = False - F3 False = True - F3 x = x - -- OK Kind inference in class instance declarations --------------------------------------------- @@ -555,43 +625,8 @@ infrastructure, and it's not clear the payoff is worth it. If you want to restrict ``b``\ 's kind in the instance above, just use a kind signature in the instance head. -Kind inference in type signatures ---------------------------------- - -When kind-checking a type, GHC considers only what is written in that -type when figuring out how to generalise the type's kind. - -For example, -consider these definitions (with :extension:`ScopedTypeVariables`): :: - - data Proxy a -- Proxy :: forall k. k -> Type - p :: forall a. Proxy a - p = Proxy :: Proxy (a :: Type) - -GHC reports an error, saying that the kind of ``a`` should be a kind variable -``k``, not ``Type``. This is because, by looking at the type signature -``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not -restricted to be ``Type``. The function definition is then rejected for being -more specific than its type signature. - -.. _explicit-kind-quantification: - -Explicit kind quantification ----------------------------- - -Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, -as in these examples: :: - - data Proxy :: forall k. k -> Type - f :: (forall k (a :: k). Proxy a -> ()) -> Int - -Note that the second example has a ``forall`` that binds both a kind ``k`` and -a type variable ``a`` of kind ``k``. In general, there is no limit to how -deeply nested this sort of dependency can work. However, the dependency must -be well-scoped: ``forall (a :: k) k. ...`` is an error. - -Implicit quantification in type synonyms and type family instances ------------------------------------------------------------------- +Kind inference in type synonyms and type family instances +--------------------------------------------------------- Consider the scoping rules for type synonyms and type family instances, such as these:: @@ -706,29 +741,41 @@ kinds. Consequently, visible dependent quantifiers are rejected in any context that is unambiguously the type of a term. They are also rejected in the types of data constructors. -Kind-indexed GADTs ------------------- +Kind inference in closed type families +-------------------------------------- -Consider the type :: +Although all open type families are considered to have a complete +user-supplied kind signature, we can relax this condition for closed +type families, where we have equations on which to perform kind +inference. GHC will infer kinds for the arguments and result types of a +closed type family. - data G (a :: k) where - GInt :: G Int - GMaybe :: G Maybe +GHC supports *kind-indexed* type families, where the family matches both +on the kind and type. GHC will *not* infer this behaviour without a +complete user-supplied kind signature, as doing so would sometimes infer +non-principal types. Indeed, we can see kind-indexing as a form +of polymorphic recursion, where a type is used at a kind other than +its most general in its own definition. -This datatype ``G`` is GADT-like in both its kind and its type. Suppose you -have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that -``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and -``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` -be in effect, but pattern-matching on ``G`` requires no extension beyond -:extension:`GADTs`. That this works is actually a straightforward extension -of regular GADTs and a consequence of the fact that kinds and types are the -same. +For example: :: -Note that the datatype ``G`` is used at different kinds in its body, and -therefore that kind-indexed GADTs use a form of polymorphic recursion. -It is thus only possible to use this feature if you have provided a -complete user-supplied kind signature -for the datatype (:ref:`complete-kind-signatures`). + type family F1 a where + F1 True = False + F1 False = True + F1 x = x + -- F1 fails to compile: kind-indexing is not inferred + + type family F2 (a :: k) where + F2 True = False + F2 False = True + F2 x = x + -- F2 fails to compile: no complete signature + + type family F3 (a :: k) :: k where + F3 True = False + F3 False = True + F3 x = x + -- OK Higher-rank kinds ----------------- ===================================== testsuite/tests/dependent/should_fail/T13780a.stderr ===================================== @@ -3,7 +3,7 @@ T13780a.hs:9:40: error: • Couldn't match kind ‘a’ with ‘Bool’ Expected kind ‘Foo a’, but ‘MkFoo’ has kind ‘Foo Bool’ ‘a’ is a rigid type variable bound by - a family instance declaration + the data constructor ‘SMkFoo’ at T13780a.hs:9:20-31 • In the second argument of ‘(~)’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ ===================================== testsuite/tests/deriving/should_compile/T11416.hs ===================================== @@ -12,9 +12,11 @@ newtype T f (a :: ConstantT Type f) = T (f a) deriving Functor data family TFam1 (f :: k1) (a :: k2) -newtype instance TFam1 f (ConstantT a f) = TFam1 (f a) +newtype instance TFam1 (f :: k -> Type) (ConstantT (a :: k) f) + = TFam1 (f a) deriving Functor data family TFam2 (f :: k1) (a :: k2) -newtype instance TFam2 f (a :: ConstantT Type f) = TFam2 (f a) +newtype instance TFam2 (f :: Type -> Type) (a :: ConstantT Type f) + = TFam2 (f a) deriving Functor ===================================== testsuite/tests/patsyn/should_fail/T15685.stderr ===================================== @@ -1,13 +1,13 @@ T15685.hs:13:24: error: - • Could not deduce: a ~ [k0] - from the context: as ~ (a1 : as1) + • Could not deduce: k ~ [k0] + from the context: as ~ (a : as1) bound by a pattern with constructor: - Here :: forall {a1} (f :: a1 -> *) (a2 :: a1) (as :: [a1]). - f a2 -> NS f (a2 : as), + Here :: forall {k} (f :: k -> *) (a :: k) (as :: [k]). + f a -> NS f (a : as), in a pattern synonym declaration at T15685.hs:13:19-26 - ‘a’ is a rigid type variable bound by + ‘k’ is a rigid type variable bound by the inferred type of HereNil :: NS f as at T15685.hs:13:9-15 Possible fix: add a type signature for ‘HereNil’ ===================================== testsuite/tests/polykinds/T13659.stderr ===================================== @@ -1,6 +1,6 @@ -T13659.hs:14:27: error: - • Expected a type, but ‘a’ has kind ‘[*]’ - • In the first argument of ‘Format’, namely ‘'[Int, a]’ - In the type ‘Format '[Int, a]’ +T13659.hs:14:15: error: + • Expected kind ‘[*]’, but ‘a’ has kind ‘*’ + • In the first argument of ‘Format’, namely ‘a’ + In the type ‘Format a’ In the definition of data constructor ‘I’ ===================================== testsuite/tests/polykinds/T16221a.stderr ===================================== @@ -1,7 +1,7 @@ T16221a.hs:6:49: error: - • Expected kind ‘k’, but ‘b’ has kind ‘k1’ - ‘k1’ is a rigid type variable bound by + • Expected kind ‘k’, but ‘b’ has kind ‘k2’ + ‘k2’ is a rigid type variable bound by an explicit forall k (b :: k) at T16221a.hs:6:20 ‘k’ is a rigid type variable bound by ===================================== testsuite/tests/th/T9692.hs ===================================== @@ -12,7 +12,7 @@ class C a where data F a (b :: k) :: Type instance C Int where - data F Int x = FInt x + data F Int (x :: Type) = FInt x $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info ===================================== testsuite/tests/typecheck/should_compile/T18891.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +data family T2 (a :: k) +data instance T2 a where + MkT2 :: T2 Maybe + +newtype N3 :: forall k -> TYPE k where + MkN3 :: N3 m -> N3 m + +type N4 :: forall k -> TYPE k +newtype N4 :: forall k -> TYPE k where + MkN4 :: N4 m -> N4 m ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs ===================================== @@ -4,6 +4,8 @@ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} module UnliftedNewtypesUnassociatedFamily where @@ -20,7 +22,16 @@ newtype instance DFT ('TupleRep '[ 'IntRep, 'WordRep]) data instance DFT 'LiftedRep = MkDFT4 | MkDFT5 data family DF :: TYPE (r :: RuntimeRep) -newtype instance DF = MkDF1 Int# -newtype instance DF = MkDF2 Word# -newtype instance DF = MkDF3 (# Int#, Word# #) + +-- Use a type application +newtype instance DF @IntRep = MkDF1 Int# + +-- Use a kind signature +newtype instance DF :: TYPE 'WordRep where + MkDF2 :: Word# -> DF + +-- Also uses a kind signature +newtype instance DF :: TYPE ('TupleRep '[ 'IntRep, 'WordRep ]) where + MkDF3 :: (# Int#, Word# #) -> DF + data instance DF = MkDF4 | MkDF5 ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs ===================================== @@ -10,14 +10,14 @@ module UnliftedNewtypesUnassociatedFamily where import GHC.Int (Int(I#)) -import GHC.Exts (Int#,Word#,RuntimeRep(IntRep)) +import GHC.Exts (Int#,Word#,RuntimeRep(IntRep, WordRep)) import GHC.Exts (TYPE) type KindOf (a :: TYPE k) = k data family D (a :: TYPE r) :: TYPE r -newtype instance D a = MkWordD Word# +newtype instance D (a :: TYPE 'WordRep) = MkWordD Word# -newtype instance D a :: TYPE (KindOf a) where - MkIntD :: forall (a :: TYPE 'IntRep). Int# -> D a +newtype instance D (a :: TYPE 'IntRep) :: TYPE (KindOf a) where + MkIntD :: forall (b :: TYPE 'IntRep). Int# -> D b ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,5 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) +test('T18891', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T18891a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +newtype N1 :: forall k. TYPE k where + MkN1 :: N1 -> N1 + +type N2 :: forall k. TYPE k +newtype N2 :: forall k. TYPE k where + MkN2 :: N2 -> N2 + ===================================== testsuite/tests/typecheck/should_fail/T18891a.stderr ===================================== @@ -0,0 +1,12 @@ + +T18891a.hs:8:4: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN1 :: N1 -> N1 + • In the definition of data constructor ‘MkN1’ + In the newtype declaration for ‘N1’ + +T18891a.hs:12:3: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN2 :: N2 -> N2 + • In the definition of data constructor ‘MkN2’ + In the newtype declaration for ‘N2’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr ===================================== @@ -1,11 +1,5 @@ -UnliftedNewtypesFamilyKindFail2.hs:12:20: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the newtype instance declaration for ‘F’ - -UnliftedNewtypesFamilyKindFail2.hs:12:31: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the type ‘(F 5)’ - In the definition of data constructor ‘MkF’ +UnliftedNewtypesFamilyKindFail2.hs:12:20: error: + • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ + • In the first argument of ‘F’, namely ‘5’ + In the newtype instance declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} + +module UnliftedNewtypesUnassociatedFamily where + +import GHC.Int (Int(I#)) +import GHC.Word (Word(W#)) +import GHC.Exts (Int#,Word#) +import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep)) + +data family DF :: TYPE (r :: RuntimeRep) + +-- All these fail: see #18891 and !4419 +-- See Note [Kind inference for data family instances] +-- in GHC.Tc.TyCl.Instance +newtype instance DF = MkDF1a Int# +newtype instance DF = MkDF2a Word# +newtype instance DF = MkDF3a (# Int#, Word# #) ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr ===================================== @@ -0,0 +1,18 @@ + +UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error: + • Expecting a lifted type, but ‘Int#’ is unlifted + • In the type ‘Int#’ + In the definition of data constructor ‘MkDF1a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error: + • Expecting a lifted type, but ‘Word#’ is unlifted + • In the type ‘Word#’ + In the definition of data constructor ‘MkDF2a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error: + • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted + • In the type ‘(# Int#, Word# #)’ + In the definition of data constructor ‘MkDF3a’ + In the newtype instance declaration for ‘DF’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKind', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, ['']) test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, ['']) +test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, ['']) test('T13834', normal, compile_fail, ['']) test('T17077', normal, compile_fail, ['']) test('T16512a', normal, compile_fail, ['']) @@ -589,3 +590,4 @@ test('T18640b', normal, compile_fail, ['']) test('T18640c', normal, compile_fail, ['']) test('T10709', normal, compile_fail, ['']) test('T10709b', normal, compile_fail, ['']) +test('T18891a', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2f32a597b6b0aeb62c8623b1a61ad168392d48b9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2f32a597b6b0aeb62c8623b1a61ad168392d48b9 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 Wed Nov 25 14:43:26 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Wed, 25 Nov 2020 09:43:26 -0500 Subject: [Git][ghc/ghc][wip/andreask/opt_dumps] Optimize dumping of consecutive whitespace. Message-ID: <5fbe6d8e79bd5_86c11450e281784b3@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/opt_dumps at Glasgow Haskell Compiler / GHC Commits: 19f77e98 by Andreas Klebinger at 2020-11-25T15:42:58+01:00 Optimize dumping of consecutive whitespace. The naive way of putting out n characters of indent would be something like `hPutStr hdl (replicate n ' ')`. However this is quite inefficient as we allocate an absurd number of strings consisting of simply spaces as we don't cache them. To improve on this we now track if we can simply write ascii spaces via hPutBuf instead. This is the case when running with -ddump-to-file where we force the encoding to be UTF8. This avoids both the cost of going through encoding as well as avoiding allocation churn from all the white space. Instead we simply use hPutBuf on a preallocated unlifted string. When dumping stg like this: > nofib/spectral/simple/Main.hs -fforce-recomp -ddump-stg-final -ddump-to-file -c +RTS -s Allocations went from 1,778 MB to 1,702MB. About a 4% reduction of allocation! I did not measure the difference in runtime but expect it to be similar. Bumps the haddock submodule since the interface of GHC's Pretty slightly changed. ------------------------- Metric Decrease: T12227 ------------------------- - - - - - 6 changed files: - compiler/GHC/Driver/Ppr.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Utils/Error.hs - compiler/GHC/Utils/Outputable.hs - compiler/GHC/Utils/Ppr.hs - utils/haddock Changes: ===================================== compiler/GHC/Driver/Ppr.hs ===================================== @@ -66,7 +66,7 @@ showSDocDebug dflags d = renderWithContext ctx d printForUser :: DynFlags -> Handle -> PrintUnqualified -> Depth -> SDoc -> IO () printForUser dflags handle unqual depth doc - = printSDocLn ctx PageMode handle doc + = printSDocLn ctx (PageMode False) handle doc where ctx = initSDocContext dflags (mkUserStyle unqual depth) -- | Like 'printSDocLn' but specialized with 'LeftMode' and ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -1377,7 +1377,7 @@ defaultFatalMessager = hPutStrLn stderr jsonLogAction :: LogAction jsonLogAction dflags reason severity srcSpan msg = - defaultLogActionHPutStrDoc dflags stdout + defaultLogActionHPutStrDoc dflags True stdout (withPprStyle (PprCode CStyle) (doc $$ text "")) where str = renderWithContext (initSDocContext dflags defaultUserStyle) msg @@ -1400,9 +1400,9 @@ defaultLogAction dflags reason severity srcSpan msg SevWarning -> printWarns SevError -> printWarns where - printOut = defaultLogActionHPrintDoc dflags stdout - printErrs = defaultLogActionHPrintDoc dflags stderr - putStrSDoc = defaultLogActionHPutStrDoc dflags stdout + printOut = defaultLogActionHPrintDoc dflags False stdout + printErrs = defaultLogActionHPrintDoc dflags False stderr + putStrSDoc = defaultLogActionHPutStrDoc dflags False stdout -- Pretty print the warning flag, if any (#10752) message = mkLocMessageAnn flagMsg severity srcSpan msg @@ -1442,16 +1442,19 @@ defaultLogAction dflags reason severity srcSpan msg | otherwise = "" -- | Like 'defaultLogActionHPutStrDoc' but appends an extra newline. -defaultLogActionHPrintDoc :: DynFlags -> Handle -> SDoc -> IO () -defaultLogActionHPrintDoc dflags h d - = defaultLogActionHPutStrDoc dflags h (d $$ text "") - -defaultLogActionHPutStrDoc :: DynFlags -> Handle -> SDoc -> IO () -defaultLogActionHPutStrDoc dflags h d +defaultLogActionHPrintDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () +defaultLogActionHPrintDoc dflags asciiSpace h d + = defaultLogActionHPutStrDoc dflags asciiSpace h (d $$ text "") + +-- | The boolean arguments let's the pretty printer know if it can optimize indent +-- by writing ascii ' ' characters without going through decoding. +defaultLogActionHPutStrDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () +defaultLogActionHPutStrDoc dflags asciiSpace h d -- Don't add a newline at the end, so that successive -- calls to this log-action can output all on the same line - = printSDoc ctx Pretty.PageMode h d - where ctx = initSDocContext dflags defaultUserStyle + = printSDoc ctx (Pretty.PageMode asciiSpace) h d + where + ctx = initSDocContext dflags defaultUserStyle newtype FlushOut = FlushOut (IO ()) ===================================== compiler/GHC/Utils/Error.hs ===================================== @@ -327,7 +327,8 @@ dumpSDocWithStyle sty dflags dumpOpt hdr doc = $$ blankLine $$ doc return $ mkDumpDoc hdr d - defaultLogActionHPrintDoc dflags handle (withPprStyle sty doc') + -- When we dump to files we use UTF8. Which allows ascii spaces. + defaultLogActionHPrintDoc dflags True handle (withPprStyle sty doc') -- write the dump to stdout writeDump Nothing = do ===================================== compiler/GHC/Utils/Outputable.hs ===================================== @@ -563,7 +563,7 @@ pprCode cs d = withPprStyle (PprCode cs) d renderWithContext :: SDocContext -> SDoc -> String renderWithContext ctx sdoc - = let s = Pretty.style{ Pretty.mode = PageMode, + = let s = Pretty.style{ Pretty.mode = PageMode False, Pretty.lineLength = sdocLineLength ctx } in Pretty.renderStyle s $ runSDoc sdoc ctx ===================================== compiler/GHC/Utils/Ppr.hs ===================================== @@ -917,16 +917,26 @@ data Style , ribbonsPerLine :: Float -- ^ Ratio of line length to ribbon length } --- | The default style (@mode=PageMode, lineLength=100, ribbonsPerLine=1.5@). +-- | The default style (@mode=PageMode False, lineLength=100, ribbonsPerLine=1.5@). style :: Style -style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode } +style = Style { lineLength = 100, ribbonsPerLine = 1.5, mode = PageMode False } -- | Rendering mode. -data Mode = PageMode -- ^ Normal +data Mode = PageMode { asciiSpace :: Bool } -- ^ Normal | ZigZagMode -- ^ With zig-zag cuts | LeftMode -- ^ No indentation, infinitely long lines | OneLineMode -- ^ All on one line +-- | Can we output an ascii space character for spaces? +-- Mostly true, but not for e.g. UTF16 +-- See Note [putSpaces optimizations] for why we bother +-- to track this. +hasAsciiSpace :: Mode -> Bool +hasAsciiSpace mode = + case mode of + PageMode asciiSpace -> asciiSpace + _ -> False + -- | Render the @Doc@ to a String using the given @Style at . renderStyle :: Style -> Doc -> String renderStyle s = fullRender (mode s) (lineLength s) (ribbonsPerLine s) @@ -1034,6 +1044,20 @@ printDoc :: Mode -> Int -> Handle -> Doc -> IO () -- printDoc adds a newline to the end printDoc mode cols hdl doc = printDoc_ mode cols hdl (doc $$ text "") +{- Note [putSpaces optimizations] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +When using dump flags a lot of what we are dumping ends up being whitespace. +This is especially true for Core/Stg dumps. Enough so that it's worth optimizing. + +Especially in the common case of writing to an UTF8 or similarly encoded file +where space is equal to ascii space we use hPutBuf to write a preallocated +buffer to the file. This avoids a fair bit of allocation. + +For other cases we fall back to the old and slow path for simplicity. + +-} + printDoc_ :: Mode -> Int -> Handle -> Doc -> IO () -- printDoc_ does not add a newline at the end, so that -- successive calls can output stuff on the same line @@ -1051,9 +1075,27 @@ printDoc_ mode pprCols hdl doc -- the I/O library's encoding layer. (#3398) put (ZStr s) next = hPutFZS hdl s >> next put (LStr s) next = hPutPtrString hdl s >> next - put (RStr n c) next = hPutStr hdl (replicate n c) >> next + put (RStr n c) next + | c == ' ' + = putSpaces n >> next + | otherwise + = hPutStr hdl (replicate n c) >> next + putSpaces n + -- If we use ascii spaces we are allowed to use hPutBuf + -- See Note [putSpaces optimizations] + | hasAsciiSpace mode + , n <= 100 + = hPutBuf hdl (Ptr spaces') n + | hasAsciiSpace mode + , n > 100 + = hPutBuf hdl (Ptr spaces') 100 >> putSpaces (n-100) + + | otherwise = hPutStr hdl (replicate n ' ') done = return () -- hPutChar hdl '\n' + -- 100 spaces, so we avoid the allocation of replicate n ' ' + spaces' = " "# + -- some versions of hPutBuf will barf if the length is zero hPutPtrString :: Handle -> PtrString -> IO () ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 4d0498d503bd51b7d7626497580232685a2691a1 +Subproject commit b2f1aef40cf50cf08eb28f34a9af2b1f9155c2df View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19f77e98935d78f997eacb2e3eafa46328df3825 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/19f77e98935d78f997eacb2e3eafa46328df3825 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 Wed Nov 25 15:02:27 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 25 Nov 2020 10:02:27 -0500 Subject: [Git][ghc/ghc][wip/T18894] Unleash exported bindings later Message-ID: <5fbe720374060_86c3fc6ab4f115c1816c6@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: 0f02b2d9 by Sebastian Graf at 2020-11-25T16:02:13+01:00 Unleash exported bindings later - - - - - 3 changed files: - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs Changes: ===================================== compiler/GHC/Core/FVs.hs ===================================== @@ -525,12 +525,11 @@ ruleLhsFVIds (Rule { ru_bndrs = bndrs, ru_args = args }) = filterFV isLocalId $ addBndrs bndrs (exprs_fvs args) ruleRhsFreeIds :: CoreRule -> VarSet --- ^ This finds all locally-defined free Ids on the left hand side of a rule +-- ^ This finds all locally-defined free Ids on the right hand side of a rule -- and returns them as a non-deterministic set ruleRhsFreeIds (BuiltinRule {}) = emptyVarSet -ruleRhsFreeIds (Rule { ru_bndrs = bndrs, ru_args = args }) - = fvVarSet $ filterFV isLocalId $ - addBndrs bndrs $ exprs_fvs args +ruleRhsFreeIds (Rule { ru_bndrs = bndrs, ru_rhs = rhs }) + = fvVarSet $ filterFV isLocalId $ addBndrs bndrs $ expr_fvs rhs {- Note [Rule free var hack] (Not a hack any more) ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -66,42 +66,43 @@ data DmdAnalOpts = DmdAnalOpts -- Note: use `seqBinds` on the result to avoid leaks due to lazyness (cf Note -- [Stamp out space leaks in demand analysis]) dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> [CoreRule] -> CoreProgram -> CoreProgram -dmdAnalProgram opts fam_envs rules binds = binds_plus_dmds +dmdAnalProgram opts fam_envs rules binds = snd $ go (emptyAnalEnv opts fam_envs) binds where - env = emptyAnalEnv opts fam_envs - rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules - binds_plus_dmds = snd $ go env nopDmdType binds - - go _ dmd_ty [] = (dmd_ty, []) - go env dmd_ty (b:bs) = case b of + go _ [] = (nopDmdType, []) + go env (b:bs) = case b of NonRec id rhs | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel NonRecursive env topSubDmd id rhs - , (dmd_ty', bs') <- go env' (add_exported_use env' dmd_ty id') bs - , (dmd_ty'', id_dmd) <- findBndrDmd env' False (dmd_ty' `addLazyFVs` lazy_fvs) id' + , (dmd_ty', bs') <- go env' bs + , let !dmd_ty'' = add_exported_use env' dmd_ty' id' `addLazyFVs` lazy_fvs + , (dmd_ty''', id_dmd) <- findBndrDmd env' False dmd_ty'' id' , let id'' = annotate_id_dmd id' id_dmd - -> (dmd_ty'', NonRec id'' rhs' : bs') + -> (dmd_ty''', NonRec id'' rhs' : bs') Rec pairs | (env', lazy_fvs, pairs') <- dmdFix TopLevel env topSubDmd pairs , let ids' = map fst pairs' - , (dmd_ty', bs') <- go env' (add_exported_uses env' dmd_ty ids') bs - , (dmd_ty'', id_dmds) <- findBndrsDmds env' (dmd_ty' `addLazyFVs` lazy_fvs) ids' + , (dmd_ty', bs') <- go env' bs + , let !dmd_ty'' = add_exported_uses env' dmd_ty' ids' `addLazyFVs` lazy_fvs + , (dmd_ty''', id_dmds) <- findBndrsDmds env' dmd_ty'' ids' , let ids'' = zipWith annotate_id_dmd ids' id_dmds , let pairs'' = zipWith (\id'' (_, rhs') -> (id'', rhs')) ids'' pairs' - -> (dmd_ty'', Rec pairs'' : bs') + -> (dmd_ty''', Rec pairs'' : bs') annotate_id_dmd id dmd - | isInterestingTopLevelFn id, not (id `elemVarSet` rule_fvs) - -- See Note [Absence analysis for stable unfoldings and RULES] + | isInterestingTopLevelFn id = id `setIdDemandInfo` dmd | otherwise = id `setIdDemandInfo` topDmd add_exported_uses env = foldl' (add_exported_use env) add_exported_use env dmd_ty id - | isExportedId id || not (isInterestingTopLevelFn id) + | isExportedId id || elemVarSet id rule_fvs + -- See Note [Absence analysis for stable unfoldings and RULES] = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) | otherwise = dmd_ty + rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules + + {- Note [Stamp out space leaks in demand analysis] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The demand analysis pass outputs a new copy of the Core program in ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -1275,10 +1275,14 @@ mk_absent_let dflags fam_envs arg abs_rhs = mkAbsentErrorApp arg_ty msg msg = showSDoc (gopt_set dflags Opt_SuppressUniques) - (ppr arg <+> ppr (idType arg) <+> file_msg) + (vcat + [ text "Arg:" <+> ppr arg + , text "Type:" <+> ppr arg_ty + , file_msg + ]) file_msg = case outputFile dflags of Nothing -> empty - Just f -> text "in output file " <+> quotes (text f) + Just f -> text "In output file " <+> quotes (text f) -- We need to suppress uniques here because otherwise they'd -- end up in the generated code as strings. This is bad for -- determinism, because with different uniques the strings View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f02b2d94bf24ba0bd45d2b6dcd529bfba9c0d50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f02b2d94bf24ba0bd45d2b6dcd529bfba9c0d50 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 Wed Nov 25 15:07:42 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Wed, 25 Nov 2020 10:07:42 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 2 commits: Linker.c: Only define freeNativeCode_ELF when using elf format. Message-ID: <5fbe733e98ba1_86c879fa9c182192@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: aff226d5 by Andreas Klebinger at 2020-11-25T12:38:38+01:00 Linker.c: Only define freeNativeCode_ELF when using elf format. - - - - - cb8f1cb0 by Andreas Klebinger at 2020-11-25T12:38:38+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 ------------------------- - - - - - 2 changed files: - .gitlab-ci.yml - rts/Linker.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | ===================================== rts/Linker.c ===================================== @@ -171,7 +171,9 @@ Mutex linker_mutex; /* Generic wrapper function to try and Resolve and RunInit oc files */ int ocTryLoad( ObjectCode* oc ); +#if defined(OBJFORMAT_ELF) static void freeNativeCode_ELF (ObjectCode *nc); +#endif /* Link objects into the lower 2Gb on x86_64 and AArch64. GHC assumes the * small memory model on this architecture (see gcc docs, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1966559b15aad7db863dff47f5422aafa7086694...cb8f1cb04177174e0338f7ad59392625488a6ef2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1966559b15aad7db863dff47f5422aafa7086694...cb8f1cb04177174e0338f7ad59392625488a6ef2 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 Wed Nov 25 15:37:33 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Wed, 25 Nov 2020 10:37:33 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 2 commits: rts: EventLog.c: Properly cast (potential) 32bit pointers to uint64_t Message-ID: <5fbe7a3d4c3f3_86c3fc6ab4f115c187196@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: 73514d32 by Andreas Klebinger at 2020-11-25T16:36:59+01:00 rts: EventLog.c: Properly cast (potential) 32bit pointers to uint64_t - - - - - 1e9f0d5a by Andreas Klebinger at 2020-11-25T16:36:59+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 ------------------------- - - - - - 2 changed files: - .gitlab-ci.yml - rts/eventlog/EventLog.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | ===================================== rts/eventlog/EventLog.c ===================================== @@ -1489,7 +1489,8 @@ static void postTickyCounterDef(EventsBuf *eb, StgEntCounter *p) ensureRoomForVariableEvent(eb, len); postEventHeader(eb, EVENT_TICKY_COUNTER_DEF); postPayloadSize(eb, len); - postWord64(eb, (uint64_t) p); + + postWord64(eb, (uint64_t)((uintptr_t) p)); postWord16(eb, (uint16_t) p->arity); postString(eb, p->arg_kinds); postString(eb, p->str); @@ -1513,7 +1514,7 @@ static void postTickyCounterSample(EventsBuf *eb, StgEntCounter *p) ensureRoomForEvent(eb, EVENT_TICKY_COUNTER_SAMPLE); postEventHeader(eb, EVENT_TICKY_COUNTER_SAMPLE); - postWord64(eb, (uint64_t) p); + postWord64(eb, (uint64_t)((uintptr_t) p)); postWord64(eb, p->entry_count); postWord64(eb, p->allocs); postWord64(eb, p->allocd); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cb8f1cb04177174e0338f7ad59392625488a6ef2...1e9f0d5aa9caf47c18aa4b3abd0d610959ab4d07 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cb8f1cb04177174e0338f7ad59392625488a6ef2...1e9f0d5aa9caf47c18aa4b3abd0d610959ab4d07 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 Wed Nov 25 15:58:43 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 25 Nov 2020 10:58:43 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/win32-high-heap Message-ID: <5fbe7f33eb098_86c7d5924019082d@gitlab.mail> Ben Gamari pushed new branch wip/win32-high-heap at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/win32-high-heap 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 Wed Nov 25 16:00:45 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Wed, 25 Nov 2020 11:00:45 -0500 Subject: [Git][ghc/ghc][wip/T18891] Fix kind inference for data types. Again. Message-ID: <5fbe7fad5d39a_86c7d59240193792@gitlab.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: 7fabe293 by Simon Peyton Jones at 2020-11-25T16:00:01+00:00 Fix kind inference for data types. Again. This patch improves kcConDecls, when we are inferring the kind of a data type decl. Specifically * In kcConDecls/kcConDecl make it clear that the tc_res_kind argument is only used in the H98 case; and in that case there is not result kind signature; and hence no need for the disgusting splitPiTys in kcConDecls (now thankfully gone). The GADT case is a bit different to before, and much nicer. This is what fixes #18891. See Note [kcConDecls: kind-checking data type decls] * Do not look at the constructor decls of a data/newtype instance in tcDataFamInstanceHeader. See new Note [Kind inference for data family instances] This causes a few knock-on effects in the tests suite, because we require more information than before in the instance /header/. New user-manual material about this in "Kind inference in data type declarations" and "Kind inference for data/newtype instance declarations". * Minor improvement in kcTyClDecl, combining GADT and H98 case. Fixes #18891 - - - - - 21 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/poly_kinds.rst - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/deriving/should_compile/T11416.hs - testsuite/tests/patsyn/should_fail/T15685.stderr - testsuite/tests/polykinds/T13659.stderr - testsuite/tests/polykinds/T16221a.stderr - testsuite/tests/th/T9692.hs - + testsuite/tests/typecheck/should_compile/T18891.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/T18891a.hs - + testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2981,7 +2981,7 @@ bindOuterSigTKBndrs_Tv_M :: TcTyMode -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) -- Do not push level; do not make implication constraint; use Tvs -- Two major clients of this "bind-only" path are: --- Note [Kind-checking for GADTs] in TyCl +-- Note [Using TyVarTvs for kind-checking GADTs] in GHC.Tc.TyCl -- Note [Checking partial type signatures] bindOuterSigTKBndrs_Tv_M mode = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = True @@ -3294,8 +3294,8 @@ When we /must/ clone. When kind-checking T, we give (a :: kappa1). Then: - In kcConDecl we make a TyVarTv unification variable kappa2 for k2 - (as described in Note [Kind-checking for GADTs], even though this - example is an existential) + (as described in Note [Using TyVarTvs for kind-checking GADTs], + even though this example is an existential) - So we get (b :: kappa2) via bindExplicitTKBndrs_Tv - We end up unifying kappa1 := kappa2, because of the (SameKind a b) ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -1529,27 +1529,16 @@ kcTyClDecl :: TyClDecl GhcRn -> TcTyCon -> TcM () -- result kind signature have already been dealt with -- by inferInitialKind, so we can ignore them here. -kcTyClDecl (DataDecl { tcdLName = (L _ name) - , tcdDataDefn = defn }) tyCon - | HsDataDefn { dd_cons = cons@((L _ (ConDeclGADT {})) : _) - , dd_ctxt = (L _ []) - , dd_ND = new_or_data } <- defn - = -- See Note [Implementation of UnliftedNewtypes] STEP 2 - kcConDecls new_or_data (tyConResKind tyCon) cons - - -- hs_tvs and dd_kindSig already dealt with in inferInitialKind - -- This must be a GADT-style decl, - -- (see invariants of DataDefn declaration) - -- so (a) we don't need to bring the hs_tvs into scope, because the - -- ConDecls bind all their own variables - -- (b) dd_ctxt is not allowed for GADT-style decls, so we can ignore it - - | HsDataDefn { dd_ctxt = ctxt - , dd_cons = cons - , dd_ND = new_or_data } <- defn +kcTyClDecl (DataDecl { tcdLName = (L _ name), tcdDataDefn = defn }) tycon + | HsDataDefn { dd_ctxt = ctxt, dd_cons = cons, dd_ND = new_or_data } <- defn = bindTyClTyVars name $ \ _ _ _ -> - do { _ <- tcHsContext ctxt - ; kcConDecls new_or_data (tyConResKind tyCon) cons + -- NB: binding these tyvars isn't necessary for GADTs, but it does no + -- harm. For GADTs, each data con brings its own tyvars into scope, + -- and the ones from this bindTyClTyVars are either not mentioned or + -- (conceivably) shadowed. + do { traceTc "kcTyClDecl" (ppr tycon $$ ppr (tyConTyVars tycon) $$ ppr (tyConResKind tycon)) + ; _ <- tcHsContext ctxt + ; kcConDecls new_or_data (tyConResKind tycon) cons } kcTyClDecl (SynDecl { tcdLName = L _ name, tcdRhs = rhs }) _tycon @@ -1606,13 +1595,12 @@ kcConGADTArgs new_or_data res_kind con_args = case con_args of kcConDecls :: NewOrData -> Kind -- The result kind signature + -- Used only in H98 case -> [LConDecl GhcRn] -- The data constructors -> TcM () -kcConDecls new_or_data res_kind cons - = mapM_ (wrapLocM_ (kcConDecl new_or_data final_res_kind)) cons - where - (_, final_res_kind) = splitPiTys res_kind - -- See Note [kcConDecls result kind] +-- See Note [kcConDecls: kind-checking data type decls] +kcConDecls new_or_data tc_res_kind cons + = mapM_ (wrapLocM_ (kcConDecl new_or_data tc_res_kind)) cons -- Kind check a data constructor. In additional to the data constructor, -- we also need to know about whether or not its corresponding type was @@ -1623,82 +1611,69 @@ kcConDecl :: NewOrData -> Kind -- Result kind of the type constructor -- Usually Type but can be TYPE UnliftedRep -- or even TYPE r, in the case of unlifted newtype + -- Used only in H98 case -> ConDecl GhcRn -> TcM () -kcConDecl new_or_data res_kind (ConDeclH98 +kcConDecl new_or_data tc_res_kind (ConDeclH98 { con_name = name, con_ex_tvs = ex_tvs , con_mb_cxt = ex_ctxt, con_args = args }) = addErrCtxt (dataConCtxtName [name]) $ discardResult $ bindExplicitTKBndrs_Tv ex_tvs $ do { _ <- tcHsMbContext ex_ctxt - ; kcConH98Args new_or_data res_kind args + ; kcConH98Args new_or_data tc_res_kind args -- We don't need to check the telescope here, -- because that's done in tcConDecl } -kcConDecl new_or_data res_kind (ConDeclGADT +kcConDecl new_or_data + _tc_res_kind -- Not used in GADT case (and doesn't make sense) + (ConDeclGADT { con_names = names, con_bndrs = L _ outer_bndrs, con_mb_cxt = cxt , con_g_args = args, con_res_ty = res_ty }) - = -- Even though the GADT-style data constructor's type is closed, - -- we must still kind-check the type, because that may influence - -- the inferred kind of the /type/ constructor. Example: - -- data T f a where - -- MkT :: f a -> T f a - -- If we don't look at MkT we won't get the correct kind - -- for the type constructor T + = -- See Note [kcConDecls: kind-checking data type decls] addErrCtxt (dataConCtxtName names) $ discardResult $ bindOuterSigTKBndrs_Tv outer_bndrs $ - -- Why "_Tv"? See Note [Kind-checking for GADTs] + -- Why "_Tv"? See Note [Using TyVarTvs for kind-checking GADTs] do { _ <- tcHsMbContext cxt - ; kcConGADTArgs new_or_data res_kind args - ; _ <- tcHsOpenType res_ty + ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty) + ; con_res_kind <- newOpenTypeKind + ; _ <- tcCheckLHsType res_ty (TheKind con_res_kind) + ; kcConGADTArgs new_or_data con_res_kind args + ; traceTc "kcConDecl:GADT }" (ppr names $$ ppr con_res_kind) ; return () } -{- Note [kcConDecls result kind] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We might have e.g. - data T a :: Type -> Type where ... -or - newtype instance N a :: Type -> Type where .. -in which case, the 'res_kind' passed to kcConDecls will be - Type->Type - -We must look past those arrows, or even foralls, to the Type in the -corner, to pass to kcConDecl c.f. #16828. Hence the splitPiTys here. - -I am a bit concerned about tycons with a declaration like - data T a :: Type -> forall k. k -> Type where ... - -It does not have a CUSK, so kcInferDeclHeader will make a TcTyCon -with tyConResKind of Type -> forall k. k -> Type. Even that is fine: -the splitPiTys will look past the forall. But I'm bothered about -what if the type "in the corner" mentions k? This is incredibly -obscure but something like this could be bad: - data T a :: Type -> foral k. k -> TYPE (F k) where ... - -I bet we are not quite right here, but my brain suffered a buffer -overflow and I thought it best to nail the common cases right now. - -Note [Recursion and promoting data constructors] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We don't want to allow promotion in a strongly connected component -when kind checking. - -Consider: - data T f = K (f (K Any)) - -When kind checking the `data T' declaration the local env contains the -mappings: - T -> ATcTyCon - K -> APromotionErr - -APromotionErr is only used for DataCons, and only used during type checking -in tcTyClGroup. - -Note [Kind-checking for GADTs] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [kcConDecls: kind-checking data type decls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +kcConDecls is used when we are inferring the kind of the type +constructor in a data type declaration. E.g. + data T f a = MkT (f a) +we want to infer the kind of 'f' and 'a'. The basic plan is described +in Note [Inferring kinds for type declarations]; here are doing Step 2. + +In the H98 case, for unlifted newtypes only, we need the result kind of +the TyCon, to unify with the argument kind. The tycon's result kind +is not used at all in the GADT case. + +In the GADT case we may have this: + data T f a where + MkT :: forall g b. g b -> T g b +Notice that the variables f,a, and g,b are quite distinct. +Nevertheless, this decl must still influence the kind T (which is, +remember Step 1, something like T :: kappa1 -> kappa2 -> Type), otherwise +we'd infer the bogus kind T :: forall k1 k2. k1 -> k2 -> Type. + +The data constructor type influences the kind of T simply by +kind-checking the result type (T g b), which will force 'f' and 'g' to +have the same kinds. This is the call to + tcCheckLHsType res_ty (TheKind con_res_kind) +Because this is the result type of an arrow, we know the kind must be +of form (TYPE rr), and we get better error messages if we enforce that +here (e.g. test gadt10). + +Note [Using TyVarTvs for kind-checking GADTs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider data Proxy a where @@ -1708,26 +1683,27 @@ Consider It seems reasonable that this should be accepted. But something very strange is going on here: when we're kind-checking this declaration, we need to unify the kind of `a` with k and j -- even though k and j's scopes are local to the type of -MkProxy{1,2}. The best approach we've come up with is to use TyVarTvs during -the kind-checking pass. First off, note that it's OK if the kind-checking pass -is too permissive: we'll snag the problems in the type-checking pass later. -(This extra permissiveness might happen with something like +MkProxy{1,2}. + +In effect, we are simply gathering constraints on the shape of Proxy's +kind, with no skolemisation or implication constraints involved at all. + +The best approach we've come up with is to use TyVarTvs during the +kind-checking pass, rather than ordinary skolems. This is why we use +the "_Tv" variant, bindOuterSigTKBndrs_Tv. + +Our only goal is to gather constraints on the kind of the type constructor; +we do not certify that the data declaration is well-kinded. For example: data SameKind :: k -> k -> Type data Bad a where MkBad :: forall k1 k2 (a :: k1) (b :: k2). Bad (SameKind a b) -which would be accepted if k1 and k2 were TyVarTvs. This is correctly rejected -in the second pass, though. Test case: polykinds/TyVarTvKinds3) -Recall that the kind-checking pass exists solely to collect constraints -on the kinds and to power unification. - -To achieve the use of TyVarTvs, we must be careful to use specialized functions -that produce TyVarTvs, not ordinary skolems. This is why we need -kcExplicitTKBndrs and kcImplicitTKBndrs in GHC.Tc.Gen.HsType, separate from their -tc... variants. +which would be accepted by kcConDecl because k1 and k2 are +TyVarTvs. It is correctly rejected in the second pass, tcConDecl. +(Test case: polykinds/TyVarTvKinds3) -The drawback of this approach is sometimes it will accept a definition that +One drawback of this approach is sometimes it will accept a definition that a (hypothetical) declarative specification would likely reject. As a general rule, we don't want to allow polymorphic recursion without a CUSK. Indeed, the whole point of CUSKs is to allow polymorphic recursion. Yet, the TyVarTvs @@ -1746,6 +1722,23 @@ be rejected (without a CUSK). However, the accepted definitions are indeed well-kinded and any rejected definitions would be accepted with a CUSK, and so this wrinkle need not cause anyone to lose sleep. +Note [Recursion and promoting data constructors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We don't want to allow promotion in a strongly connected component +when kind checking. + +Consider: + data T f = K (f (K Any)) + +When kind checking the `data T' declaration the local env contains the +mappings: + T -> ATcTyCon + K -> APromotionErr + +APromotionErr is only used for DataCons, and only used during type checking +in tcTyClGroup. + + ************************************************************************ * * \subsection{Type checking} @@ -3214,7 +3207,7 @@ tcConDecl :: KnotTied TyCon -- Representation tycon. Knot-tied! -> ConDecl GhcRn -> TcM [DataCon] -tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs res_kind res_tmpl new_or_data (ConDeclH98 { con_name = lname@(L _ name) , con_ex_tvs = explicit_tkv_nms , con_mb_cxt = hs_ctxt @@ -3224,7 +3217,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Get hold of the existential type variables -- e.g. data T a = forall k (b::k) f. MkT a (f b) - -- Here tmpl_bndrs = {a} + -- Here tc_bndrs = {a} -- hs_qvars = HsQTvs { hsq_implicit = {k} -- , hsq_explicit = {f,b} } @@ -3242,29 +3235,35 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data } - ; let tmpl_tvs = binderVars tmpl_bndrs - ; let fake_ty = mkSpecForAllTys tmpl_tvs $ + ; let tc_tvs = binderVars tc_bndrs + fake_ty = mkSpecForAllTys tc_tvs $ mkInvisForAllTys exp_tvbndrs $ mkPhiTy ctxt $ mkVisFunTys arg_tys $ unitTy -- That type is a lie, of course. (It shouldn't end in ()!) -- And we could construct a proper result type from the info - -- at hand. But the result would mention only the tmpl_tvs, + -- at hand. But the result would mention only the univ_tvs, -- and so it just creates more work to do it right. Really, -- we're only doing this to find the right kind variables to -- quantify over, and this type is fine for that purpose. - -- exp_tvs have explicit, user-written binding sites + -- exp_tvbndrs have explicit, user-written binding sites -- the kvs below are those kind variables entirely unmentioned by the user -- and discovered only by generalization ; kvs <- kindGeneralizeAll fake_ty - ; let skol_tvs = kvs ++ tmpl_tvs + ; let skol_tvs = tc_tvs ++ kvs ++ binderVars exp_tvbndrs ; reportUnsolvedEqualities skol_info skol_tvs tclvl wanted - - -- Zonk to Types + -- The skol_info claims that all the variables are bound + -- by the data constructor decl, whereas actually the + -- univ_tvs are bound by the data type decl itself. It + -- would be better to have a doubly-nested implication. + -- But that just doesn't seem worth it. + -- See test dependent/should_fail/T13780a + + -- Zonk to Types ; (ze, qkvs) <- zonkTyBndrs kvs ; (ze, user_qtvbndrs) <- zonkTyVarBindersX ze exp_tvbndrs ; arg_tys <- zonkScaledTcTypesToTypesX ze arg_tys @@ -3272,15 +3271,13 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Can't print univ_tvs, arg_tys etc, because we are inside the knot here ; traceTc "tcConDecl 2" (ppr name $$ ppr field_lbls) - ; let - univ_tvbs = tyConInvisTVBinders tmpl_bndrs - univ_tvs = binderVars univ_tvbs - ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs - ex_tvs = binderVars ex_tvbs - -- For H98 datatypes, the user-written tyvar binders are precisely - -- the universals followed by the existentials. - -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. - user_tvbs = univ_tvbs ++ ex_tvbs + ; let univ_tvbs = tyConInvisTVBinders tc_bndrs + ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs + ex_tvs = binderVars ex_tvbs + -- For H98 datatypes, the user-written tyvar binders are precisely + -- the universals followed by the existentials. + -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. + user_tvbs = univ_tvbs ++ ex_tvbs ; traceTc "tcConDecl 2" (ppr name) ; is_infix <- tcConIsInfixH98 name hs_args @@ -3288,7 +3285,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data ; fam_envs <- tcGetFamInstEnvs ; dc <- buildDataCon fam_envs name is_infix rep_nm stricts Nothing field_lbls - univ_tvs ex_tvs user_tvbs + tc_tvs ex_tvs user_tvbs [{- no eq_preds -}] ctxt arg_tys res_tmpl rep_tycon tag_map -- NB: we put data_tc, the type constructor gotten from the @@ -3299,7 +3296,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data where skol_info = DataConSkol name -tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs _res_kind res_tmpl new_or_data -- NB: don't use res_kind here, as it's ill-scoped. Instead, -- we get the res_kind by typechecking the result type. (ConDeclGADT { con_names = names @@ -3344,7 +3341,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data ; res_ty <- zonkTcTypeToTypeX ze res_ty ; let (univ_tvs, ex_tvs, tvbndrs', eq_preds, arg_subst) - = rejigConRes tmpl_bndrs res_tmpl tvbndrs res_ty + = rejigConRes tc_bndrs res_tmpl tvbndrs res_ty -- See Note [Checking GADT return types] ctxt' = substTys arg_subst ctxt @@ -3532,9 +3529,9 @@ errors reported in one pass. See #7175, and #10836. -- TI :: forall b1 c1. (b1 ~ c1) => b1 -> :R7T b1 c1 -- In this case orig_res_ty = T (e,e) -rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result type; e.g. - -- data instance T [a] b c ... - -- gives template ([a,b,c], T [a] b c) +rejigConRes :: [KnotTied TyConBinder] -- Template for result type; e.g. + -> KnotTied Type -- data instance T [a] b c ... + -- gives template ([a,b,c], T [a] b c) -> [InvisTVBinder] -- The constructor's type variables (both inferred and user-written) -> KnotTied Type -- res_ty -> ([TyVar], -- Universal @@ -3546,10 +3543,10 @@ rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result -- We don't check that the TyCon given in the ResTy is -- the same as the parent tycon, because checkValidDataCon will do it -- NB: All arguments may potentially be knot-tied -rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty +rejigConRes tc_tvbndrs res_tmpl dc_tvbndrs res_ty -- E.g. data T [a] b c where -- MkT :: forall x y z. T [(x,y)] z z - -- The {a,b,c} are the tmpl_tvs, and the {x,y,z} are the dc_tvs + -- The {a,b,c} are the tc_tvs, and the {x,y,z} are the dc_tvs -- (NB: unlike the H98 case, the dc_tvs are not all existential) -- Then we generate -- Univ tyvars Eq-spec @@ -3564,7 +3561,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- , [], [x,y,z] -- , [a~(x,y),b~z], ) | Just subst <- tcMatchTy res_tmpl res_ty - = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tmpl_tvs dc_tvs subst + = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tc_tvs dc_tvs subst raw_ex_tvs = dc_tvs `minusList` univ_tvs (arg_subst, substed_ex_tvs) = substTyVarBndrs kind_subst raw_ex_tvs @@ -3591,10 +3588,10 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- albeit bogus, relying on checkValidDataCon to check the -- bad-result-type error before seeing that the other fields look odd -- See Note [Checking GADT return types] - = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, dc_tvbndrs, [], emptyTCvSubst) + = (tc_tvs, dc_tvs `minusList` tc_tvs, dc_tvbndrs, [], emptyTCvSubst) where - dc_tvs = binderVars dc_tvbndrs - tmpl_tvs = binderVars tmpl_bndrs + dc_tvs = binderVars dc_tvbndrs + tc_tvs = binderVars tc_tvbndrs {- Note [mkGADTVars] ~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -688,9 +688,8 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env -- Do /not/ check that the number of patterns = tyConArity fam_tc -- See [Arity of data families] in GHC.Core.FamInstEnv ; (qtvs, pats, res_kind, stupid_theta) - <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs - fixity hs_ctxt hs_pats m_ksig hs_cons - new_or_data + <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity + hs_ctxt hs_pats m_ksig new_or_data -- Eta-reduce the axiom if possible -- Quite tricky: see Note [Implementing eta reduction for data families] @@ -857,7 +856,7 @@ TyVarEnv will simply be empty, and there is nothing to worry about. tcDataFamInstHeader :: AssocInstInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn -> LexicalFixity -> LHsContext GhcRn - -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> [LConDecl GhcRn] + -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> NewOrData -> TcM ([TyVar], [Type], Kind, ThetaType) -- The "header" of a data family instance is the part other than @@ -865,7 +864,7 @@ tcDataFamInstHeader -- e.g. data instance D [a] :: * -> * where ... -- Here the "header" is the bit before the "where" tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity - hs_ctxt hs_pats m_ksig hs_cons new_or_data + hs_ctxt hs_pats m_ksig new_or_data = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (scoped_tvs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ @@ -884,8 +883,8 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity -- Add constraints from the result signature ; res_kind <- tc_kind_sig m_ksig - -- Add constraints from the data constructors - ; kcConDecls new_or_data res_kind hs_cons + -- Do not add constraints from the data constructors + -- See Note [Kind inference for data family instances] -- Check that the result kind of the TyCon applied to its args -- is compatible with the explicit signature (or Type, if there @@ -1049,6 +1048,86 @@ however, so this Note aims to describe these subtleties: themselves. Heavy sigh. But not truly hard; that's what tcbVisibilities does. +Note [Kind inference for data family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this GADT-style data type declaration, where I have used +fresh variables in the data constructor's type, to stress that c,d are +quite distinct from a,b. + data T a b where + MkT :: forall c d. c d -> T c d + +Following Note [Inferring kinds for type declarations] in GHC.Tc.TyCl, +to infer T's kind, we initially give T :: kappa, a monomorpic kind, +gather constraints from the header and data constructors, and conclude + T :: (kappa1 -> type) -> kappa1 -> Type +Then we generalise, giving + T :: forall k. (k->Type) -> k -> Type + +Now what about a data /instance/ decl + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p Int where ... + +No doubt here! The poly-kinded T is instantiated with k=Type, so the +header really looks like + data instance T @Type (p :: Type->Type) Int where ... + +But what about this? + data instance T p q where + MkT :: forall r. r Int -> T r Int + +So what kind do 'p' and 'q' have? No clues from the header, but from +the data constructor we can clearly see that (r :: Type->Type). Does +that mean that the the /entire data instance/ is instantiated at Type, +like this? + data instance T @Type (p :: Type->Type) (q :: Type) where + ... + +Not at all! This is a /GADT/-style decl, so the kind argument might +be specialised in this particular data constructor, thus: + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall (r :: Type -> Type). + r Int -> T @Type r Int +(and perhaps specialised differently in some other data +constructor MkT2). + +The key difference in this case and 'data T' at the top of this Note +is that we have no known kind for 'data T'. We thus forbid different +specialisations of T in its constructors, in an attempt to avoid +inferring polymorphic recursion. In data family T, however, there is +no problem with polymorphic recursion: we already /fully know/ T's +kind -- that came from the family declaration, and is not influenced +by the data instances -- and hence we /can/ specialise T's kind +differently in different GADT data constructors. + +SHORT SUMMARY: in a data instance decl, it's not clear whether kind +constraints arising from the data constructors should be considered +local to the (GADT) data /constructor/ or should apply to the entire +data instance. + +DESIGN CHOICE: in data/newtype family instance declarations, we ignore +the /data constructor/ declarations altogether, looking only at the +data instance /header/. + +Observations: +* This choice is simple to describe, as well as simple to implment. + For a data/newtype instance decl, the instance kinds are influenced + /only/ by the header. + +* We could treat Haskell-98 style data-instance decls differently, by + taking the data constructors into account, since there are no GADT + issues. But we don't, for simplicity, and becuase it means you can + understand the data type instance by looking only at the header. + +* Newtypes can be declared in GADT syntax, but they can't do GADT-style + specialisation, so like Haskell-98 definitions we could take the + data constructors into account. Again we don't, for the same reason. + +So for now at least, we keep the simplest choice. See #18891 and !4419 +for more discussion of this issue. + +Kind inference for data types (Xie et al) https://arxiv.org/abs/1911.06153 +takes a slightly different approach. -} ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,12 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- Kind inference for data/newtype instance declarations is sligtly + more restrictive than before. See the user manual "Kind inference + for data/newtype instance declarations". This is a breaking change, albeit + a fairly obscure one that corrects a specification bug. + + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/exts/poly_kinds.rst ===================================== @@ -130,8 +130,45 @@ This rule has occasionally-surprising consequences (see The kind-polymorphism from the class declaration makes ``D1`` kind-polymorphic, but not so ``D2``; and similarly ``F1``, ``F2``. +Kind inference in type signatures +--------------------------------- + +When kind-checking a type, GHC considers only what is written in that +type when figuring out how to generalise the type's kind. + +For example, +consider these definitions (with :extension:`ScopedTypeVariables`): :: + + data Proxy a -- Proxy :: forall k. k -> Type + p :: forall a. Proxy a + p = Proxy :: Proxy (a :: Type) + +GHC reports an error, saying that the kind of ``a`` should be a kind variable +``k``, not ``Type``. This is because, by looking at the type signature +``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not +restricted to be ``Type``. The function definition is then rejected for being +more specific than its type signature. + +.. _explicit-kind-quantification: + +Explicit kind quantification +---------------------------- + +Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, +as in these examples: :: + + data Proxy :: forall k. k -> Type + f :: (forall k (a :: k). Proxy a -> ()) -> Int + +Note that the second example has a ``forall`` that binds both a kind ``k`` and +a type variable ``a`` of kind ``k``. In general, there is no limit to how +deeply nested this sort of dependency can work. However, the dependency must +be well-scoped: ``forall (a :: k) k. ...`` is an error. + + .. _inferring-variable-order: + Inferring the order of variables in a type/class declaration ------------------------------------------------------------ @@ -490,41 +527,89 @@ This also applies to GADT-style data instances: :: -- • In the data instance declaration for ‘T’ -Kind inference in closed type families --------------------------------------- +Kind inference in data type declarations +---------------------------------------- -Although all open type families are considered to have a complete -user-supplied kind signature, we can relax this condition for closed -type families, where we have equations on which to perform kind -inference. GHC will infer kinds for the arguments and result types of a -closed type family. +Consider the declaration :: -GHC supports *kind-indexed* type families, where the family matches both -on the kind and type. GHC will *not* infer this behaviour without a -complete user-supplied kind signature, as doing so would sometimes infer -non-principal types. Indeed, we can see kind-indexing as a form -of polymorphic recursion, where a type is used at a kind other than -its most general in its own definition. + data T1 f a = MkT1 (f a) + data T2 f a where + MkT2 :: f a -> T f a -For example: :: +In both cases GHC looks at the data constructor declarations to +give constraints on the kind of ``T``, yielding :: - type family F1 a where - F1 True = False - F1 False = True - F1 x = x - -- F1 fails to compile: kind-indexing is not inferred + T1, T2 :: forall k. (k -> Type) -> k -> Type - type family F2 (a :: k) where - F2 True = False - F2 False = True - F2 x = x - -- F2 fails to compile: no complete signature +Consider the type :: + + data G (a :: k) where + GInt :: G Int + GMaybe :: G Maybe + +This datatype ``G`` is GADT-like in both its kind and its type. Suppose you +have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that +``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and +``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` +be in effect, but pattern-matching on ``G`` requires no extension beyond +:extension:`GADTs`. That this works is actually a straightforward extension +of regular GADTs and a consequence of the fact that kinds and types are the +same. + +Note that the datatype ``G`` is used at different kinds in its body, and +therefore that kind-indexed GADTs use a form of polymorphic recursion. +It is thus only possible to use this feature if you have provided a +complete user-supplied kind signature (CUSK) +for the datatype (:ref:`complete-kind-signatures`), or a standalone +kind signature (:ref:`standalone-kind-signatures`); +in the case of ``G`` we have a CUSK. +If you wish to see the kind indexing explicitly, you can do so by enabling :ghc-flag:`-fprint-explicit-kinds` and querying ``G`` with GHCi's :ghci-cmd:`:info` command: :: + + > :set -fprint-explicit-kinds + > :info G + type role G nominal nominal + type G :: forall k. k -> Type + data G @k a where + GInt :: G @Type Int + GMaybe :: G @(Type -> Type) Maybe + +where you can see the GADT-like nature of the two constructors. + +Kind inference for data/newtype instance declarations +----------------------------------------------------- + +Consider these declarations :: + + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p q where + MkT :: forall r. r Int -> T r Int + +Here ``T`` has an invisible kind argument; and perhaps it is instantiated +to ``Type`` in the instance, thus :: + + data instance T @Type (p :: Type->Type) (q :: Type) where + MkT :: forall r. r Int -> T r Int + +Or perhaps we intended the specialisation to be in the GADT data +constructor, thus :: + + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall r. r Int -> T @Type r Int + +It gets more complicated if there are multiple constructors. In +general, there is no principled way to tell which type specialisation +comes from the data instance, and which from the individual GADT data +constructors. + +So GHC implements this rule: in data/newtype instance declararations +(unlike ordinary data/newtype declarations) we do *not* look at the +constructor declarations when inferring the shape of the instance +header. The principle is that *the instantiation of the data instance +should be apparent from the header alone*. This principle makes the +program easier to understand, and avoids the swamp of complexity +indicated above. - type family F3 (a :: k) :: k where - F3 True = False - F3 False = True - F3 x = x - -- OK Kind inference in class instance declarations --------------------------------------------- @@ -555,43 +640,8 @@ infrastructure, and it's not clear the payoff is worth it. If you want to restrict ``b``\ 's kind in the instance above, just use a kind signature in the instance head. -Kind inference in type signatures ---------------------------------- - -When kind-checking a type, GHC considers only what is written in that -type when figuring out how to generalise the type's kind. - -For example, -consider these definitions (with :extension:`ScopedTypeVariables`): :: - - data Proxy a -- Proxy :: forall k. k -> Type - p :: forall a. Proxy a - p = Proxy :: Proxy (a :: Type) - -GHC reports an error, saying that the kind of ``a`` should be a kind variable -``k``, not ``Type``. This is because, by looking at the type signature -``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not -restricted to be ``Type``. The function definition is then rejected for being -more specific than its type signature. - -.. _explicit-kind-quantification: - -Explicit kind quantification ----------------------------- - -Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, -as in these examples: :: - - data Proxy :: forall k. k -> Type - f :: (forall k (a :: k). Proxy a -> ()) -> Int - -Note that the second example has a ``forall`` that binds both a kind ``k`` and -a type variable ``a`` of kind ``k``. In general, there is no limit to how -deeply nested this sort of dependency can work. However, the dependency must -be well-scoped: ``forall (a :: k) k. ...`` is an error. - -Implicit quantification in type synonyms and type family instances ------------------------------------------------------------------- +Kind inference in type synonyms and type family instances +--------------------------------------------------------- Consider the scoping rules for type synonyms and type family instances, such as these:: @@ -706,29 +756,44 @@ kinds. Consequently, visible dependent quantifiers are rejected in any context that is unambiguously the type of a term. They are also rejected in the types of data constructors. -Kind-indexed GADTs ------------------- +Kind inference in closed type families +-------------------------------------- + +Although all open type families are considered to have a complete +user-supplied kind signature (:ref:`complete-kind-signatures`), +we can relax this condition for closed +type families, where we have equations on which to perform kind +inference. GHC will infer kinds for the arguments and result types of a +closed type family. -Consider the type :: +GHC supports *kind-indexed* type families, where the family matches both +on the kind and type. GHC will *not* infer this behaviour without a +complete user-supplied kind signature or standalone kind +signature (see :ref:`standalone-kind-signatures`), +because doing so would sometimes infer +non-principal types. Indeed, we can see kind-indexing as a form +of polymorphic recursion, where a type is used at a kind other than +its most general in its own definition. - data G (a :: k) where - GInt :: G Int - GMaybe :: G Maybe +For example: :: -This datatype ``G`` is GADT-like in both its kind and its type. Suppose you -have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that -``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and -``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` -be in effect, but pattern-matching on ``G`` requires no extension beyond -:extension:`GADTs`. That this works is actually a straightforward extension -of regular GADTs and a consequence of the fact that kinds and types are the -same. + type family F1 a where + F1 True = False + F1 False = True + F1 x = x + -- F1 fails to compile: kind-indexing is not inferred -Note that the datatype ``G`` is used at different kinds in its body, and -therefore that kind-indexed GADTs use a form of polymorphic recursion. -It is thus only possible to use this feature if you have provided a -complete user-supplied kind signature -for the datatype (:ref:`complete-kind-signatures`). + type family F2 (a :: k) where + F2 True = False + F2 False = True + F2 x = x + -- F2 fails to compile: no complete signature + + type family F3 (a :: k) :: k where + F3 True = False + F3 False = True + F3 x = x + -- OK Higher-rank kinds ----------------- ===================================== testsuite/tests/dependent/should_fail/T13780a.stderr ===================================== @@ -3,7 +3,7 @@ T13780a.hs:9:40: error: • Couldn't match kind ‘a’ with ‘Bool’ Expected kind ‘Foo a’, but ‘MkFoo’ has kind ‘Foo Bool’ ‘a’ is a rigid type variable bound by - a family instance declaration + the data constructor ‘SMkFoo’ at T13780a.hs:9:20-31 • In the second argument of ‘(~)’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ ===================================== testsuite/tests/deriving/should_compile/T11416.hs ===================================== @@ -12,9 +12,11 @@ newtype T f (a :: ConstantT Type f) = T (f a) deriving Functor data family TFam1 (f :: k1) (a :: k2) -newtype instance TFam1 f (ConstantT a f) = TFam1 (f a) +newtype instance TFam1 (f :: k -> Type) (ConstantT (a :: k) f) + = TFam1 (f a) deriving Functor data family TFam2 (f :: k1) (a :: k2) -newtype instance TFam2 f (a :: ConstantT Type f) = TFam2 (f a) +newtype instance TFam2 (f :: Type -> Type) (a :: ConstantT Type f) + = TFam2 (f a) deriving Functor ===================================== testsuite/tests/patsyn/should_fail/T15685.stderr ===================================== @@ -1,13 +1,13 @@ T15685.hs:13:24: error: - • Could not deduce: a ~ [k0] - from the context: as ~ (a1 : as1) + • Could not deduce: k ~ [k0] + from the context: as ~ (a : as1) bound by a pattern with constructor: - Here :: forall {a1} (f :: a1 -> *) (a2 :: a1) (as :: [a1]). - f a2 -> NS f (a2 : as), + Here :: forall {k} (f :: k -> *) (a :: k) (as :: [k]). + f a -> NS f (a : as), in a pattern synonym declaration at T15685.hs:13:19-26 - ‘a’ is a rigid type variable bound by + ‘k’ is a rigid type variable bound by the inferred type of HereNil :: NS f as at T15685.hs:13:9-15 Possible fix: add a type signature for ‘HereNil’ ===================================== testsuite/tests/polykinds/T13659.stderr ===================================== @@ -1,6 +1,6 @@ -T13659.hs:14:27: error: - • Expected a type, but ‘a’ has kind ‘[*]’ - • In the first argument of ‘Format’, namely ‘'[Int, a]’ - In the type ‘Format '[Int, a]’ +T13659.hs:14:15: error: + • Expected kind ‘[*]’, but ‘a’ has kind ‘*’ + • In the first argument of ‘Format’, namely ‘a’ + In the type ‘Format a’ In the definition of data constructor ‘I’ ===================================== testsuite/tests/polykinds/T16221a.stderr ===================================== @@ -1,7 +1,7 @@ T16221a.hs:6:49: error: - • Expected kind ‘k’, but ‘b’ has kind ‘k1’ - ‘k1’ is a rigid type variable bound by + • Expected kind ‘k’, but ‘b’ has kind ‘k2’ + ‘k2’ is a rigid type variable bound by an explicit forall k (b :: k) at T16221a.hs:6:20 ‘k’ is a rigid type variable bound by ===================================== testsuite/tests/th/T9692.hs ===================================== @@ -12,7 +12,7 @@ class C a where data F a (b :: k) :: Type instance C Int where - data F Int x = FInt x + data F Int (x :: Type) = FInt x $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info ===================================== testsuite/tests/typecheck/should_compile/T18891.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +data family T2 (a :: k) +data instance T2 a where + MkT2 :: T2 Maybe + +newtype N3 :: forall k -> TYPE k where + MkN3 :: N3 m -> N3 m + +type N4 :: forall k -> TYPE k +newtype N4 :: forall k -> TYPE k where + MkN4 :: N4 m -> N4 m ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs ===================================== @@ -4,6 +4,8 @@ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} module UnliftedNewtypesUnassociatedFamily where @@ -20,7 +22,16 @@ newtype instance DFT ('TupleRep '[ 'IntRep, 'WordRep]) data instance DFT 'LiftedRep = MkDFT4 | MkDFT5 data family DF :: TYPE (r :: RuntimeRep) -newtype instance DF = MkDF1 Int# -newtype instance DF = MkDF2 Word# -newtype instance DF = MkDF3 (# Int#, Word# #) + +-- Use a type application +newtype instance DF @IntRep = MkDF1 Int# + +-- Use a kind signature +newtype instance DF :: TYPE 'WordRep where + MkDF2 :: Word# -> DF + +-- Also uses a kind signature +newtype instance DF :: TYPE ('TupleRep '[ 'IntRep, 'WordRep ]) where + MkDF3 :: (# Int#, Word# #) -> DF + data instance DF = MkDF4 | MkDF5 ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs ===================================== @@ -10,14 +10,14 @@ module UnliftedNewtypesUnassociatedFamily where import GHC.Int (Int(I#)) -import GHC.Exts (Int#,Word#,RuntimeRep(IntRep)) +import GHC.Exts (Int#,Word#,RuntimeRep(IntRep, WordRep)) import GHC.Exts (TYPE) type KindOf (a :: TYPE k) = k data family D (a :: TYPE r) :: TYPE r -newtype instance D a = MkWordD Word# +newtype instance D (a :: TYPE 'WordRep) = MkWordD Word# -newtype instance D a :: TYPE (KindOf a) where - MkIntD :: forall (a :: TYPE 'IntRep). Int# -> D a +newtype instance D (a :: TYPE 'IntRep) :: TYPE (KindOf a) where + MkIntD :: forall (b :: TYPE 'IntRep). Int# -> D b ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,5 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) +test('T18891', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T18891a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +newtype N1 :: forall k. TYPE k where + MkN1 :: N1 -> N1 + +type N2 :: forall k. TYPE k +newtype N2 :: forall k. TYPE k where + MkN2 :: N2 -> N2 + ===================================== testsuite/tests/typecheck/should_fail/T18891a.stderr ===================================== @@ -0,0 +1,12 @@ + +T18891a.hs:8:4: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN1 :: N1 -> N1 + • In the definition of data constructor ‘MkN1’ + In the newtype declaration for ‘N1’ + +T18891a.hs:12:3: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN2 :: N2 -> N2 + • In the definition of data constructor ‘MkN2’ + In the newtype declaration for ‘N2’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr ===================================== @@ -1,11 +1,5 @@ -UnliftedNewtypesFamilyKindFail2.hs:12:20: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the newtype instance declaration for ‘F’ - -UnliftedNewtypesFamilyKindFail2.hs:12:31: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the type ‘(F 5)’ - In the definition of data constructor ‘MkF’ +UnliftedNewtypesFamilyKindFail2.hs:12:20: error: + • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ + • In the first argument of ‘F’, namely ‘5’ + In the newtype instance declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} + +module UnliftedNewtypesUnassociatedFamily where + +import GHC.Int (Int(I#)) +import GHC.Word (Word(W#)) +import GHC.Exts (Int#,Word#) +import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep)) + +data family DF :: TYPE (r :: RuntimeRep) + +-- All these fail: see #18891 and !4419 +-- See Note [Kind inference for data family instances] +-- in GHC.Tc.TyCl.Instance +newtype instance DF = MkDF1a Int# +newtype instance DF = MkDF2a Word# +newtype instance DF = MkDF3a (# Int#, Word# #) ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr ===================================== @@ -0,0 +1,18 @@ + +UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error: + • Expecting a lifted type, but ‘Int#’ is unlifted + • In the type ‘Int#’ + In the definition of data constructor ‘MkDF1a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error: + • Expecting a lifted type, but ‘Word#’ is unlifted + • In the type ‘Word#’ + In the definition of data constructor ‘MkDF2a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error: + • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted + • In the type ‘(# Int#, Word# #)’ + In the definition of data constructor ‘MkDF3a’ + In the newtype instance declaration for ‘DF’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKind', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, ['']) test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, ['']) +test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, ['']) test('T13834', normal, compile_fail, ['']) test('T17077', normal, compile_fail, ['']) test('T16512a', normal, compile_fail, ['']) @@ -589,3 +590,4 @@ test('T18640b', normal, compile_fail, ['']) test('T18640c', normal, compile_fail, ['']) test('T10709', normal, compile_fail, ['']) test('T10709b', normal, compile_fail, ['']) +test('T18891a', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7fabe2937d3815887a9bf6038289f2811442707d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7fabe2937d3815887a9bf6038289f2811442707d 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 Wed Nov 25 16:17:52 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 25 Nov 2020 11:17:52 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] Fix and enable object unloading in GHCi Message-ID: <5fbe83b055624_86c111d4a0020703c@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 58ed8da7 by Ömer Sinan Ağacan at 2020-11-25T11:17:21-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 25 changed files: - compiler/ghci/Linker.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsStartup.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/linker_error.c Changes: ===================================== compiler/ghci/Linker.hs ===================================== @@ -1134,14 +1134,15 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do where unloadObjs :: Linkable -> IO () unloadObjs lnk + -- The RTS's PEi386 linker currently doesn't support unloading. + | isWindowsHost = return () + | dynamicGhc = return () -- We don't do any cleanup when linking objects with the -- dynamic linker. Doing so introduces extra complexity for -- not much benefit. - -- Code unloading currently disabled due to instability. - -- See #16841. - | False -- otherwise + | otherwise = mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk] -- The components of a BCO linkable may contain -- dot-o files. Which is very confusing. @@ -1149,7 +1150,6 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do -- But the BCO parts can be unlinked just by -- letting go of them (plus of course depopulating -- the symbol table which is done in the main body) - | otherwise = return () -- see #16841 {- ********************************************************************** ===================================== rts/CheckUnload.c ===================================== @@ -17,43 +17,99 @@ #include "CheckUnload.h" #include "sm/Storage.h" #include "sm/GCThread.h" +#include "sm/HeapUtils.h" // -// Code that we unload may be referenced from: -// - info pointers in heap objects and stack frames -// - pointers to static objects from the heap -// - StablePtrs to static objects -// - pointers to cost centres from the cost centre tree +// Note [Object unloading] +// ~~~~~~~~~~~~~~~~~~~~~~~ // -// We can find live static objects after a major GC, so we don't have -// to look at every closure pointer in the heap. However, we do have -// to look at every info pointer. So this is like a heap census -// traversal: we look at the header of every object, but not its -// contents. +// Overview of object unloading: // -// On the assumption that there aren't many different info pointers in -// a typical heap, we insert addresses into a hash table. The -// first time we see an address, we check it against the pending -// unloadable objects and if it lies within any of them, we mark that -// object as referenced so that it won't get unloaded in this round. +// - In a major GC, for every static object we mark the object's object code and +// its dependencies as 'live'. This is done by `markObjectCode`, called by +// `evacuate`. // - -// Note [Speeding up checkUnload] -// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -// In certain circumstances, there may be a lot of unloaded ObjectCode structs -// chained in `unloaded_objects` (such as when users `:load` a module in a very -// big repo in GHCi). To speed up checking whether an address lies within any of -// these objects, we populate the addresses of their mapped sections in -// an array sorted by their `start` address and do binary search for our address -// on that array. Note that this works because the sections are mapped to mutual -// exclusive memory regions, so we can simply find the largest lower bound among -// the `start` addresses of the sections and then check if our address is inside -// that section. In particular, we store the start address and end address of -// each mapped section in a OCSectionIndex, arrange them all on a contiguous -// memory range and then sort by start address. We then put this array in an -// OCSectionIndices struct to be passed into `checkAddress` to do binary search -// on. +// - Marking object code is done using a global "section index table" +// (global_s_indices below). When we load an object code we add its section +// indices to the table. `markObjectCode` does binary search on this table to +// find object code for the marked object, and mark it and its dependencies. +// +// Dependency of an object code is simply other object code that the object +// code refers to in its code. We know these dependencies by the relocations +// present in the referent. This is recorded by lookupSymbolDependent. +// +// - global_s_indices is updated as we load and unload objects. When we load an +// object code we add its section indices to the table, we remove those +// indices when we unload. +// +// The table is sorted and old indices are removed in `checkUnload`, instead +// on every load/unload, to avoid quadratic behavior when we load a list of +// objects. +// +// - After a major GC `checkUnload` unloads objects that are (1) explicitly +// asked for unloading (via `unloadObj`) and (2) are not marked during GC. +// +// Note that, crucially, we don't unload an object code even if it's not +// reachable from the heap, unless it's explicitly asked for unloading (via +// `unloadObj`). This is a feature and not a but! Two use cases: +// +// - The user might request a symbol from a loaded object at any point with +// lookupSymbol (e.g. GHCi might do this). +// +// - Sometimes we load objects that are not Haskell objects. +// +// To avoid unloading objects that are unreachable but are not asked for +// unloading we maintain a "root set" of object code, `loaded_objects` below. +// `loadObj` adds the loaded objects (and its dependencies) to the list. +// `unloadObj` removes. After a major GC, `checkUnload` first marks the root set +// (`loaded_objects`) to avoid unloading objects that are not asked for +// unloading. +// +// Two other lists `objects` and `old_objects` are similar to large object lists +// in GC. Before a major GC we move `objects` to `old_objects`, and move marked +// objects back to `objects` during evacuation and when marking roots in +// `checkUnload`. Any objects in `old_objects` after that is unloaded. +// +// TODO: We currently don't unload objects when non-moving GC is enabled. The +// implementation would be similar to `nonmovingGcCafs`: +// +// - Maintain a "snapshot": +// +// - Copy `loaded_objects` as the root set of the snapshot +// +// - Stash `objects` to `old_objects` as the snapshot. We don't need a new +// list for this as `old_objects` won't be used by any other code when +// non-moving GC is enabled. +// +// - Copy `global_s_indices` table to be able to mark objects while mutators +// call `loadObj_` and `unloadObj_` concurrently. +// +// - Don't mark object code in `evacuate`, marking will be done in the +// non-moving collector. // +// - After preparation, bump the object code mark bit (`object_code_mark_bit` +// below) and mark static objects using a version of `markObjectCode` that +// basically does the same thing but: +// +// - Needs to update `objects` list in a thread-safe way, as mutators will be +// concurrently calling `loadObj_` and add new stuff to `objects`. +// (alternatively we could have a new list for non-moving GC's objects list, +// and then merge it to the global list in the pause before moving to +// concurrent sweep phase) +// +// - Needs to use the copied `global_s_indices` +// +// - After marking anything left in `old_objects` are unreachable objects within +// the snapshot, unload those. The unload loop will be the same as in +// `checkUnload`. This step needs to happen in the final sync (before sweep +// begins) to avoid races when updating `global_s_indices`. +// +// - NOTE: We don't need write barriers in loadObj/unloadObj as we don't +// introduce a dependency from an already-loaded object to a newly loaded +// object and we don't delete existing dependencies. +// + +uint8_t object_code_mark_bit = 0; typedef struct { W_ start; @@ -62,20 +118,85 @@ typedef struct { } OCSectionIndex; typedef struct { + int capacity; // Doubled on resize int n_sections; + bool sorted; // Invalidated on insertion. Sorted in checkUnload. + bool unloaded; // Whether we removed anything from the table in + // removeOCSectionIndices. If this is set we "compact" the + // table (remove unused entries) in `sortOCSectionIndices. OCSectionIndex *indices; } OCSectionIndices; -static OCSectionIndices *createOCSectionIndices(int n_sections) +// List of currently live objects. Moved to `old_objects` before unload check. +// Marked objects moved back to this list in `markObjectLive`. Remaining objects +// are freed at the end of `checkUnload`. +// +// Double-linked list to be able to remove marked objects. List formed with +// `next` and `prev` fields of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *objects = NULL; + +// `objects` list is moved here before unload check. Marked objects are moved +// back to `objects`. Remaining objects are freed. +static ObjectCode *old_objects = NULL; + +// Number of objects that we want to unload. When this value is 0 we skip static +// object marking during GC and `checkUnload`. +// +// Not static: we use this value to skip static object marking in evacuate when +// this is 0. +// +// Incremented in `unloadObj_`, decremented as we unload objects in +// `checkUnload`. +int n_unloaded_objects = 0; + +// List of objects that we don't want to unload (i.e. we haven't called +// unloadObj on these yet). Used as root set for unload check in checkUnload. +// Objects are added with loadObj_ and removed with unloadObj_. +// +// List formed with `next_loaded_object` field of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *loaded_objects; + +// Section index table for currently loaded objects. New indices are added by +// `loadObj_`, indices of unloaded objects are removed in `checkUnload`. Used to +// map static closures to their ObjectCode. +static OCSectionIndices *global_s_indices = NULL; + +static OCSectionIndices *createOCSectionIndices(void) { - OCSectionIndices *s_indices; - s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); - s_indices->n_sections = n_sections; - s_indices->indices = stgMallocBytes(n_sections*sizeof(OCSectionIndex), + // TODO (osa): Maybe initialize as empty (without allocation) and allocate + // on first insertion? + OCSectionIndices *s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); + int capacity = 1024; + s_indices->capacity = capacity; + s_indices->n_sections = 0; + s_indices->sorted = true; + s_indices->unloaded = false; + s_indices->indices = stgMallocBytes(capacity * sizeof(OCSectionIndex), "OCSectionIndices::indices"); return s_indices; } +static void freeOCSectionIndices(OCSectionIndices *s_indices) +{ + free(s_indices->indices); + free(s_indices); +} + +void initUnloadCheck() +{ + global_s_indices = createOCSectionIndices(); +} + +void exitUnloadCheck() +{ + freeOCSectionIndices(global_s_indices); + global_s_indices = NULL; +} + static int cmpSectionIndex(const void* indexa, const void *indexb) { W_ s1 = ((OCSectionIndex*)indexa)->start; @@ -88,44 +209,124 @@ static int cmpSectionIndex(const void* indexa, const void *indexb) return 0; } -static OCSectionIndices* buildOCSectionIndices(ObjectCode *ocs) +static void reserveOCSectionIndices(OCSectionIndices *s_indices, int len) { - int cnt_sections = 0; - ObjectCode *oc; - for (oc = ocs; oc; oc = oc->next) { - cnt_sections += oc->n_sections; + int current_capacity = s_indices->capacity; + int current_len = s_indices->n_sections; + if (current_capacity - current_len >= len) { + return; + } + + // Round up to nearest power of 2 + int new_capacity = 1 << (int)ceil(log2(current_len + len)); + + OCSectionIndex *old_indices = s_indices->indices; + OCSectionIndex *new_indices = stgMallocBytes(new_capacity * sizeof(OCSectionIndex), + "reserveOCSectionIndices"); + + for (int i = 0; i < current_len; ++i) { + new_indices[i] = old_indices[i]; } - OCSectionIndices* s_indices = createOCSectionIndices(cnt_sections); - int s_i = 0, i; - for (oc = ocs; oc; oc = oc->next) { - for (i = 0; i < oc->n_sections; i++) { - if (oc->sections[i].kind != SECTIONKIND_OTHER) { - s_indices->indices[s_i].start = (W_)oc->sections[i].start; - s_indices->indices[s_i].end = (W_)oc->sections[i].start - + oc->sections[i].size; - s_indices->indices[s_i].oc = oc; - s_i++; + + s_indices->capacity = new_capacity; + s_indices->indices = new_indices; + + free(old_indices); +} + +// Insert object section indices of a single ObjectCode. Invalidates 'sorted' +// state. +void insertOCSectionIndices(ObjectCode *oc) +{ + reserveOCSectionIndices(global_s_indices, oc->n_sections); + global_s_indices->sorted = false; + + int s_i = global_s_indices->n_sections; + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + global_s_indices->indices[s_i].start = (W_)oc->sections[i].start; + global_s_indices->indices[s_i].end = (W_)oc->sections[i].start + + oc->sections[i].size; + global_s_indices->indices[s_i].oc = oc; + s_i++; + } + } + + global_s_indices->n_sections = s_i; + + // Add object to 'objects' list + if (objects != NULL) { + objects->prev = oc; + } + oc->next = objects; + objects = oc; +} + +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr); + +static void removeOCSectionIndices(OCSectionIndices *s_indices, ObjectCode *oc) +{ + // To avoid quadratic behavior in checkUnload we set `oc` fields of indices + // of unloaded objects NULL here. Removing unused entries is done in + // `sortOCSectionIndices`. + + s_indices->unloaded = true; + + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + int section_idx = findSectionIdx(s_indices, oc->sections[i].start); + if (section_idx != -1) { + s_indices->indices[section_idx].oc = NULL; } } } - s_indices->n_sections = s_i; +} + +static void sortOCSectionIndices(OCSectionIndices *s_indices) { + if (s_indices->sorted) { + return; + } + qsort(s_indices->indices, s_indices->n_sections, sizeof(OCSectionIndex), cmpSectionIndex); - return s_indices; + + s_indices->sorted = true; } -static void freeOCSectionIndices(OCSectionIndices *section_indices) -{ - free(section_indices->indices); - free(section_indices); +static void removeRemovedOCSections(OCSectionIndices *s_indices) { + if (!s_indices->unloaded) { + return; + } + + int next_free_idx = 0; + for (int i = 0; i < s_indices->n_sections; ++i) { + if (s_indices->indices[i].oc == NULL) { + // free entry, skip + } else if (i == next_free_idx) { + ++next_free_idx; + } else { + s_indices->indices[next_free_idx] = s_indices->indices[i]; + ++next_free_idx; + } + } + + s_indices->n_sections = next_free_idx; + s_indices->unloaded = true; } -static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { +// Returns -1 if not found +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr) { + ASSERT(s_indices->sorted); + W_ w_addr = (W_)addr; - if (s_indices->n_sections <= 0) return NULL; - if (w_addr < s_indices->indices[0].start) return NULL; + if (s_indices->n_sections <= 0) { + return -1; + } + if (w_addr < s_indices->indices[0].start) { + return -1; + } int left = 0, right = s_indices->n_sections; while (left + 1 < right) { @@ -139,330 +340,125 @@ static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { } ASSERT(w_addr >= s_indices->indices[left].start); if (w_addr < s_indices->indices[left].end) { - return s_indices->indices[left].oc; + return left; } - return NULL; + return -1; } -static void checkAddress (HashTable *addrs, const void *addr, - OCSectionIndices *s_indices) -{ - ObjectCode *oc; - - if (!lookupHashTable(addrs, (W_)addr)) { - insertHashTable(addrs, (W_)addr, addr); +static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { + int oc_idx = findSectionIdx(s_indices, addr); - oc = findOC(s_indices, addr); - if (oc != NULL) { - oc->referenced = 1; - return; - } + if (oc_idx == -1) { + return NULL; } + + return s_indices->indices[oc_idx].oc; } -static void searchStackChunk (HashTable *addrs, StgPtr sp, StgPtr stack_end, - OCSectionIndices *s_indices) -{ - StgPtr p; - const StgRetInfoTable *info; +static bool markObjectLive(void *data STG_UNUSED, StgWord key, const void *value STG_UNUSED) { + ObjectCode *oc = (ObjectCode*)key; + if (oc->mark == object_code_mark_bit) { + return true; // for hash table iteration + } + + oc->mark = object_code_mark_bit; + // Remove from 'old_objects' list + if (oc->prev != NULL) { + // TODO(osa): Maybe 'prev' should be a pointer to the referencing + // *field* ? (instead of referencing *object*) + oc->prev->next = oc->next; + } else { + old_objects = oc->next; + } + if (oc->next != NULL) { + oc->next->prev = oc->prev; + } - p = sp; - while (p < stack_end) { - info = get_ret_itbl((StgClosure *)p); + // Add it to 'objects' list + oc->prev = NULL; + oc->next = objects; + if (objects != NULL) { + objects->prev = oc; + } + objects = oc; - switch (info->i.type) { - case RET_SMALL: - case RET_BIG: - checkAddress(addrs, (const void*)info, s_indices); - break; + // Mark its dependencies + iterHashTable(oc->dependencies, NULL, markObjectLive); - default: - break; - } + return true; // for hash table iteration +} + +void markObjectCode(const void *addr) +{ + if (global_s_indices == NULL) { + return; + } - p += stack_frame_sizeW((StgClosure*)p); + // This should be checked at the call site + ASSERT(!HEAP_ALLOCED(addr)); + + ObjectCode *oc = findOC(global_s_indices, addr); + if (oc != NULL) { + // Mark the object code and its dependencies + markObjectLive(NULL, (W_)oc, NULL); } } - -static void searchHeapBlocks (HashTable *addrs, bdescr *bd, - OCSectionIndices *s_indices) +// Returns whether or not the GC that follows needs to mark code for potential +// unloading. +bool prepareUnloadCheck() { - StgPtr p; - const StgInfoTable *info; - uint32_t size; - bool prim; + if (global_s_indices == NULL) { + return false; + } - for (; bd != NULL; bd = bd->link) { + removeRemovedOCSections(global_s_indices); + sortOCSectionIndices(global_s_indices); - if (bd->flags & BF_PINNED) { - // Assume that objects in PINNED blocks cannot refer to - continue; - } + ASSERT(old_objects == NULL); - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); - prim = false; - - switch (info->type) { - - case THUNK: - size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case FUN: - case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR: - case CONSTR_NOCAF: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case BLACKHOLE: - case BLOCKING_QUEUE: - prim = true; - size = sizeW_fromITBL(info); - break; - - case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. - prim = true; - size = BLACKHOLE_sizeW(); - break; - - case BCO: - prim = true; - size = bco_sizeW((StgBCO *)p); - break; - - case MVAR_CLEAN: - case MVAR_DIRTY: - case TVAR: - case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = true; - size = sizeW_fromITBL(info); - break; - - case AP: - prim = true; - size = ap_sizeW((StgAP *)p); - break; - - case PAP: - prim = true; - size = pap_sizeW((StgPAP *)p); - break; - - case AP_STACK: - { - StgAP_STACK *ap = (StgAP_STACK *)p; - prim = true; - size = ap_stack_sizeW(ap); - searchStackChunk(addrs, (StgPtr)ap->payload, - (StgPtr)ap->payload + ap->size, s_indices); - break; - } + object_code_mark_bit = ~object_code_mark_bit; + old_objects = objects; + objects = NULL; + return true; +} - case ARR_WORDS: - prim = true; - size = arr_words_sizeW((StgArrBytes*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN_CLEAN: - case MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = true; - size = sizeofW(StgTSO); - break; - - case STACK: { - StgStack *stack = (StgStack*)p; - prim = true; - searchStackChunk(addrs, stack->sp, - stack->stack + stack->stack_size, s_indices); - size = stack_sizeW(stack); - break; - } +void checkUnload() +{ + if (global_s_indices == NULL) { + return; + } - case TREC_CHUNK: - prim = true; - size = sizeofW(StgTRecChunk); - break; + // At this point we've marked all dynamically loaded static objects + // (including their dependencies) during GC, but not the root set of object + // code (loaded_objects). Mark the roots first, then unload any unmarked + // objects. - default: - barf("searchHeapBlocks, unknown object: %d", info->type); - } + OCSectionIndices *s_indices = global_s_indices; + ASSERT(s_indices->sorted); - if (!prim) { - checkAddress(addrs,info, s_indices); - } - - p += size; - } + // Mark roots + for (ObjectCode *oc = loaded_objects; oc != NULL; oc = oc->next_loaded_object) { + markObjectLive(NULL, (W_)oc, NULL); } -} -#if defined(PROFILING) -// -// Do not unload the object if the CCS tree refers to a CCS or CC which -// originates in the object. -// -static void searchCostCentres (HashTable *addrs, CostCentreStack *ccs, - OCSectionIndices* s_indices) -{ - IndexTable *i; + // Free unmarked objects + ObjectCode *next = NULL; + for (ObjectCode *oc = old_objects; oc != NULL; oc = next) { + next = oc->next; - checkAddress(addrs, ccs, s_indices); - checkAddress(addrs, ccs->cc, s_indices); - for (i = ccs->indexTable; i != NULL; i = i->next) { - if (!i->back_edge) { - searchCostCentres(addrs, i->ccs, s_indices); - } + removeOCSectionIndices(s_indices, oc); + + // Symbols should be removed by unloadObj_. + // NB (osa): If this assertion doesn't hold then freeObjectCode below + // will corrupt symhash as keys of that table live in ObjectCodes. If + // you see a segfault in a hash table operation in linker (in non-debug + // RTS) then it's probably becuse this assertion did not hold. + ASSERT(oc->symbols == NULL); + + freeObjectCode(oc); + n_unloaded_objects -= 1; } -} -#endif -// -// Check whether we can unload any object code. This is called at the -// appropriate point during a GC, where all the heap data is nice and -// packed together and we have a linked list of the static objects. -// -// The check involves a complete heap traversal, but you only pay for -// this (a) when you have called unloadObj(), and (b) at a major GC, -// which is much more expensive than the traversal we're doing here. -// -void checkUnload (StgClosure *static_objects) -{ - uint32_t g, n; - HashTable *addrs; - StgClosure* p; - const StgInfoTable *info; - ObjectCode *oc, *prev, *next; - gen_workspace *ws; - StgClosure* link; - - if (unloaded_objects == NULL) return; - - ACQUIRE_LOCK(&linker_unloaded_mutex); - - OCSectionIndices *s_indices = buildOCSectionIndices(unloaded_objects); - // Mark every unloadable object as unreferenced initially - for (oc = unloaded_objects; oc; oc = oc->next) { - IF_DEBUG(linker, debugBelch("Checking whether to unload %" PATH_FMT "\n", - oc->fileName)); - oc->referenced = false; - } - - addrs = allocHashTable(); - - for (p = static_objects; p != END_OF_STATIC_OBJECT_LIST; p = link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - info = get_itbl(p); - checkAddress(addrs, info, s_indices); - link = *STATIC_LINK(info, p); - } - - // CAFs on revertible_caf_list are not on static_objects - for (p = (StgClosure*)revertible_caf_list; - p != END_OF_CAF_LIST; - p = ((StgIndStatic *)p)->static_link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - } - - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - searchHeapBlocks (addrs, generations[g].blocks, s_indices); - searchHeapBlocks (addrs, generations[g].large_objects, s_indices); - - for (n = 0; n < n_capabilities; n++) { - ws = &gc_threads[n]->gens[g]; - searchHeapBlocks(addrs, ws->todo_bd, s_indices); - searchHeapBlocks(addrs, ws->part_list, s_indices); - searchHeapBlocks(addrs, ws->scavd_list, s_indices); - } - } - -#if defined(PROFILING) - /* Traverse the cost centre tree, calling checkAddress on each CCS/CC */ - searchCostCentres(addrs, CCS_MAIN, s_indices); - - /* Also check each cost centre in the CC_LIST */ - CostCentre *cc; - for (cc = CC_LIST; cc != NULL; cc = cc->link) { - checkAddress(addrs, cc, s_indices); - } -#endif /* PROFILING */ - - freeOCSectionIndices(s_indices); - // Look through the unloadable objects, and any object that is still - // marked as unreferenced can be physically unloaded, because we - // have no references to it. - prev = NULL; - for (oc = unloaded_objects; oc; oc = next) { - next = oc->next; - if (oc->referenced == 0) { - if (prev == NULL) { - unloaded_objects = oc->next; - } else { - prev->next = oc->next; - } - IF_DEBUG(linker, debugBelch("Unloading object file %" PATH_FMT "\n", - oc->fileName)); - freeObjectCode(oc); - } else { - IF_DEBUG(linker, debugBelch("Object file still in use: %" - PATH_FMT "\n", oc->fileName)); - prev = oc; - } - } - - freeHashTable(addrs, NULL); - - RELEASE_LOCK(&linker_unloaded_mutex); + old_objects = NULL; } ===================================== rts/CheckUnload.h ===================================== @@ -12,6 +12,34 @@ #include "BeginPrivate.h" -void checkUnload (StgClosure *static_objects); +#include "LinkerInternals.h" + +// Currently live objects +extern ObjectCode *objects; + +// Root set for object collection +extern ObjectCode *loaded_objects; + +// Mark bit for live objects +extern uint8_t object_code_mark_bit; + +// Number of object code currently marked for unloading. See the definition in +// CheckUnload.c for details. +extern int n_unloaded_objects; + +void initUnloadCheck(void); +void exitUnloadCheck(void); + +// Call before major GC to prepare section index table for marking +bool prepareUnloadCheck(void); + +// Mark object code of a static closure address as 'live' +void markObjectCode(const void *addr); + +// Call after major GC to unload unused and unmarked object code +void checkUnload(void); + +// Call on loaded object code +void insertOCSectionIndices(ObjectCode *oc); #include "EndPrivate.h" ===================================== rts/Hash.c ===================================== @@ -400,6 +400,27 @@ mapHashTable(HashTable *table, void *data, MapHashFn fn) } } +void +iterHashTable(HashTable *table, void *data, IterHashFn fn) +{ + /* The last bucket with something in it is table->max + table->split - 1 */ + long segment = (table->max + table->split - 1) / HSEGSIZE; + long index = (table->max + table->split - 1) % HSEGSIZE; + + while (segment >= 0) { + while (index >= 0) { + for (HashList *hl = table->dir[segment][index]; hl != NULL; hl = hl->next) { + if (!fn(data, hl->key, hl->data)) { + return; + } + } + index--; + } + segment--; + index = HSEGSIZE - 1; + } +} + /* ----------------------------------------------------------------------------- * When we initialize a hash table, we set up the first segment as well, * initializing all of the first segment's hash buckets to NULL. @@ -444,12 +465,6 @@ allocStrHashTable(void) return allocHashTable_(hashStr, compareStr); } -void -exitHashTable(void) -{ - /* nothing to do */ -} - int keyCountHashTable (HashTable *table) { return table->kcount; ===================================== rts/Hash.h ===================================== @@ -33,8 +33,11 @@ int keyCountHashTable (HashTable *table); int keysHashTable(HashTable *table, StgWord keys[], int szKeys); typedef void (*MapHashFn)(void *data, StgWord key, const void *value); +// Return true -> continue; false -> stop +typedef bool (*IterHashFn)(void *data, StgWord key, const void *value); void mapHashTable(HashTable *table, void *data, MapHashFn fn); +void iterHashTable(HashTable *table, void *data, IterHashFn); /* Hash table access where the keys are C strings (the strings are * assumed to be allocated by the caller, and mustn't be deallocated @@ -62,6 +65,32 @@ int hashStr(const HashTable *table, StgWord key); */ void freeHashTable ( HashTable *table, void (*freeDataFun)(void *) ); -void exitHashTable ( void ); +INLINE_HEADER void freeStrHashTable ( HashTable *table, void (*freeDataFun)(void *) ) +{ + freeHashTable((HashTable*)table, freeDataFun); +} + +/* + * Hash set API + * + * A hash set is bascially a hash table where values are NULL. + */ + +typedef struct hashtable HashSet; + +INLINE_HEADER HashSet *allocHashSet ( void ) +{ + return (HashSet*)allocHashTable(); +} + +INLINE_HEADER void freeHashSet ( HashSet *set ) +{ + freeHashTable((HashTable*)set, NULL); +} + +INLINE_HEADER void insertHashSet ( HashSet *set, StgWord key ) +{ + insertHashTable((HashTable*)set, key, NULL); +} #include "EndPrivate.h" ===================================== rts/Linker.c ===================================== @@ -32,6 +32,7 @@ #include "linker/CacheFlush.h" #include "linker/SymbolExtras.h" #include "PathUtils.h" +#include "CheckUnload.h" // createOCSectionIndices #if !defined(mingw32_HOST_OS) #include "posix/Signals.h" @@ -161,23 +162,9 @@ */ /*Str*/HashTable *symhash; -/* List of currently loaded objects */ -ObjectCode *objects = NULL; /* initially empty */ - -/* List of objects that have been unloaded via unloadObj(), but are waiting - to be actually freed via checkUnload() */ -ObjectCode *unloaded_objects = NULL; /* initially empty */ - #if defined(THREADED_RTS) -/* This protects all the Linker's global state except unloaded_objects */ +/* This protects all the Linker's global state */ Mutex linker_mutex; -/* - * This protects unloaded_objects. We have a separate mutex for this, because - * the GC needs to access unloaded_objects in checkUnload, while the linker only - * needs to access unloaded_objects in unloadObj(), so this allows most linker - * operations proceed concurrently with the GC. - */ -Mutex linker_unloaded_mutex; #endif /* Generic wrapper function to try and Resolve and RunInit oc files */ @@ -447,12 +434,10 @@ initLinker_ (int retain_cafs) linker_init_done = 1; } - objects = NULL; - unloaded_objects = NULL; + initUnloadCheck(); #if defined(THREADED_RTS) initMutex(&linker_mutex); - initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -538,6 +523,7 @@ exitLinker( void ) { #endif if (linker_init_done == 1) { freeHashTable(symhash, free); + exitUnloadCheck(); } #if defined(THREADED_RTS) closeMutex(&linker_mutex); @@ -864,18 +850,24 @@ HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data) } /* ----------------------------------------------------------------------------- - * lookup a symbol in the hash table + * Lookup a symbol in the hash table + * + * When 'dependent' is not NULL, adds it as a dependent to the owner of the + * symbol. */ #if defined(OBJFORMAT_PEi386) -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + (void)dependent; // TODO + ASSERT_LOCK_HELD(&linker_mutex); return lookupSymbol_PEi386(lbl); } #else -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + ASSERT_LOCK_HELD(&linker_mutex); IF_DEBUG(linker, debugBelch("lookupSymbol: looking up '%s'\n", lbl)); ASSERT(symhash != NULL); @@ -900,10 +892,18 @@ SymbolAddr* lookupSymbol_ (SymbolName* lbl) return internal_dlsym(lbl + 1); # else - ASSERT(2+2 == 5); + ASSERT(false); return NULL; # endif } else { + if (dependent) { + // Add dependent as symbol's owner's dependency + ObjectCode *owner = pinfo->owner; + if (owner) { + // TODO: what does it mean for a symbol to not have an owner? + insertHashSet(dependent->dependencies, (W_)owner); + } + } return loadSymbol(lbl, pinfo); } } @@ -942,7 +942,7 @@ SymbolAddr* loadSymbol(SymbolName *lbl, RtsSymbolInfo *pinfo) { SymbolAddr* lookupSymbol( SymbolName* lbl ) { ACQUIRE_LOCK(&linker_mutex); - SymbolAddr* r = lookupSymbol_(lbl); + SymbolAddr* r = lookupDependentSymbol(lbl, NULL); if (!r) { errorBelch("^^ Could not load '%s', dependency unresolved. " "See top entry above.\n", lbl); @@ -1342,6 +1342,8 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->fileName); stgFree(oc->archiveMemberName); + freeHashSet(oc->dependencies); + stgFree(oc); } @@ -1403,6 +1405,10 @@ mkOc( pathchar *path, char *image, int imageSize, /* chain it onto the list of objects */ oc->next = NULL; + oc->prev = NULL; + oc->next_loaded_object = NULL; + oc->mark = object_code_mark_bit; + oc->dependencies = allocHashSet(); #if RTS_LINKER_USE_MMAP oc->rw_m32 = m32_allocator_new(false); @@ -1421,9 +1427,9 @@ mkOc( pathchar *path, char *image, int imageSize, HsInt isAlreadyLoaded( pathchar *path ) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path) + && o->status != OBJECT_UNLOADED) { return 1; /* already loaded */ } } @@ -1557,21 +1563,16 @@ preloadObjectFile (pathchar *path) */ static HsInt loadObj_ (pathchar *path) { - ObjectCode* oc; - IF_DEBUG(linker, debugBelch("loadObj: %" PATH_FMT "\n", path)); - - /* debugBelch("loadObj %s\n", path ); */ - - /* Check that we haven't already loaded this object. - Ignore requests to load multiple times */ + // Check that we haven't already loaded this object. + // Ignore requests to load multiple times if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); - return 1; /* success */ + return 1; // success } - oc = preloadObjectFile(path); + ObjectCode *oc = preloadObjectFile(path); if (oc == NULL) return 0; if (! loadOc(oc)) { @@ -1582,8 +1583,10 @@ static HsInt loadObj_ (pathchar *path) return 0; } - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); + + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; return 1; } @@ -1778,15 +1781,14 @@ int ocTryLoad (ObjectCode* oc) { */ static HsInt resolveObjs_ (void) { - ObjectCode *oc; - int r; - IF_DEBUG(linker, debugBelch("resolveObjs: start\n")); - for (oc = objects; oc; oc = oc->next) { - r = ocTryLoad(oc); + for (ObjectCode *oc = objects; oc; oc = oc->next) { + int r = ocTryLoad(oc); if (!r) { + errorBelch("Could not load Object Code %" PATH_FMT ".\n", OC_INFORMATIVE_FILENAME(oc)); + fflush(stderr); return r; } } @@ -1813,45 +1815,35 @@ HsInt resolveObjs (void) */ static HsInt unloadObj_ (pathchar *path, bool just_purge) { - ObjectCode *oc, *prev, *next; - HsBool unloadedAnyObj = HS_BOOL_FALSE; - ASSERT(symhash != NULL); ASSERT(objects != NULL); IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); - prev = NULL; - for (oc = objects; oc; oc = next) { - next = oc->next; // oc might be freed - - if (!pathcmp(oc->fileName,path)) { + bool unloadedAnyObj = false; + ObjectCode *prev = NULL; + // NOTE (osa): There may be more than one object with the same file name + // (happens when loading archive files) so we don't stop after unloading one + for (ObjectCode *oc = loaded_objects; oc; oc = oc->next_loaded_object) { + if (pathcmp(oc->fileName,path) == 0) { + oc->status = OBJECT_UNLOADED; - // these are both idempotent, so in just_purge mode we can - // later call unloadObj() to really unload the object. + // These are both idempotent, so in just_purge mode we can later + // call unloadObj() to really unload the object. removeOcSymbols(oc); freeOcStablePtrs(oc); + unloadedAnyObj = true; + if (!just_purge) { + n_unloaded_objects += 1; + // Remove object code from root set if (prev == NULL) { - objects = oc->next; + loaded_objects = oc->next_loaded_object; } else { - prev->next = oc->next; + prev->next_loaded_object = oc->next_loaded_object; } - ACQUIRE_LOCK(&linker_unloaded_mutex); - oc->next = unloaded_objects; - unloaded_objects = oc; - oc->status = OBJECT_UNLOADED; - RELEASE_LOCK(&linker_unloaded_mutex); - // We do not own oc any more; it can be released at any time by - // the GC in checkUnload(). - } else { - prev = oc; } - - /* This could be a member of an archive so continue - * unloading other members. */ - unloadedAnyObj = HS_BOOL_TRUE; } else { prev = oc; } @@ -1859,8 +1851,7 @@ static HsInt unloadObj_ (pathchar *path, bool just_purge) if (unloadedAnyObj) { return 1; - } - else { + } else { errorBelch("unloadObj: can't find `%" PATH_FMT "' to unload", path); return 0; } @@ -1884,13 +1875,7 @@ HsInt purgeObj (pathchar *path) static OStatus getObjectLoadStatus_ (pathchar *path) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } - } - for (o = unloaded_objects; o; o = o->next) { + for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { return o->status; } ===================================== rts/LinkerInternals.h ===================================== @@ -191,9 +191,6 @@ typedef struct _ObjectCode { /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; - /* flag used when deciding whether to unload an object file */ - int referenced; - /* record by how much image has been deliberately misaligned after allocation, so that we can use realloc */ int misalignment; @@ -205,8 +202,37 @@ typedef struct _ObjectCode { int n_segments; Segment *segments; - /* Allow a chain of these things */ - struct _ObjectCode * next; + // + // Garbage collection fields + // + + // Next object in `objects` list + struct _ObjectCode *next; + + // Previous object in `objects` list + struct _ObjectCode *prev; + + // Next object in `loaded_objects` list + struct _ObjectCode *next_loaded_object; + + // Mark bit + uint8_t mark; + + // Set of dependencies (ObjectCode*) of the object file. Traverse + // dependencies using `iterHashTable`. + // + // New entries are added as we resolve symbols in an object file, in + // `lookupDependentSymbol`. When an object file uses multiple symbols from + // another object file we add the dependent multiple times, so we use a + // `HashTable` here rather than a list/array to avoid copies. + // + // Used when unloading object files. See Note [Object unloading] in + // CheckUnload.c. + HashSet *dependencies; + + // + // End of garbage collection fields + // /* SANITY CHECK ONLY: a list of the only memory regions which may safely be prodded during relocation. Any attempt to prod @@ -250,12 +276,8 @@ typedef struct _ObjectCode { (OC)->fileName \ ) -extern ObjectCode *objects; -extern ObjectCode *unloaded_objects; - #if defined(THREADED_RTS) extern Mutex linker_mutex; -extern Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -306,8 +328,9 @@ int ghciInsertSymbolTable( HsBool weak, ObjectCode *owner); -/* lock-free version of lookupSymbol */ -SymbolAddr* lookupSymbol_ (SymbolName* lbl); +/* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a + * dependent to the owner of the symbol. */ +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent); extern /*Str*/HashTable *symhash; ===================================== rts/RtsStartup.c ===================================== @@ -512,9 +512,6 @@ hs_exit_(bool wait_foreign) shutdownAsyncIO(wait_foreign); #endif - /* free hash table storage */ - exitHashTable(); - // Finally, free all our storage. However, we only free the heap // memory if we have waited for foreign calls to complete; // otherwise a foreign call in progress may still be referencing ===================================== rts/linker/Elf.c ===================================== @@ -1099,7 +1099,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) { S = (Elf_Addr)symbol->addr; } else { - S_tmp = lookupSymbol_( symbol->name ); + S_tmp = lookupDependentSymbol( symbol->name, oc ); S = (Elf_Addr)S_tmp; } if (!S) { @@ -1519,7 +1519,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } else { /* No, so look up the name in our global table. */ symbol = strtab + sym.st_name; - S_tmp = lookupSymbol_( symbol ); + S_tmp = lookupDependentSymbol( symbol, oc ); S = (Elf_Addr)S_tmp; } if (!S) { ===================================== rts/linker/LoadArchive.c ===================================== @@ -5,6 +5,7 @@ #include "sm/OSMem.h" #include "RtsUtils.h" #include "LinkerInternals.h" +#include "CheckUnload.h" // loaded_objects, insertOCSectionIndices #include "linker/M32Alloc.h" /* Platform specific headers */ @@ -241,7 +242,6 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, static HsInt loadArchive_ (pathchar *path) { - ObjectCode* oc = NULL; char *image = NULL; HsInt retcode = 0; int memberSize; @@ -520,8 +520,8 @@ static HsInt loadArchive_ (pathchar *path) sprintf(archiveMemberName, "%" PATH_FMT "(%.*s)", path, (int)thisFileNameSize, fileName); - oc = mkOc(path, image, memberSize, false, archiveMemberName - , misalignment); + ObjectCode *oc = mkOc(path, image, memberSize, false, archiveMemberName, + misalignment); #if defined(OBJFORMAT_MACHO) ocInit_MachO( oc ); #endif @@ -536,8 +536,9 @@ static HsInt loadArchive_ (pathchar *path) fclose(f); return 0; } else { - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); // also adds the object to `objects` list + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; } } else if (isGnuIndex) { ===================================== rts/linker/MachO.c ===================================== @@ -242,7 +242,7 @@ resolveImports( addr = (SymbolAddr*) (symbol->nlist->n_value); IF_DEBUG(linker, debugBelch("resolveImports: undefined external %s has value %p\n", symbol->name, addr)); } else { - addr = lookupSymbol_(symbol->name); + addr = lookupDependentSymbol(symbol->name, oc); IF_DEBUG(linker, debugBelch("resolveImports: looking up %s, %p\n", symbol->name, addr)); } @@ -564,12 +564,12 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { /* external symbols should be able to be - * looked up via the lookupSymbol_ function. + * looked up via the lookupDependentSymbol function. * Either through the global symbol hashmap * or asking the system, if not found * in the symbol hashmap */ - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -609,7 +609,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -784,7 +784,7 @@ relocateSection(ObjectCode* oc, int curSection) // symtab, or it is undefined, meaning dlsym must be used // to resolve it. - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); IF_DEBUG(linker, debugBelch("relocateSection: looked up %s, " "external X86_64_RELOC_GOT or X86_64_RELOC_GOT_LOAD\n" " : addr = %p\n", nm, addr)); @@ -845,7 +845,7 @@ relocateSection(ObjectCode* oc, int curSection) nm, (void *)value)); } else { - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); if (addr == NULL) { errorBelch("\nlookupSymbol failed in relocateSection (relocate external)\n" @@ -1345,7 +1345,7 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->nlist[i].n_type & N_EXT) { if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) - && lookupSymbol_(nm)) { + && lookupDependentSymbol(nm, oc)) { // weak definition, and we already have a definition IF_DEBUG(linker, debugBelch(" weak: %s\n", nm)); } @@ -1497,7 +1497,7 @@ ocResolve_MachO(ObjectCode* oc) * have the address. */ if(NULL == symbol->addr) { - symbol->addr = lookupSymbol_((char*)symbol->name); + symbol->addr = lookupDependentSymbol((char*)symbol->name, oc); if(NULL == symbol->addr) barf("Failed to lookup symbol: %s", symbol->name); } else { ===================================== rts/linker/PEi386.c ===================================== @@ -185,6 +185,7 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" #include "GetEnv.h" +#include "CheckUnload.h" #include "linker/PEi386.h" #include "linker/PEi386Types.h" #include "linker/SymbolExtras.h" @@ -1894,7 +1895,7 @@ ocResolve_PEi386 ( ObjectCode* oc ) } else { copyName ( getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1 ); - S = (size_t) lookupSymbol_( (char*)symbol ); + S = (size_t) lookupDependentSymbol( (char*)symbol, oc ); if ((void*)S == NULL) { errorBelch(" | %" PATH_FMT ": unknown symbol `%s'", oc->fileName, symbol); releaseOcInfo (oc); ===================================== rts/linker/elf_got.c ===================================== @@ -88,7 +88,7 @@ fillGot(ObjectCode * oc) { if( STT_NOTYPE == ELF_ST_TYPE(symbol->elf_sym->st_info) || STB_WEAK == ELF_ST_BIND(symbol->elf_sym->st_info)) { if(0x0 == symbol->addr) { - symbol->addr = lookupSymbol_(symbol->name); + symbol->addr = lookupDependentSymbol(symbol->name, oc); if(0x0 == symbol->addr) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; ===================================== rts/sm/Evac.c ===================================== @@ -28,6 +28,7 @@ #include "CNF.h" #include "Scav.h" #include "NonMoving.h" +#include "CheckUnload.h" // n_unloaded_objects and markObjectCode #if defined(THREADED_RTS) && !defined(PARALLEL_GC) #define evacuate(p) evacuate1(p) @@ -593,6 +594,11 @@ loop: if (!HEAP_ALLOCED_GC(q)) { if (!major_gc) return; + // Note [Object unloading] in CheckUnload.c + if (RTS_UNLIKELY(unload_mark_needed)) { + markObjectCode(q); + } + info = get_itbl(q); switch (info->type) { ===================================== rts/sm/GC.c ===================================== @@ -97,6 +97,13 @@ * See also: Note [STATIC_LINK fields] in Storage.h. */ +/* Hot GC globals + * ~~~~~~~~~~~~~~ + * The globals below are quite hot during GC but read-only, initialized during + * the beginning of collection. It is important that they reside in the same + * cache-line to minimize unnecessary cache misses. + */ + /* N is the oldest generation being collected, where the generations * are numbered starting at 0. A major GC (indicated by the major_gc * flag) is when we're collecting all generations. We only attempt to @@ -105,6 +112,7 @@ uint32_t N; bool major_gc; bool deadlock_detect_gc; +bool unload_mark_needed; /* Data used for allocation area sizing. */ @@ -297,6 +305,12 @@ GarbageCollect (uint32_t collect_gen, static_flag == STATIC_FLAG_A ? STATIC_FLAG_B : STATIC_FLAG_A; } + if (major_gc) { + unload_mark_needed = prepareUnloadCheck(); + } else { + unload_mark_needed = false; + } + #if defined(THREADED_RTS) work_stealing = RtsFlags.ParFlags.parGcLoadBalancingEnabled && N >= RtsFlags.ParFlags.parGcLoadBalancingGen; @@ -810,9 +824,12 @@ GarbageCollect (uint32_t collect_gen, resetNurseries(); - // mark the garbage collected CAFs as dead #if defined(DEBUG) - if (major_gc && !RtsFlags.GcFlags.useNonmoving) { gcCAFs(); } + // Mark the garbage collected CAFs as dead. Done in `nonmovingGcCafs()` when + // non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + gcCAFs(); + } #endif // Update the stable name hash table @@ -823,9 +840,14 @@ GarbageCollect (uint32_t collect_gen, // hs_free_stable_ptr(), both of which access the StablePtr table. stablePtrUnlock(); - // Must be after stablePtrUnlock(), because it might free stable ptrs. - if (major_gc) { - checkUnload (gct->scavenged_static_objects); + // Unload dynamically-loaded object code after a major GC. + // See Note [Object unloading] in CheckUnload.c for details. + // + // TODO: Similar to `nonmovingGcCafs` non-moving GC should have its own + // collector for these objects, but that's currently not implemented, so we + // simply don't unload object code when non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + checkUnload(); } #if defined(PROFILING) ===================================== rts/sm/GC.h ===================================== @@ -35,6 +35,7 @@ extern uint32_t N; extern bool major_gc; /* See Note [Deadlock detection under nonmoving collector]. */ extern bool deadlock_detect_gc; +extern bool unload_mark_needed; extern bdescr *mark_stack_bd; extern bdescr *mark_stack_top_bd; ===================================== testsuite/tests/ghci/T16525a/T16525a.script ===================================== @@ -1,6 +1,10 @@ :set -fobject-code :load A import Control.Concurrent -_ <- forkIO $ threadDelay 1000000 >> (print (map v1 value)) +_ <- forkIO $ threadDelay 500000 >> print (map v1 value) :l [] System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC ===================================== testsuite/tests/ghci/T16525a/T16525a.stdout ===================================== @@ -0,0 +1 @@ +["a;lskdfa;lszkfsd;alkfjas"] ===================================== testsuite/tests/ghci/T16525a/all.T ===================================== @@ -1,6 +1,3 @@ test('T16525a', - [extra_files(['A.hs', 'B.hs', ]), - when(compiler_debugged(), extra_run_opts('+RTS -DS -RTS')), - # We don't support unloading with the dynamic linker - when(ghc_dynamic(), skip), ], + [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525a.script']) ===================================== testsuite/tests/ghci/T16525b/A.hs ===================================== @@ -0,0 +1,6 @@ +module A (a) where + +import B + +a :: () -> IO Int +a x = b x ===================================== testsuite/tests/ghci/T16525b/B.hs ===================================== @@ -0,0 +1,5 @@ +module B (b) where + +{-# NOINLINE b #-} +b :: () -> IO Int +b () = return 999999999 ===================================== testsuite/tests/ghci/T16525b/T16525b.script ===================================== @@ -0,0 +1,22 @@ +:set -fobject-code +:load A +import Control.Concurrent +import Control.Monad +:{ +_ <- forkIO $ do + replicateM_ 3 (a () >>= print >> threadDelay 500000) + putStrLn "===== THREAD DONE =====" +:} +:l [] +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 ===================================== testsuite/tests/ghci/T16525b/T16525b.stdout ===================================== @@ -0,0 +1,4 @@ +999999999 +999999999 +999999999 +===== THREAD DONE ===== ===================================== testsuite/tests/ghci/T16525b/all.T ===================================== @@ -0,0 +1,2 @@ +# Tests unloading an object file which is in use in a thread +test('T16525b', [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525b.script']) ===================================== testsuite/tests/rts/linker/linker_error.c ===================================== @@ -57,7 +57,10 @@ int main (int argc, char *argv[]) r = resolveObjs(); if (!r) { debugBelch("resolveObjs failed\n"); + // Mark the object as unloadable: unloadObj(obj); + // Actually unload it: + performMajorGC(); continue; } errorBelch("loading succeeded"); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58ed8da7a076ebf0037d30ff96b6144045679d50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/58ed8da7a076ebf0037d30ff96b6144045679d50 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 Wed Nov 25 16:25:18 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Wed, 25 Nov 2020 11:25:18 -0500 Subject: [Git][ghc/ghc][wip/win32-high-heap] rts: Allocate MBlocks with MAP_TOP_DOWN on Windows Message-ID: <5fbe856e730e8_86ce89fc5c208621@gitlab.mail> Ben Gamari pushed to branch wip/win32-high-heap at Glasgow Haskell Compiler / GHC Commits: 839255bc by Ben Gamari at 2020-11-25T11:25:13-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 1 changed file: - rts/win32/OSMem.c Changes: ===================================== rts/win32/OSMem.c ===================================== @@ -50,8 +50,11 @@ allocNew(uint32_t n) { alloc_rec* rec; rec = (alloc_rec*)stgMallocBytes(sizeof(alloc_rec),"getMBlocks: allocNew"); rec->size = ((W_)n+1)*MBLOCK_SIZE; + // N.B. We use MEM_TOP_DOWN here to ensure that we leave the bottom of the + // address space available for the linker and libraries, which in general + // want to live in low memory. See #18991. rec->base = - VirtualAlloc(NULL, rec->size, MEM_RESERVE, PAGE_READWRITE); + VirtualAlloc(NULL, rec->size, MEM_RESERVE | MEM_TOP_DOWN, PAGE_READWRITE); if(rec->base==0) { stgFree((void*)rec); rec=0; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/839255bc7ce4f5472144185766ad206350c14c3d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/839255bc7ce4f5472144185766ad206350c14c3d 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 Wed Nov 25 16:45:35 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 25 Nov 2020 11:45:35 -0500 Subject: [Git][ghc/ghc][wip/T18894] DmdAnal: Annotate top-level function bindings with demands (#18894) Message-ID: <5fbe8a2f541e6_86cfd752bc2094c6@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: 2391fad6 by Sebastian Graf at 2020-11-25T17:37:02+01:00 DmdAnal: Annotate top-level function bindings with demands (#18894) It's useful to annotate a (non-exported) top-level function like `g` in ```hs g :: Int -> Int -> (Int,Int) g m 1 = (m, 0) g m n = (2 * m, 2 `div` n) {-# NOINLINE g #-} h :: Int -> Int h 1 = 0 h m | odd m = snd (g m 2) | otherwise = uncurry (+) (g 2 m) ``` with its demand `UCU(CS(P(1P(U),SP(U))`, which tells us that whenever `g` was called, the second component of the returned pair was evaluated strictly. This is crucial information for Nested CPR, which may the go on and unbox `g` for the second pair component. That is true even if that pair component may diverge, as is the case for the call site `g 13 0`, which throws a div-by-zero exception. We only track bindings of function type in order not to risk huge compile-time regressions. Fixes #18894. - - - - - 7 changed files: - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id/Info.hs Changes: ===================================== compiler/GHC/Core/FVs.hs ===================================== @@ -525,12 +525,11 @@ ruleLhsFVIds (Rule { ru_bndrs = bndrs, ru_args = args }) = filterFV isLocalId $ addBndrs bndrs (exprs_fvs args) ruleRhsFreeIds :: CoreRule -> VarSet --- ^ This finds all locally-defined free Ids on the left hand side of a rule +-- ^ This finds all locally-defined free Ids on the right hand side of a rule -- and returns them as a non-deterministic set ruleRhsFreeIds (BuiltinRule {}) = emptyVarSet -ruleRhsFreeIds (Rule { ru_bndrs = bndrs, ru_args = args }) - = fvVarSet $ filterFV isLocalId $ - addBndrs bndrs $ exprs_fvs args +ruleRhsFreeIds (Rule { ru_bndrs = bndrs, ru_rhs = rhs }) + = fvVarSet $ filterFV isLocalId $ addBndrs bndrs $ expr_fvs rhs {- Note [Rule free var hack] (Not a hack any more) ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -37,6 +37,7 @@ import GHC.Core.Type import GHC.Core.FVs ( exprFreeIds, ruleRhsFreeIds ) import GHC.Core.Coercion ( Coercion, coVarsOfCo ) import GHC.Core.FamInstEnv +import GHC.Core.Opt.Arity ( typeArity ) import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Data.Maybe ( isJust ) @@ -64,28 +65,42 @@ data DmdAnalOpts = DmdAnalOpts -- -- Note: use `seqBinds` on the result to avoid leaks due to lazyness (cf Note -- [Stamp out space leaks in demand analysis]) -dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> CoreProgram -> CoreProgram -dmdAnalProgram opts fam_envs binds = binds_plus_dmds - where - env = emptyAnalEnv opts fam_envs - binds_plus_dmds = snd $ mapAccumL dmdAnalTopBind env binds - --- Analyse a (group of) top-level binding(s) -dmdAnalTopBind :: AnalEnv - -> CoreBind - -> (AnalEnv, CoreBind) -dmdAnalTopBind env (NonRec id rhs) - = ( extendAnalEnv TopLevel env id sig - , NonRec (setIdStrictness id sig) rhs') +dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> [CoreRule] -> CoreProgram -> CoreProgram +dmdAnalProgram opts fam_envs rules binds + = snd $ go (emptyAnalEnv opts fam_envs) binds where - ( _, sig, rhs') = dmdAnalRhsLetDown Nothing env topSubDmd id rhs + go _ [] = (nopDmdType, []) + go env (b:bs) = case b of + NonRec id rhs + | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel NonRecursive env topSubDmd id rhs + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_use env' dmd_ty' id' `addLazyFVs` lazy_fvs + , (!dmd_ty''', id_dmd) <- findBndrDmd env' False dmd_ty'' id' + , let id'' = annotate_id_dmd id' id_dmd + -> (dmd_ty''', NonRec id'' rhs' : bs') + Rec pairs + | (env', lazy_fvs, pairs') <- dmdFix TopLevel env topSubDmd pairs + , let ids' = map fst pairs' + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_uses env' dmd_ty' ids' `addLazyFVs` lazy_fvs + , (!dmd_ty''', id_dmds) <- findBndrsDmds env' dmd_ty'' ids' + , let pairs'' = zipWith (\(id', rhs') dmd -> (annotate_id_dmd id' dmd, rhs')) pairs' id_dmds + -> (dmd_ty''', Rec pairs'' : bs') + + annotate_id_dmd id dmd + | isInterestingTopLevelFn id + = id `setIdDemandInfo` dmd + | otherwise + = id `setIdDemandInfo` topDmd -dmdAnalTopBind env (Rec pairs) - = (env', Rec pairs') - where - (env', _, pairs') = dmdFix TopLevel env topSubDmd pairs - -- We get two iterations automatically - -- c.f. the NonRec case above + add_exported_uses env = foldl' (add_exported_use env) + add_exported_use env dmd_ty id + | isExportedId id || elemVarSet id rule_fvs + -- See Note [Absence analysis for stable unfoldings and RULES] + = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) + | otherwise = dmd_ty + + rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules {- Note [Stamp out space leaks in demand analysis] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -320,9 +335,7 @@ dmdAnal' env dmd (Let (NonRec id rhs) body) dmdAnal' env dmd (Let (NonRec id rhs) body) = (body_ty2, Let (NonRec id2 rhs') body') where - (lazy_fv, sig, rhs') = dmdAnalRhsLetDown Nothing env dmd id rhs - id1 = setIdStrictness id sig - env1 = extendAnalEnv NotTopLevel env id sig + (env1, lazy_fv, id1, rhs') = dmdAnalRhsLetDown NotTopLevel NonRecursive env dmd id rhs (body_ty, body') = dmdAnal env1 dmd body (body_ty1, id2) = annotateBndr env body_ty id1 body_ty2 = addLazyFVs body_ty1 lazy_fv -- see Note [Lazy and unleashable free variables] @@ -344,8 +357,8 @@ dmdAnal' env dmd (Let (Rec pairs) body) = let (env', lazy_fv, pairs') = dmdFix NotTopLevel env dmd pairs (body_ty, body') = dmdAnal env' dmd body - body_ty1 = deleteFVs body_ty (map fst pairs) - body_ty2 = addLazyFVs body_ty1 lazy_fv -- see Note [Lazy and unleashable free variables] + body_ty1 = addLazyFVs body_ty lazy_fv -- see Note [Lazy and unleashable free variables] + body_ty2 = deleteFVs body_ty1 (map fst pairs) -- TODO: We could annotate idDemandInfo here in body_ty2 `seq` (body_ty2, Let (Rec pairs') body') @@ -554,6 +567,16 @@ strict in |y|. ************************************************************************ -} +-- | Whether we want to store demands on a top-level Id or just default +-- to 'topDmd'. +-- +-- Basically, we want to now how top-level *functions* are *used* +-- (e.g. called), but aren't interested in whether they were called strictly +-- or not. Other top-level bindings are boring. +isInterestingTopLevelFn :: Id -> Bool +isInterestingTopLevelFn id = + typeArity (idType id) `lengthExceeds` 0 + dmdTransform :: AnalEnv -- ^ The strictness environment -> Id -- ^ The function -> SubDemand -- ^ The demand on the function @@ -582,9 +605,13 @@ dmdTransform env var dmd | Just (sig, top_lvl) <- lookupSigEnv env var , let fn_ty = dmdTransformSig sig dmd = -- pprTrace "dmdTransform:LetDown" (vcat [ppr var, ppr sig, ppr dmd, ppr fn_ty]) $ - if isTopLevel top_lvl - then fn_ty -- Don't record demand on top-level things - else addVarDmd fn_ty var (C_11 :* dmd) + case top_lvl of + NotTopLevel -> addVarDmd fn_ty var (C_11 :* dmd) + TopLevel + | isInterestingTopLevelFn var + -> addVarDmd fn_ty var (C_0N `multDmd` (C_11 :* dmd)) -- discard strictness + | otherwise + -> fn_ty -- don't bother tracking; just annotate with 'topDmd' later -- Everything else: -- * Local let binders for which we use LetUp (cf. 'useLetUp') -- * Lambda binders @@ -612,33 +639,36 @@ dmdTransform env var dmd -- -- This is the LetDown rule in the paper “Higher-Order Cardinality Analysis”. dmdAnalRhsLetDown - :: Maybe [Id] -- Just bs <=> recursive, Nothing <=> non-recursive + :: TopLevelFlag + -> RecFlag -> AnalEnv -> SubDemand -> Id -> CoreExpr - -> (DmdEnv, StrictSig, CoreExpr) + -> (AnalEnv, DmdEnv, Id, CoreExpr) -- Process the RHS of the binding, add the strictness signature -- to the Id, and augment the environment with the signature as well. -- See Note [NOINLINE and strictness] -dmdAnalRhsLetDown rec_flag env let_dmd id rhs +dmdAnalRhsLetDown top_lvl rec_flag env let_dmd id rhs = -- pprTrace "dmdAnalRhsLetDown" (ppr id $$ ppr let_dmd $$ ppr sig $$ ppr lazy_fv) $ - (lazy_fv, sig, rhs') + (env', lazy_fv, id', rhs') where rhs_arity = idArity id + -- See Note [Demand signatures are computed for a threshold demand based on idArity] rhs_dmd -- See Note [Demand analysis for join points] -- See Note [Invariants on join points] invariant 2b, in GHC.Core -- rhs_arity matches the join arity of the join point | isJoinId id = mkCallDmds rhs_arity let_dmd | otherwise - -- NB: rhs_arity - -- See Note [Demand signatures are computed for a threshold demand based on idArity] - = mkRhsDmd env rhs_arity rhs + = mkCallDmds rhs_arity topSubDmd (rhs_dmd_ty, rhs') = dmdAnal env rhs_dmd rhs DmdType rhs_fv rhs_dmds rhs_div = rhs_dmd_ty sig = mkStrictSigForArity rhs_arity (DmdType sig_fv rhs_dmds rhs_div) + id' = id `setIdStrictness` sig + env' = extendAnalEnv top_lvl env id' sig + -- See Note [Aggregated demand for cardinality] -- FIXME: That Note doesn't explain the following lines at all. The reason -- is really much different: When we have a recursive function, we'd @@ -651,8 +681,8 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs -- we'd have to do an additional iteration. reuseEnv makes sure that -- we never get used-once info for FVs of recursive functions. rhs_fv1 = case rec_flag of - Just bs -> reuseEnv (delVarEnvList rhs_fv bs) - Nothing -> rhs_fv + Recursive -> reuseEnv rhs_fv + NonRecursive -> rhs_fv rhs_fv2 = rhs_fv1 `keepAliveDmdEnv` extra_fvs -- Find the RHS free vars of the unfoldings and RULES @@ -669,13 +699,6 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs = exprFreeIds unf_body | otherwise = emptyVarSet --- | @mkRhsDmd env rhs_arity rhs@ creates a 'SubDemand' for --- unleashing on the given function's @rhs@, by creating --- a call demand of @rhs_arity@ --- See Historical Note [Product demands for function body] -mkRhsDmd :: AnalEnv -> Arity -> CoreExpr -> SubDemand -mkRhsDmd _env rhs_arity _rhs = mkCallDmds rhs_arity topSubDmd - -- | If given the (local, non-recursive) let-bound 'Id', 'useLetUp' determines -- whether we should process the binding up (body before rhs) or down (rhs -- before body). @@ -939,8 +962,6 @@ dmdFix :: TopLevelFlag dmdFix top_lvl env let_dmd orig_pairs = loop 1 initial_pairs where - bndrs = map fst orig_pairs - -- See Note [Initialising strictness] initial_pairs | ae_virgin env = [(setIdStrictness id botSig, rhs) | (id, rhs) <- orig_pairs ] | otherwise = orig_pairs @@ -990,10 +1011,8 @@ dmdFix top_lvl env let_dmd orig_pairs = -- pprTrace "my_downRhs" (ppr id $$ ppr (idStrictness id) $$ ppr sig) $ ((env', lazy_fv'), (id', rhs')) where - (lazy_fv1, sig, rhs') = dmdAnalRhsLetDown (Just bndrs) env let_dmd id rhs - lazy_fv' = plusVarEnv_C plusDmd lazy_fv lazy_fv1 - env' = extendAnalEnv top_lvl env id sig - id' = setIdStrictness id sig + (env', lazy_fv1, id', rhs') = dmdAnalRhsLetDown top_lvl Recursive env let_dmd id rhs + lazy_fv' = plusVarEnv_C plusDmd lazy_fv lazy_fv1 zapIdStrictness :: [(Id, CoreExpr)] -> [(Id, CoreExpr)] zapIdStrictness pairs = [(setIdStrictness id nopSig, rhs) | (id, rhs) <- pairs ] ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -65,6 +65,7 @@ import GHC.Types.SrcLoc import GHC.Types.Id import GHC.Types.Id.Info import GHC.Types.Basic +import GHC.Types.Demand ( zapDmdEnvSig ) import GHC.Types.Var.Set import GHC.Types.Var.Env import GHC.Types.Unique.Supply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply ) @@ -495,7 +496,7 @@ doCorePass CoreDoExitify = {-# SCC "Exitify" #-} doPass exitifyProgram doCorePass CoreDoDemand = {-# SCC "DmdAnal" #-} - doPassDFM dmdAnal + doPassDFRM dmdAnal doCorePass CoreDoCpr = {-# SCC "CprAnal" #-} doPassDFM cprAnalProgram @@ -575,6 +576,13 @@ doPassDFM do_pass guts = do let fam_envs = (p_fam_env, mg_fam_inst_env guts) doPassM (liftIO . do_pass dflags fam_envs) guts +doPassDFRM :: (DynFlags -> FamInstEnvs -> [CoreRule] -> CoreProgram -> IO CoreProgram) -> ModGuts -> CoreM ModGuts +doPassDFRM do_pass guts = do + dflags <- getDynFlags + p_fam_env <- getPackageFamInstEnv + let fam_envs = (p_fam_env, mg_fam_inst_env guts) + doPassM (liftIO . do_pass dflags fam_envs (mg_rules guts)) guts + doPassDFU :: (DynFlags -> FamInstEnvs -> UniqSupply -> CoreProgram -> CoreProgram) -> ModGuts -> CoreM ModGuts doPassDFU do_pass guts = do dflags <- getDynFlags @@ -1088,13 +1096,13 @@ transferIdInfo exported_id local_id -dmdAnal :: DynFlags -> FamInstEnvs -> CoreProgram -> IO CoreProgram -dmdAnal dflags fam_envs binds = do +dmdAnal :: DynFlags -> FamInstEnvs -> [CoreRule] -> CoreProgram -> IO CoreProgram +dmdAnal dflags fam_envs rules binds = do let opts = DmdAnalOpts { dmd_strict_dicts = gopt Opt_DictsStrict dflags } - binds_plus_dmds = dmdAnalProgram opts fam_envs binds + binds_plus_dmds = dmdAnalProgram opts fam_envs rules binds Err.dumpIfSet_dyn dflags Opt_D_dump_str_signatures "Strictness signatures" FormatText $ - dumpIdInfoOfProgram (ppr . strictnessInfo) binds_plus_dmds + dumpIdInfoOfProgram (ppr . zapDmdEnvSig . strictnessInfo) binds_plus_dmds -- See Note [Stamp out space leaks in demand analysis] in GHC.Core.Opt.DmdAnal seqBinds binds_plus_dmds `seq` return binds_plus_dmds ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -1275,10 +1275,14 @@ mk_absent_let dflags fam_envs arg abs_rhs = mkAbsentErrorApp arg_ty msg msg = showSDoc (gopt_set dflags Opt_SuppressUniques) - (ppr arg <+> ppr (idType arg) <+> file_msg) + (vcat + [ text "Arg:" <+> ppr arg + , text "Type:" <+> ppr arg_ty + , file_msg + ]) file_msg = case outputFile dflags of Nothing -> empty - Just f -> text "in output file " <+> quotes (text f) + Just f -> text "In output file " <+> quotes (text f) -- We need to suppress uniques here because otherwise they'd -- end up in the generated code as strings. This is bad for -- determinism, because with different uniques the strings ===================================== compiler/GHC/Core/Tidy.hs ===================================== @@ -21,7 +21,7 @@ import GHC.Core import GHC.Core.Seq ( seqUnfolding ) import GHC.Types.Id import GHC.Types.Id.Info -import GHC.Types.Demand ( zapUsageEnvSig ) +import GHC.Types.Demand ( zapDmdEnvSig ) import GHC.Core.Type ( tidyType, tidyVarBndr ) import GHC.Core.Coercion ( tidyCo ) import GHC.Types.Var @@ -206,7 +206,7 @@ tidyLetBndr rec_tidy_env env@(tidy_env, var_env) id new_info = vanillaIdInfo `setOccInfo` occInfo old_info `setArityInfo` arityInfo old_info - `setStrictnessInfo` zapUsageEnvSig (strictnessInfo old_info) + `setStrictnessInfo` zapDmdEnvSig (strictnessInfo old_info) `setDemandInfo` demandInfo old_info `setInlinePragInfo` inlinePragInfo old_info `setUnfoldingInfo` new_unf ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -73,7 +73,7 @@ module GHC.Types.Demand ( seqDemand, seqDemandList, seqDmdType, seqStrictSig, -- * Zapping usage information - zapUsageDemand, zapUsageEnvSig, zapUsedOnceDemand, zapUsedOnceSig + zapUsageDemand, zapDmdEnvSig, zapUsedOnceDemand, zapUsedOnceSig ) where #include "HsVersions.h" @@ -1571,9 +1571,9 @@ This is weird, so I'm not worried about whether this optimises brilliantly; but it should not fall over. -} -zapUsageEnvSig :: StrictSig -> StrictSig --- Remove the usage environment from the demand -zapUsageEnvSig (StrictSig (DmdType _ ds r)) = mkClosedStrictSig ds r +-- | Remove the demand environment from the signature. +zapDmdEnvSig :: StrictSig -> StrictSig +zapDmdEnvSig (StrictSig (DmdType _ ds r)) = mkClosedStrictSig ds r zapUsageDemand :: Demand -> Demand -- Remove the usage info, but not the strictness info, from the demand ===================================== compiler/GHC/Types/Id/Info.hs ===================================== @@ -650,7 +650,7 @@ zapUsageInfo info = Just (info {demandInfo = zapUsageDemand (demandInfo info)}) zapUsageEnvInfo :: IdInfo -> Maybe IdInfo zapUsageEnvInfo info | hasDemandEnvSig (strictnessInfo info) - = Just (info {strictnessInfo = zapUsageEnvSig (strictnessInfo info)}) + = Just (info {strictnessInfo = zapDmdEnvSig (strictnessInfo info)}) | otherwise = Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2391fad6423e51219c958f964499db6171a7cb73 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2391fad6423e51219c958f964499db6171a7cb73 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 Wed Nov 25 17:08:56 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Wed, 25 Nov 2020 12:08:56 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fbe8fa8c94bb_86c3fc6ab4f115c2215c8@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c4958d33 by Moritz Angermann at 2020-11-25T12:08:44-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - deded16f by David Eichmann at 2020-11-25T12:08:45-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - ace59520 by Andreas Klebinger at 2020-11-25T12:08:45-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - d5c9c7fb by Tim Barnes at 2020-11-25T12:08:47-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - d0fc1f14 by Ben Gamari at 2020-11-25T12:08:47-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - b1d71396 by Matthew Pickering at 2020-11-25T12:08:48-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - 526a1665 by Matthew Pickering at 2020-11-25T12:08:48-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h - libraries/array - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b45267375d83d4172607547f8f82c355a51db0cf...526a166544007a4ded1d3e01ca2a46a17f1406b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b45267375d83d4172607547f8f82c355a51db0cf...526a166544007a4ded1d3e01ca2a46a17f1406b2 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 Wed Nov 25 17:38:58 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Wed, 25 Nov 2020 12:38:58 -0500 Subject: [Git][ghc/ghc][wip/T18891] Fix kind inference for data types. Again. Message-ID: <5fbe96b2c2353_86ce89fc5c2374d9@gitlab.mail> Simon Peyton Jones pushed to branch wip/T18891 at Glasgow Haskell Compiler / GHC Commits: 4bdd70d9 by Simon Peyton Jones at 2020-11-25T17:38:08+00:00 Fix kind inference for data types. Again. This patch improves kcConDecls, when we are inferring the kind of a data type decl. Specifically * In kcConDecls/kcConDecl make it clear that the tc_res_kind argument is only used in the H98 case; and in that case there is not result kind signature; and hence no need for the disgusting splitPiTys in kcConDecls (now thankfully gone). The GADT case is a bit different to before, and much nicer. This is what fixes #18891. See Note [kcConDecls: kind-checking data type decls] * Do not look at the constructor decls of a data/newtype instance in tcDataFamInstanceHeader. See new Note [Kind inference for data family instances] This causes a few knock-on effects in the tests suite, because we require more information than before in the instance /header/. New user-manual material about this in "Kind inference in data type declarations" and "Kind inference for data/newtype instance declarations". * Minor improvement in kcTyClDecl, combining GADT and H98 case. Fixes #18891 - - - - - 22 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Instance.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/poly_kinds.rst - testsuite/tests/dependent/should_fail/T13780a.stderr - testsuite/tests/deriving/should_compile/T11416.hs - testsuite/tests/deriving/should_compile/T9359.hs - testsuite/tests/patsyn/should_fail/T15685.stderr - testsuite/tests/polykinds/T13659.stderr - testsuite/tests/polykinds/T16221a.stderr - testsuite/tests/th/T9692.hs - + testsuite/tests/typecheck/should_compile/T18891.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs - testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/T18891a.hs - + testsuite/tests/typecheck/should_fail/T18891a.stderr - testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs - + testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -2981,7 +2981,7 @@ bindOuterSigTKBndrs_Tv_M :: TcTyMode -> TcM a -> TcM (HsOuterSigTyVarBndrs GhcTc, a) -- Do not push level; do not make implication constraint; use Tvs -- Two major clients of this "bind-only" path are: --- Note [Kind-checking for GADTs] in TyCl +-- Note [Using TyVarTvs for kind-checking GADTs] in GHC.Tc.TyCl -- Note [Checking partial type signatures] bindOuterSigTKBndrs_Tv_M mode = bindOuterTKBndrsX (smVanilla { sm_clone = True, sm_tvtv = True @@ -3294,8 +3294,8 @@ When we /must/ clone. When kind-checking T, we give (a :: kappa1). Then: - In kcConDecl we make a TyVarTv unification variable kappa2 for k2 - (as described in Note [Kind-checking for GADTs], even though this - example is an existential) + (as described in Note [Using TyVarTvs for kind-checking GADTs], + even though this example is an existential) - So we get (b :: kappa2) via bindExplicitTKBndrs_Tv - We end up unifying kappa1 := kappa2, because of the (SameKind a b) ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -1529,27 +1529,16 @@ kcTyClDecl :: TyClDecl GhcRn -> TcTyCon -> TcM () -- result kind signature have already been dealt with -- by inferInitialKind, so we can ignore them here. -kcTyClDecl (DataDecl { tcdLName = (L _ name) - , tcdDataDefn = defn }) tyCon - | HsDataDefn { dd_cons = cons@((L _ (ConDeclGADT {})) : _) - , dd_ctxt = (L _ []) - , dd_ND = new_or_data } <- defn - = -- See Note [Implementation of UnliftedNewtypes] STEP 2 - kcConDecls new_or_data (tyConResKind tyCon) cons - - -- hs_tvs and dd_kindSig already dealt with in inferInitialKind - -- This must be a GADT-style decl, - -- (see invariants of DataDefn declaration) - -- so (a) we don't need to bring the hs_tvs into scope, because the - -- ConDecls bind all their own variables - -- (b) dd_ctxt is not allowed for GADT-style decls, so we can ignore it - - | HsDataDefn { dd_ctxt = ctxt - , dd_cons = cons - , dd_ND = new_or_data } <- defn +kcTyClDecl (DataDecl { tcdLName = (L _ name), tcdDataDefn = defn }) tycon + | HsDataDefn { dd_ctxt = ctxt, dd_cons = cons, dd_ND = new_or_data } <- defn = bindTyClTyVars name $ \ _ _ _ -> - do { _ <- tcHsContext ctxt - ; kcConDecls new_or_data (tyConResKind tyCon) cons + -- NB: binding these tyvars isn't necessary for GADTs, but it does no + -- harm. For GADTs, each data con brings its own tyvars into scope, + -- and the ones from this bindTyClTyVars are either not mentioned or + -- (conceivably) shadowed. + do { traceTc "kcTyClDecl" (ppr tycon $$ ppr (tyConTyVars tycon) $$ ppr (tyConResKind tycon)) + ; _ <- tcHsContext ctxt + ; kcConDecls new_or_data (tyConResKind tycon) cons } kcTyClDecl (SynDecl { tcdLName = L _ name, tcdRhs = rhs }) _tycon @@ -1606,13 +1595,12 @@ kcConGADTArgs new_or_data res_kind con_args = case con_args of kcConDecls :: NewOrData -> Kind -- The result kind signature + -- Used only in H98 case -> [LConDecl GhcRn] -- The data constructors -> TcM () -kcConDecls new_or_data res_kind cons - = mapM_ (wrapLocM_ (kcConDecl new_or_data final_res_kind)) cons - where - (_, final_res_kind) = splitPiTys res_kind - -- See Note [kcConDecls result kind] +-- See Note [kcConDecls: kind-checking data type decls] +kcConDecls new_or_data tc_res_kind cons + = mapM_ (wrapLocM_ (kcConDecl new_or_data tc_res_kind)) cons -- Kind check a data constructor. In additional to the data constructor, -- we also need to know about whether or not its corresponding type was @@ -1623,82 +1611,69 @@ kcConDecl :: NewOrData -> Kind -- Result kind of the type constructor -- Usually Type but can be TYPE UnliftedRep -- or even TYPE r, in the case of unlifted newtype + -- Used only in H98 case -> ConDecl GhcRn -> TcM () -kcConDecl new_or_data res_kind (ConDeclH98 +kcConDecl new_or_data tc_res_kind (ConDeclH98 { con_name = name, con_ex_tvs = ex_tvs , con_mb_cxt = ex_ctxt, con_args = args }) = addErrCtxt (dataConCtxtName [name]) $ discardResult $ bindExplicitTKBndrs_Tv ex_tvs $ do { _ <- tcHsMbContext ex_ctxt - ; kcConH98Args new_or_data res_kind args + ; kcConH98Args new_or_data tc_res_kind args -- We don't need to check the telescope here, -- because that's done in tcConDecl } -kcConDecl new_or_data res_kind (ConDeclGADT +kcConDecl new_or_data + _tc_res_kind -- Not used in GADT case (and doesn't make sense) + (ConDeclGADT { con_names = names, con_bndrs = L _ outer_bndrs, con_mb_cxt = cxt , con_g_args = args, con_res_ty = res_ty }) - = -- Even though the GADT-style data constructor's type is closed, - -- we must still kind-check the type, because that may influence - -- the inferred kind of the /type/ constructor. Example: - -- data T f a where - -- MkT :: f a -> T f a - -- If we don't look at MkT we won't get the correct kind - -- for the type constructor T + = -- See Note [kcConDecls: kind-checking data type decls] addErrCtxt (dataConCtxtName names) $ discardResult $ bindOuterSigTKBndrs_Tv outer_bndrs $ - -- Why "_Tv"? See Note [Kind-checking for GADTs] + -- Why "_Tv"? See Note [Using TyVarTvs for kind-checking GADTs] do { _ <- tcHsMbContext cxt - ; kcConGADTArgs new_or_data res_kind args - ; _ <- tcHsOpenType res_ty + ; traceTc "kcConDecl:GADT {" (ppr names $$ ppr res_ty) + ; con_res_kind <- newOpenTypeKind + ; _ <- tcCheckLHsType res_ty (TheKind con_res_kind) + ; kcConGADTArgs new_or_data con_res_kind args + ; traceTc "kcConDecl:GADT }" (ppr names $$ ppr con_res_kind) ; return () } -{- Note [kcConDecls result kind] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We might have e.g. - data T a :: Type -> Type where ... -or - newtype instance N a :: Type -> Type where .. -in which case, the 'res_kind' passed to kcConDecls will be - Type->Type - -We must look past those arrows, or even foralls, to the Type in the -corner, to pass to kcConDecl c.f. #16828. Hence the splitPiTys here. - -I am a bit concerned about tycons with a declaration like - data T a :: Type -> forall k. k -> Type where ... - -It does not have a CUSK, so kcInferDeclHeader will make a TcTyCon -with tyConResKind of Type -> forall k. k -> Type. Even that is fine: -the splitPiTys will look past the forall. But I'm bothered about -what if the type "in the corner" mentions k? This is incredibly -obscure but something like this could be bad: - data T a :: Type -> foral k. k -> TYPE (F k) where ... - -I bet we are not quite right here, but my brain suffered a buffer -overflow and I thought it best to nail the common cases right now. - -Note [Recursion and promoting data constructors] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -We don't want to allow promotion in a strongly connected component -when kind checking. - -Consider: - data T f = K (f (K Any)) - -When kind checking the `data T' declaration the local env contains the -mappings: - T -> ATcTyCon - K -> APromotionErr - -APromotionErr is only used for DataCons, and only used during type checking -in tcTyClGroup. - -Note [Kind-checking for GADTs] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [kcConDecls: kind-checking data type decls] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +kcConDecls is used when we are inferring the kind of the type +constructor in a data type declaration. E.g. + data T f a = MkT (f a) +we want to infer the kind of 'f' and 'a'. The basic plan is described +in Note [Inferring kinds for type declarations]; here are doing Step 2. + +In the H98 case, for unlifted newtypes only, we need the result kind of +the TyCon, to unify with the argument kind. The tycon's result kind +is not used at all in the GADT case. + +In the GADT case we may have this: + data T f a where + MkT :: forall g b. g b -> T g b +Notice that the variables f,a, and g,b are quite distinct. +Nevertheless, this decl must still influence the kind T (which is, +remember Step 1, something like T :: kappa1 -> kappa2 -> Type), otherwise +we'd infer the bogus kind T :: forall k1 k2. k1 -> k2 -> Type. + +The data constructor type influences the kind of T simply by +kind-checking the result type (T g b), which will force 'f' and 'g' to +have the same kinds. This is the call to + tcCheckLHsType res_ty (TheKind con_res_kind) +Because this is the result type of an arrow, we know the kind must be +of form (TYPE rr), and we get better error messages if we enforce that +here (e.g. test gadt10). + +Note [Using TyVarTvs for kind-checking GADTs] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Consider data Proxy a where @@ -1708,26 +1683,27 @@ Consider It seems reasonable that this should be accepted. But something very strange is going on here: when we're kind-checking this declaration, we need to unify the kind of `a` with k and j -- even though k and j's scopes are local to the type of -MkProxy{1,2}. The best approach we've come up with is to use TyVarTvs during -the kind-checking pass. First off, note that it's OK if the kind-checking pass -is too permissive: we'll snag the problems in the type-checking pass later. -(This extra permissiveness might happen with something like +MkProxy{1,2}. + +In effect, we are simply gathering constraints on the shape of Proxy's +kind, with no skolemisation or implication constraints involved at all. + +The best approach we've come up with is to use TyVarTvs during the +kind-checking pass, rather than ordinary skolems. This is why we use +the "_Tv" variant, bindOuterSigTKBndrs_Tv. + +Our only goal is to gather constraints on the kind of the type constructor; +we do not certify that the data declaration is well-kinded. For example: data SameKind :: k -> k -> Type data Bad a where MkBad :: forall k1 k2 (a :: k1) (b :: k2). Bad (SameKind a b) -which would be accepted if k1 and k2 were TyVarTvs. This is correctly rejected -in the second pass, though. Test case: polykinds/TyVarTvKinds3) -Recall that the kind-checking pass exists solely to collect constraints -on the kinds and to power unification. - -To achieve the use of TyVarTvs, we must be careful to use specialized functions -that produce TyVarTvs, not ordinary skolems. This is why we need -kcExplicitTKBndrs and kcImplicitTKBndrs in GHC.Tc.Gen.HsType, separate from their -tc... variants. +which would be accepted by kcConDecl because k1 and k2 are +TyVarTvs. It is correctly rejected in the second pass, tcConDecl. +(Test case: polykinds/TyVarTvKinds3) -The drawback of this approach is sometimes it will accept a definition that +One drawback of this approach is sometimes it will accept a definition that a (hypothetical) declarative specification would likely reject. As a general rule, we don't want to allow polymorphic recursion without a CUSK. Indeed, the whole point of CUSKs is to allow polymorphic recursion. Yet, the TyVarTvs @@ -1746,6 +1722,23 @@ be rejected (without a CUSK). However, the accepted definitions are indeed well-kinded and any rejected definitions would be accepted with a CUSK, and so this wrinkle need not cause anyone to lose sleep. +Note [Recursion and promoting data constructors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +We don't want to allow promotion in a strongly connected component +when kind checking. + +Consider: + data T f = K (f (K Any)) + +When kind checking the `data T' declaration the local env contains the +mappings: + T -> ATcTyCon + K -> APromotionErr + +APromotionErr is only used for DataCons, and only used during type checking +in tcTyClGroup. + + ************************************************************************ * * \subsection{Type checking} @@ -3214,7 +3207,7 @@ tcConDecl :: KnotTied TyCon -- Representation tycon. Knot-tied! -> ConDecl GhcRn -> TcM [DataCon] -tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs res_kind res_tmpl new_or_data (ConDeclH98 { con_name = lname@(L _ name) , con_ex_tvs = explicit_tkv_nms , con_mb_cxt = hs_ctxt @@ -3224,7 +3217,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Get hold of the existential type variables -- e.g. data T a = forall k (b::k) f. MkT a (f b) - -- Here tmpl_bndrs = {a} + -- Here tc_bndrs = {a} -- hs_qvars = HsQTvs { hsq_implicit = {k} -- , hsq_explicit = {f,b} } @@ -3242,29 +3235,35 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data } - ; let tmpl_tvs = binderVars tmpl_bndrs - ; let fake_ty = mkSpecForAllTys tmpl_tvs $ + ; let tc_tvs = binderVars tc_bndrs + fake_ty = mkSpecForAllTys tc_tvs $ mkInvisForAllTys exp_tvbndrs $ mkPhiTy ctxt $ mkVisFunTys arg_tys $ unitTy -- That type is a lie, of course. (It shouldn't end in ()!) -- And we could construct a proper result type from the info - -- at hand. But the result would mention only the tmpl_tvs, + -- at hand. But the result would mention only the univ_tvs, -- and so it just creates more work to do it right. Really, -- we're only doing this to find the right kind variables to -- quantify over, and this type is fine for that purpose. - -- exp_tvs have explicit, user-written binding sites + -- exp_tvbndrs have explicit, user-written binding sites -- the kvs below are those kind variables entirely unmentioned by the user -- and discovered only by generalization ; kvs <- kindGeneralizeAll fake_ty - ; let skol_tvs = kvs ++ tmpl_tvs + ; let skol_tvs = tc_tvs ++ kvs ++ binderVars exp_tvbndrs ; reportUnsolvedEqualities skol_info skol_tvs tclvl wanted - - -- Zonk to Types + -- The skol_info claims that all the variables are bound + -- by the data constructor decl, whereas actually the + -- univ_tvs are bound by the data type decl itself. It + -- would be better to have a doubly-nested implication. + -- But that just doesn't seem worth it. + -- See test dependent/should_fail/T13780a + + -- Zonk to Types ; (ze, qkvs) <- zonkTyBndrs kvs ; (ze, user_qtvbndrs) <- zonkTyVarBindersX ze exp_tvbndrs ; arg_tys <- zonkScaledTcTypesToTypesX ze arg_tys @@ -3272,15 +3271,13 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data -- Can't print univ_tvs, arg_tys etc, because we are inside the knot here ; traceTc "tcConDecl 2" (ppr name $$ ppr field_lbls) - ; let - univ_tvbs = tyConInvisTVBinders tmpl_bndrs - univ_tvs = binderVars univ_tvbs - ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs - ex_tvs = binderVars ex_tvbs - -- For H98 datatypes, the user-written tyvar binders are precisely - -- the universals followed by the existentials. - -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. - user_tvbs = univ_tvbs ++ ex_tvbs + ; let univ_tvbs = tyConInvisTVBinders tc_bndrs + ex_tvbs = mkTyVarBinders InferredSpec qkvs ++ user_qtvbndrs + ex_tvs = binderVars ex_tvbs + -- For H98 datatypes, the user-written tyvar binders are precisely + -- the universals followed by the existentials. + -- See Note [DataCon user type variable binders] in GHC.Core.DataCon. + user_tvbs = univ_tvbs ++ ex_tvbs ; traceTc "tcConDecl 2" (ppr name) ; is_infix <- tcConIsInfixH98 name hs_args @@ -3288,7 +3285,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data ; fam_envs <- tcGetFamInstEnvs ; dc <- buildDataCon fam_envs name is_infix rep_nm stricts Nothing field_lbls - univ_tvs ex_tvs user_tvbs + tc_tvs ex_tvs user_tvbs [{- no eq_preds -}] ctxt arg_tys res_tmpl rep_tycon tag_map -- NB: we put data_tc, the type constructor gotten from the @@ -3299,7 +3296,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs res_kind res_tmpl new_or_data where skol_info = DataConSkol name -tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data +tcConDecl rep_tycon tag_map tc_bndrs _res_kind res_tmpl new_or_data -- NB: don't use res_kind here, as it's ill-scoped. Instead, -- we get the res_kind by typechecking the result type. (ConDeclGADT { con_names = names @@ -3344,7 +3341,7 @@ tcConDecl rep_tycon tag_map tmpl_bndrs _res_kind res_tmpl new_or_data ; res_ty <- zonkTcTypeToTypeX ze res_ty ; let (univ_tvs, ex_tvs, tvbndrs', eq_preds, arg_subst) - = rejigConRes tmpl_bndrs res_tmpl tvbndrs res_ty + = rejigConRes tc_bndrs res_tmpl tvbndrs res_ty -- See Note [Checking GADT return types] ctxt' = substTys arg_subst ctxt @@ -3532,9 +3529,9 @@ errors reported in one pass. See #7175, and #10836. -- TI :: forall b1 c1. (b1 ~ c1) => b1 -> :R7T b1 c1 -- In this case orig_res_ty = T (e,e) -rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result type; e.g. - -- data instance T [a] b c ... - -- gives template ([a,b,c], T [a] b c) +rejigConRes :: [KnotTied TyConBinder] -- Template for result type; e.g. + -> KnotTied Type -- data instance T [a] b c ... + -- gives template ([a,b,c], T [a] b c) -> [InvisTVBinder] -- The constructor's type variables (both inferred and user-written) -> KnotTied Type -- res_ty -> ([TyVar], -- Universal @@ -3546,10 +3543,10 @@ rejigConRes :: [KnotTied TyConBinder] -> KnotTied Type -- Template for result -- We don't check that the TyCon given in the ResTy is -- the same as the parent tycon, because checkValidDataCon will do it -- NB: All arguments may potentially be knot-tied -rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty +rejigConRes tc_tvbndrs res_tmpl dc_tvbndrs res_ty -- E.g. data T [a] b c where -- MkT :: forall x y z. T [(x,y)] z z - -- The {a,b,c} are the tmpl_tvs, and the {x,y,z} are the dc_tvs + -- The {a,b,c} are the tc_tvs, and the {x,y,z} are the dc_tvs -- (NB: unlike the H98 case, the dc_tvs are not all existential) -- Then we generate -- Univ tyvars Eq-spec @@ -3564,7 +3561,7 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- , [], [x,y,z] -- , [a~(x,y),b~z], ) | Just subst <- tcMatchTy res_tmpl res_ty - = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tmpl_tvs dc_tvs subst + = let (univ_tvs, raw_eqs, kind_subst) = mkGADTVars tc_tvs dc_tvs subst raw_ex_tvs = dc_tvs `minusList` univ_tvs (arg_subst, substed_ex_tvs) = substTyVarBndrs kind_subst raw_ex_tvs @@ -3591,10 +3588,10 @@ rejigConRes tmpl_bndrs res_tmpl dc_tvbndrs res_ty -- albeit bogus, relying on checkValidDataCon to check the -- bad-result-type error before seeing that the other fields look odd -- See Note [Checking GADT return types] - = (tmpl_tvs, dc_tvs `minusList` tmpl_tvs, dc_tvbndrs, [], emptyTCvSubst) + = (tc_tvs, dc_tvs `minusList` tc_tvs, dc_tvbndrs, [], emptyTCvSubst) where - dc_tvs = binderVars dc_tvbndrs - tmpl_tvs = binderVars tmpl_bndrs + dc_tvs = binderVars dc_tvbndrs + tc_tvs = binderVars tc_tvbndrs {- Note [mkGADTVars] ~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/TyCl/Instance.hs ===================================== @@ -688,9 +688,8 @@ tcDataFamInstDecl mb_clsinfo tv_skol_env -- Do /not/ check that the number of patterns = tyConArity fam_tc -- See [Arity of data families] in GHC.Core.FamInstEnv ; (qtvs, pats, res_kind, stupid_theta) - <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs - fixity hs_ctxt hs_pats m_ksig hs_cons - new_or_data + <- tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity + hs_ctxt hs_pats m_ksig new_or_data -- Eta-reduce the axiom if possible -- Quite tricky: see Note [Implementing eta reduction for data families] @@ -857,7 +856,7 @@ TyVarEnv will simply be empty, and there is nothing to worry about. tcDataFamInstHeader :: AssocInstInfo -> TyCon -> HsOuterFamEqnTyVarBndrs GhcRn -> LexicalFixity -> LHsContext GhcRn - -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> [LConDecl GhcRn] + -> HsTyPats GhcRn -> Maybe (LHsKind GhcRn) -> NewOrData -> TcM ([TyVar], [Type], Kind, ThetaType) -- The "header" of a data family instance is the part other than @@ -865,7 +864,7 @@ tcDataFamInstHeader -- e.g. data instance D [a] :: * -> * where ... -- Here the "header" is the bit before the "where" tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity - hs_ctxt hs_pats m_ksig hs_cons new_or_data + hs_ctxt hs_pats m_ksig new_or_data = do { traceTc "tcDataFamInstHeader {" (ppr fam_tc <+> ppr hs_pats) ; (tclvl, wanted, (scoped_tvs, (stupid_theta, lhs_ty, master_res_kind, instance_res_kind))) <- pushLevelAndSolveEqualitiesX "tcDataFamInstHeader" $ @@ -884,8 +883,8 @@ tcDataFamInstHeader mb_clsinfo fam_tc outer_bndrs fixity -- Add constraints from the result signature ; res_kind <- tc_kind_sig m_ksig - -- Add constraints from the data constructors - ; kcConDecls new_or_data res_kind hs_cons + -- Do not add constraints from the data constructors + -- See Note [Kind inference for data family instances] -- Check that the result kind of the TyCon applied to its args -- is compatible with the explicit signature (or Type, if there @@ -1049,6 +1048,86 @@ however, so this Note aims to describe these subtleties: themselves. Heavy sigh. But not truly hard; that's what tcbVisibilities does. +Note [Kind inference for data family instances] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider this GADT-style data type declaration, where I have used +fresh variables in the data constructor's type, to stress that c,d are +quite distinct from a,b. + data T a b where + MkT :: forall c d. c d -> T c d + +Following Note [Inferring kinds for type declarations] in GHC.Tc.TyCl, +to infer T's kind, we initially give T :: kappa, a monomorpic kind, +gather constraints from the header and data constructors, and conclude + T :: (kappa1 -> type) -> kappa1 -> Type +Then we generalise, giving + T :: forall k. (k->Type) -> k -> Type + +Now what about a data /instance/ decl + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p Int where ... + +No doubt here! The poly-kinded T is instantiated with k=Type, so the +header really looks like + data instance T @Type (p :: Type->Type) Int where ... + +But what about this? + data instance T p q where + MkT :: forall r. r Int -> T r Int + +So what kind do 'p' and 'q' have? No clues from the header, but from +the data constructor we can clearly see that (r :: Type->Type). Does +that mean that the the /entire data instance/ is instantiated at Type, +like this? + data instance T @Type (p :: Type->Type) (q :: Type) where + ... + +Not at all! This is a /GADT/-style decl, so the kind argument might +be specialised in this particular data constructor, thus: + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall (r :: Type -> Type). + r Int -> T @Type r Int +(and perhaps specialised differently in some other data +constructor MkT2). + +The key difference in this case and 'data T' at the top of this Note +is that we have no known kind for 'data T'. We thus forbid different +specialisations of T in its constructors, in an attempt to avoid +inferring polymorphic recursion. In data family T, however, there is +no problem with polymorphic recursion: we already /fully know/ T's +kind -- that came from the family declaration, and is not influenced +by the data instances -- and hence we /can/ specialise T's kind +differently in different GADT data constructors. + +SHORT SUMMARY: in a data instance decl, it's not clear whether kind +constraints arising from the data constructors should be considered +local to the (GADT) data /constructor/ or should apply to the entire +data instance. + +DESIGN CHOICE: in data/newtype family instance declarations, we ignore +the /data constructor/ declarations altogether, looking only at the +data instance /header/. + +Observations: +* This choice is simple to describe, as well as simple to implment. + For a data/newtype instance decl, the instance kinds are influenced + /only/ by the header. + +* We could treat Haskell-98 style data-instance decls differently, by + taking the data constructors into account, since there are no GADT + issues. But we don't, for simplicity, and because it means you can + understand the data type instance by looking only at the header. + +* Newtypes can be declared in GADT syntax, but they can't do GADT-style + specialisation, so like Haskell-98 definitions we could take the + data constructors into account. Again we don't, for the same reason. + +So for now at least, we keep the simplest choice. See #18891 and !4419 +for more discussion of this issue. + +Kind inference for data types (Xie et al) https://arxiv.org/abs/1911.06153 +takes a slightly different approach. -} ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -40,6 +40,12 @@ Compiler - GHCi's ``:kind!`` command now expands through type synonyms in addition to type families. See :ghci-cmd:`:kind`. +- Kind inference for data/newtype instance declarations is sligtly + more restrictive than before. See the user manual :ref:`kind-inference-data-family-instances`. + This is a breaking change, albeit + a fairly obscure one that corrects a specification bug. + + ``ghc-prim`` library ~~~~~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/exts/poly_kinds.rst ===================================== @@ -130,8 +130,45 @@ This rule has occasionally-surprising consequences (see The kind-polymorphism from the class declaration makes ``D1`` kind-polymorphic, but not so ``D2``; and similarly ``F1``, ``F2``. +Kind inference in type signatures +--------------------------------- + +When kind-checking a type, GHC considers only what is written in that +type when figuring out how to generalise the type's kind. + +For example, +consider these definitions (with :extension:`ScopedTypeVariables`): :: + + data Proxy a -- Proxy :: forall k. k -> Type + p :: forall a. Proxy a + p = Proxy :: Proxy (a :: Type) + +GHC reports an error, saying that the kind of ``a`` should be a kind variable +``k``, not ``Type``. This is because, by looking at the type signature +``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not +restricted to be ``Type``. The function definition is then rejected for being +more specific than its type signature. + +.. _explicit-kind-quantification: + +Explicit kind quantification +---------------------------- + +Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, +as in these examples: :: + + data Proxy :: forall k. k -> Type + f :: (forall k (a :: k). Proxy a -> ()) -> Int + +Note that the second example has a ``forall`` that binds both a kind ``k`` and +a type variable ``a`` of kind ``k``. In general, there is no limit to how +deeply nested this sort of dependency can work. However, the dependency must +be well-scoped: ``forall (a :: k) k. ...`` is an error. + + .. _inferring-variable-order: + Inferring the order of variables in a type/class declaration ------------------------------------------------------------ @@ -490,41 +527,91 @@ This also applies to GADT-style data instances: :: -- • In the data instance declaration for ‘T’ -Kind inference in closed type families --------------------------------------- +Kind inference in data type declarations +---------------------------------------- -Although all open type families are considered to have a complete -user-supplied kind signature, we can relax this condition for closed -type families, where we have equations on which to perform kind -inference. GHC will infer kinds for the arguments and result types of a -closed type family. +Consider the declaration :: -GHC supports *kind-indexed* type families, where the family matches both -on the kind and type. GHC will *not* infer this behaviour without a -complete user-supplied kind signature, as doing so would sometimes infer -non-principal types. Indeed, we can see kind-indexing as a form -of polymorphic recursion, where a type is used at a kind other than -its most general in its own definition. + data T1 f a = MkT1 (f a) + data T2 f a where + MkT2 :: f a -> T f a -For example: :: +In both cases GHC looks at the data constructor declarations to +give constraints on the kind of ``T``, yielding :: - type family F1 a where - F1 True = False - F1 False = True - F1 x = x - -- F1 fails to compile: kind-indexing is not inferred + T1, T2 :: forall k. (k -> Type) -> k -> Type - type family F2 (a :: k) where - F2 True = False - F2 False = True - F2 x = x - -- F2 fails to compile: no complete signature +Consider the type :: + + data G (a :: k) where + GInt :: G Int + GMaybe :: G Maybe + +This datatype ``G`` is GADT-like in both its kind and its type. Suppose you +have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that +``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and +``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` +be in effect, but pattern-matching on ``G`` requires no extension beyond +:extension:`GADTs`. That this works is actually a straightforward extension +of regular GADTs and a consequence of the fact that kinds and types are the +same. + +Note that the datatype ``G`` is used at different kinds in its body, and +therefore that kind-indexed GADTs use a form of polymorphic recursion. +It is thus only possible to use this feature if you have provided a +complete user-supplied kind signature (CUSK) +for the datatype (:ref:`complete-kind-signatures`), or a standalone +kind signature (:ref:`standalone-kind-signatures`); +in the case of ``G`` we have a CUSK. +If you wish to see the kind indexing explicitly, you can do so by enabling :ghc-flag:`-fprint-explicit-kinds` and querying ``G`` with GHCi's :ghci-cmd:`:info` command: :: + + > :set -fprint-explicit-kinds + > :info G + type role G nominal nominal + type G :: forall k. k -> Type + data G @k a where + GInt :: G @Type Int + GMaybe :: G @(Type -> Type) Maybe + +where you can see the GADT-like nature of the two constructors. + +.. _kind-inference-data-family-instances: + +Kind inference for data/newtype instance declarations +----------------------------------------------------- + +Consider these declarations :: + + data family T :: forall k. (k->Type) -> k -> Type + + data instance T p q where + MkT :: forall r. r Int -> T r Int + +Here ``T`` has an invisible kind argument; and perhaps it is instantiated +to ``Type`` in the instance, thus :: + + data instance T @Type (p :: Type->Type) (q :: Type) where + MkT :: forall r. r Int -> T r Int + +Or perhaps we intended the specialisation to be in the GADT data +constructor, thus :: + + data instance T @k (p :: k->Type) (q :: k) where + MkT :: forall r. r Int -> T @Type r Int + +It gets more complicated if there are multiple constructors. In +general, there is no principled way to tell which type specialisation +comes from the data instance, and which from the individual GADT data +constructors. + +So GHC implements this rule: in data/newtype instance declararations +(unlike ordinary data/newtype declarations) we do *not* look at the +constructor declarations when inferring the shape of the instance +header. The principle is that *the instantiation of the data instance +should be apparent from the header alone*. This principle makes the +program easier to understand, and avoids the swamp of complexity +indicated above. - type family F3 (a :: k) :: k where - F3 True = False - F3 False = True - F3 x = x - -- OK Kind inference in class instance declarations --------------------------------------------- @@ -555,43 +642,8 @@ infrastructure, and it's not clear the payoff is worth it. If you want to restrict ``b``\ 's kind in the instance above, just use a kind signature in the instance head. -Kind inference in type signatures ---------------------------------- - -When kind-checking a type, GHC considers only what is written in that -type when figuring out how to generalise the type's kind. - -For example, -consider these definitions (with :extension:`ScopedTypeVariables`): :: - - data Proxy a -- Proxy :: forall k. k -> Type - p :: forall a. Proxy a - p = Proxy :: Proxy (a :: Type) - -GHC reports an error, saying that the kind of ``a`` should be a kind variable -``k``, not ``Type``. This is because, by looking at the type signature -``forall a. Proxy a``, GHC assumes ``a``'s kind should be generalised, not -restricted to be ``Type``. The function definition is then rejected for being -more specific than its type signature. - -.. _explicit-kind-quantification: - -Explicit kind quantification ----------------------------- - -Enabled by :extension:`PolyKinds`, GHC supports explicit kind quantification, -as in these examples: :: - - data Proxy :: forall k. k -> Type - f :: (forall k (a :: k). Proxy a -> ()) -> Int - -Note that the second example has a ``forall`` that binds both a kind ``k`` and -a type variable ``a`` of kind ``k``. In general, there is no limit to how -deeply nested this sort of dependency can work. However, the dependency must -be well-scoped: ``forall (a :: k) k. ...`` is an error. - -Implicit quantification in type synonyms and type family instances ------------------------------------------------------------------- +Kind inference in type synonyms and type family instances +--------------------------------------------------------- Consider the scoping rules for type synonyms and type family instances, such as these:: @@ -706,29 +758,44 @@ kinds. Consequently, visible dependent quantifiers are rejected in any context that is unambiguously the type of a term. They are also rejected in the types of data constructors. -Kind-indexed GADTs ------------------- +Kind inference in closed type families +-------------------------------------- -Consider the type :: +Although all open type families are considered to have a complete +user-supplied kind signature (:ref:`complete-kind-signatures`), +we can relax this condition for closed +type families, where we have equations on which to perform kind +inference. GHC will infer kinds for the arguments and result types of a +closed type family. - data G (a :: k) where - GInt :: G Int - GMaybe :: G Maybe +GHC supports *kind-indexed* type families, where the family matches both +on the kind and type. GHC will *not* infer this behaviour without a +complete user-supplied kind signature or standalone kind +signature (see :ref:`standalone-kind-signatures`), +because doing so would sometimes infer +non-principal types. Indeed, we can see kind-indexing as a form +of polymorphic recursion, where a type is used at a kind other than +its most general in its own definition. -This datatype ``G`` is GADT-like in both its kind and its type. Suppose you -have ``g :: G a``, where ``a :: k``. Then pattern matching to discover that -``g`` is in fact ``GMaybe`` tells you both that ``k ~ (Type -> Type)`` and -``a ~ Maybe``. The definition for ``G`` requires that :extension:`PolyKinds` -be in effect, but pattern-matching on ``G`` requires no extension beyond -:extension:`GADTs`. That this works is actually a straightforward extension -of regular GADTs and a consequence of the fact that kinds and types are the -same. +For example: :: -Note that the datatype ``G`` is used at different kinds in its body, and -therefore that kind-indexed GADTs use a form of polymorphic recursion. -It is thus only possible to use this feature if you have provided a -complete user-supplied kind signature -for the datatype (:ref:`complete-kind-signatures`). + type family F1 a where + F1 True = False + F1 False = True + F1 x = x + -- F1 fails to compile: kind-indexing is not inferred + + type family F2 (a :: k) where + F2 True = False + F2 False = True + F2 x = x + -- F2 fails to compile: no complete signature + + type family F3 (a :: k) :: k where + F3 True = False + F3 False = True + F3 x = x + -- OK Higher-rank kinds ----------------- ===================================== testsuite/tests/dependent/should_fail/T13780a.stderr ===================================== @@ -3,7 +3,7 @@ T13780a.hs:9:40: error: • Couldn't match kind ‘a’ with ‘Bool’ Expected kind ‘Foo a’, but ‘MkFoo’ has kind ‘Foo Bool’ ‘a’ is a rigid type variable bound by - a family instance declaration + the data constructor ‘SMkFoo’ at T13780a.hs:9:20-31 • In the second argument of ‘(~)’, namely ‘MkFoo’ In the definition of data constructor ‘SMkFoo’ ===================================== testsuite/tests/deriving/should_compile/T11416.hs ===================================== @@ -12,9 +12,11 @@ newtype T f (a :: ConstantT Type f) = T (f a) deriving Functor data family TFam1 (f :: k1) (a :: k2) -newtype instance TFam1 f (ConstantT a f) = TFam1 (f a) +newtype instance TFam1 (f :: k -> Type) (ConstantT (a :: k) f) + = TFam1 (f a) deriving Functor data family TFam2 (f :: k1) (a :: k2) -newtype instance TFam2 f (a :: ConstantT Type f) = TFam2 (f a) +newtype instance TFam2 (f :: Type -> Type) (a :: ConstantT Type f) + = TFam2 (f a) deriving Functor ===================================== testsuite/tests/deriving/should_compile/T9359.hs ===================================== @@ -9,6 +9,5 @@ data Cmp a where deriving (Show, Eq) data family CmpInterval (a :: Cmp k) (b :: Cmp k) :: Type -data instance CmpInterval (V c) Sup = Starting c +data instance CmpInterval (V (c :: Type)) Sup = Starting c deriving( Show ) - ===================================== testsuite/tests/patsyn/should_fail/T15685.stderr ===================================== @@ -1,13 +1,13 @@ T15685.hs:13:24: error: - • Could not deduce: a ~ [k0] - from the context: as ~ (a1 : as1) + • Could not deduce: k ~ [k0] + from the context: as ~ (a : as1) bound by a pattern with constructor: - Here :: forall {a1} (f :: a1 -> *) (a2 :: a1) (as :: [a1]). - f a2 -> NS f (a2 : as), + Here :: forall {k} (f :: k -> *) (a :: k) (as :: [k]). + f a -> NS f (a : as), in a pattern synonym declaration at T15685.hs:13:19-26 - ‘a’ is a rigid type variable bound by + ‘k’ is a rigid type variable bound by the inferred type of HereNil :: NS f as at T15685.hs:13:9-15 Possible fix: add a type signature for ‘HereNil’ ===================================== testsuite/tests/polykinds/T13659.stderr ===================================== @@ -1,6 +1,6 @@ -T13659.hs:14:27: error: - • Expected a type, but ‘a’ has kind ‘[*]’ - • In the first argument of ‘Format’, namely ‘'[Int, a]’ - In the type ‘Format '[Int, a]’ +T13659.hs:14:15: error: + • Expected kind ‘[*]’, but ‘a’ has kind ‘*’ + • In the first argument of ‘Format’, namely ‘a’ + In the type ‘Format a’ In the definition of data constructor ‘I’ ===================================== testsuite/tests/polykinds/T16221a.stderr ===================================== @@ -1,7 +1,7 @@ T16221a.hs:6:49: error: - • Expected kind ‘k’, but ‘b’ has kind ‘k1’ - ‘k1’ is a rigid type variable bound by + • Expected kind ‘k’, but ‘b’ has kind ‘k2’ + ‘k2’ is a rigid type variable bound by an explicit forall k (b :: k) at T16221a.hs:6:20 ‘k’ is a rigid type variable bound by ===================================== testsuite/tests/th/T9692.hs ===================================== @@ -12,7 +12,7 @@ class C a where data F a (b :: k) :: Type instance C Int where - data F Int x = FInt x + data F Int (x :: Type) = FInt x $( do info <- qReify (mkName "F") runIO $ putStrLn $ pprint info ===================================== testsuite/tests/typecheck/should_compile/T18891.hs ===================================== @@ -0,0 +1,16 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +data family T2 (a :: k) +data instance T2 a where + MkT2 :: T2 Maybe + +newtype N3 :: forall k -> TYPE k where + MkN3 :: N3 m -> N3 m + +type N4 :: forall k -> TYPE k +newtype N4 :: forall k -> TYPE k where + MkN4 :: N4 m -> N4 m ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnassociatedFamily.hs ===================================== @@ -4,6 +4,8 @@ {-# LANGUAGE PolyKinds #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} +{-# LANGUAGE TypeApplications #-} module UnliftedNewtypesUnassociatedFamily where @@ -20,7 +22,16 @@ newtype instance DFT ('TupleRep '[ 'IntRep, 'WordRep]) data instance DFT 'LiftedRep = MkDFT4 | MkDFT5 data family DF :: TYPE (r :: RuntimeRep) -newtype instance DF = MkDF1 Int# -newtype instance DF = MkDF2 Word# -newtype instance DF = MkDF3 (# Int#, Word# #) + +-- Use a type application +newtype instance DF @IntRep = MkDF1 Int# + +-- Use a kind signature +newtype instance DF :: TYPE 'WordRep where + MkDF2 :: Word# -> DF + +-- Also uses a kind signature +newtype instance DF :: TYPE ('TupleRep '[ 'IntRep, 'WordRep ]) where + MkDF3 :: (# Int#, Word# #) -> DF + data instance DF = MkDF4 | MkDF5 ===================================== testsuite/tests/typecheck/should_compile/UnliftedNewtypesUnifySig.hs ===================================== @@ -10,14 +10,14 @@ module UnliftedNewtypesUnassociatedFamily where import GHC.Int (Int(I#)) -import GHC.Exts (Int#,Word#,RuntimeRep(IntRep)) +import GHC.Exts (Int#,Word#,RuntimeRep(IntRep, WordRep)) import GHC.Exts (TYPE) type KindOf (a :: TYPE k) = k data family D (a :: TYPE r) :: TYPE r -newtype instance D a = MkWordD Word# +newtype instance D (a :: TYPE 'WordRep) = MkWordD Word# -newtype instance D a :: TYPE (KindOf a) where - MkIntD :: forall (a :: TYPE 'IntRep). Int# -> D a +newtype instance D (a :: TYPE 'IntRep) :: TYPE (KindOf a) where + MkIntD :: forall (b :: TYPE 'IntRep). Int# -> D b ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -728,4 +728,5 @@ test('T18831', normal, compile, ['']) test('T18920', normal, compile, ['']) test('T15942', normal, compile, ['']) test('ClassDefaultInHsBoot', [extra_files(['ClassDefaultInHsBootA1.hs','ClassDefaultInHsBootA2.hs','ClassDefaultInHsBootA2.hs-boot','ClassDefaultInHsBootA3.hs'])], multimod_compile, ['ClassDefaultInHsBoot', '-v0']) +test('T18891', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T18891a.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE GADTs, UnliftedNewtypes, StandaloneKindSignatures, RankNTypes, TypeFamilies, PolyKinds #-} + +module T18891 where + +import GHC.Exts( TYPE ) + +newtype N1 :: forall k. TYPE k where + MkN1 :: N1 -> N1 + +type N2 :: forall k. TYPE k +newtype N2 :: forall k. TYPE k where + MkN2 :: N2 -> N2 + ===================================== testsuite/tests/typecheck/should_fail/T18891a.stderr ===================================== @@ -0,0 +1,12 @@ + +T18891a.hs:8:4: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN1 :: N1 -> N1 + • In the definition of data constructor ‘MkN1’ + In the newtype declaration for ‘N1’ + +T18891a.hs:12:3: error: + • A newtype constructor must have a return type of form T a1 ... an + MkN2 :: N2 -> N2 + • In the definition of data constructor ‘MkN2’ + In the newtype declaration for ‘N2’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesFamilyKindFail2.stderr ===================================== @@ -1,11 +1,5 @@ -UnliftedNewtypesFamilyKindFail2.hs:12:20: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the newtype instance declaration for ‘F’ - -UnliftedNewtypesFamilyKindFail2.hs:12:31: - Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ - In the first argument of ‘F’, namely ‘5’ - In the type ‘(F 5)’ - In the definition of data constructor ‘MkF’ +UnliftedNewtypesFamilyKindFail2.hs:12:20: error: + • Expected a type, but ‘5’ has kind ‘GHC.Num.Natural.Natural’ + • In the first argument of ‘F’, namely ‘5’ + In the newtype instance declaration for ‘F’ ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.hs ===================================== @@ -0,0 +1,23 @@ +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE GADTs #-} + +module UnliftedNewtypesUnassociatedFamily where + +import GHC.Int (Int(I#)) +import GHC.Word (Word(W#)) +import GHC.Exts (Int#,Word#) +import GHC.Exts (TYPE,RuntimeRep(LiftedRep,IntRep,WordRep,TupleRep)) + +data family DF :: TYPE (r :: RuntimeRep) + +-- All these fail: see #18891 and !4419 +-- See Note [Kind inference for data family instances] +-- in GHC.Tc.TyCl.Instance +newtype instance DF = MkDF1a Int# +newtype instance DF = MkDF2a Word# +newtype instance DF = MkDF3a (# Int#, Word# #) ===================================== testsuite/tests/typecheck/should_fail/UnliftedNewtypesUnassociatedFamilyFail.stderr ===================================== @@ -0,0 +1,18 @@ + +UnliftedNewtypesUnassociatedFamilyFail.hs:21:30: error: + • Expecting a lifted type, but ‘Int#’ is unlifted + • In the type ‘Int#’ + In the definition of data constructor ‘MkDF1a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:22:30: error: + • Expecting a lifted type, but ‘Word#’ is unlifted + • In the type ‘Word#’ + In the definition of data constructor ‘MkDF2a’ + In the newtype instance declaration for ‘DF’ + +UnliftedNewtypesUnassociatedFamilyFail.hs:23:30: error: + • Expecting a lifted type, but ‘(# Int#, Word# #)’ is unlifted + • In the type ‘(# Int#, Word# #)’ + In the definition of data constructor ‘MkDF3a’ + In the newtype instance declaration for ‘DF’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -546,6 +546,7 @@ test('UnliftedNewtypesConstraintFamily', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKind', normal, compile_fail, ['']) test('UnliftedNewtypesMismatchedKindRecord', normal, compile_fail, ['']) test('UnliftedNewtypesMultiFieldGadt', normal, compile_fail, ['']) +test('UnliftedNewtypesUnassociatedFamilyFail', normal, compile_fail, ['']) test('T13834', normal, compile_fail, ['']) test('T17077', normal, compile_fail, ['']) test('T16512a', normal, compile_fail, ['']) @@ -589,3 +590,4 @@ test('T18640b', normal, compile_fail, ['']) test('T18640c', normal, compile_fail, ['']) test('T10709', normal, compile_fail, ['']) test('T10709b', normal, compile_fail, ['']) +test('T18891a', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bdd70d9ad7b4de288341e0797d314c1166dd2ce -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bdd70d9ad7b4de288341e0797d314c1166dd2ce 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 Wed Nov 25 17:42:47 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Wed, 25 Nov 2020 12:42:47 -0500 Subject: [Git][ghc/ghc][wip/T18894] Try to find all top-level bindings interesting Message-ID: <5fbe979791669_86c111d4a0023957@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: 549af695 by Sebastian Graf at 2020-11-25T18:42:41+01:00 Try to find all top-level bindings interesting - - - - - 1 changed file: - compiler/GHC/Core/Opt/DmdAnal.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -575,7 +575,7 @@ strict in |y|. -- or not. Other top-level bindings are boring. isInterestingTopLevelFn :: Id -> Bool isInterestingTopLevelFn id = - typeArity (idType id) `lengthExceeds` 0 + typeArity (idType id) `lengthExceeds` 0 || True dmdTransform :: AnalEnv -- ^ The strictness environment -> Id -- ^ The function View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/549af6957748293cd497ccbef421c30666b56f31 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/549af6957748293cd497ccbef421c30666b56f31 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 Wed Nov 25 17:55:55 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Wed, 25 Nov 2020 12:55:55 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/raPlatform_fix Message-ID: <5fbe9aab2cacb_86cbee259024499c@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/raPlatform_fix at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/raPlatform_fix 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 Wed Nov 25 17:57:31 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Wed, 25 Nov 2020 12:57:31 -0500 Subject: [Git][ghc/ghc][wip/andreask/raPlatform_fix] RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Message-ID: <5fbe9b0b6e117_86c113a5b2c2451cc@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/raPlatform_fix at Glasgow Haskell Compiler / GHC Commits: f67dac44 by Andreas Klebinger at 2020-11-25T18:56:14+01:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 - - - - - 2 changed files: - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -283,7 +283,8 @@ regAlloc_spin config spinCount triv regsFree slotsFree slotsCount debug_codeGrap , raCoalesced = rmCoalesce , raSpillStats = spillStats , raSpillCosts = spillCosts - , raSpilled = code_spilled } + , raSpilled = code_spilled + , raPlatform = platform } -- Bundle up all the register allocator statistics. -- .. but make sure to drop them on the floor if they're not ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs ===================================== @@ -79,7 +79,10 @@ data RegAllocStats statics instr , raSpillCosts :: SpillCostInfo -- | Code with spill instructions added. - , raSpilled :: [LiveCmmDecl statics instr] } + , raSpilled :: [LiveCmmDecl statics instr] + + -- | Target platform + , raPlatform = platform } -- a successful coloring View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f67dac44951e5abd16f3813a05caf3584ff5aa24 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f67dac44951e5abd16f3813a05caf3584ff5aa24 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 Wed Nov 25 18:04:11 2020 From: gitlab at gitlab.haskell.org (Benjamin Maurer) Date: Wed, 25 Nov 2020 13:04:11 -0500 Subject: [Git][ghc/ghc][wip/andreask/raPlatform_fix] Replaced accidental assignment with appropriate type annotation. Message-ID: <5fbe9c9bd5dea_86c7d5924024673a@gitlab.mail> Benjamin Maurer pushed to branch wip/andreask/raPlatform_fix at Glasgow Haskell Compiler / GHC Commits: 1ab4a79d by Benjamin Maurer at 2020-11-25T13:04:10-05:00 Replaced accidental assignment with appropriate type annotation. - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs ===================================== @@ -82,7 +82,8 @@ data RegAllocStats statics instr , raSpilled :: [LiveCmmDecl statics instr] -- | Target platform - , raPlatform = platform } + , raPlatform :: !Platform + } -- a successful coloring View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1ab4a79dacb767ff893019eeea6f2965227968d2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1ab4a79dacb767ff893019eeea6f2965227968d2 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 Wed Nov 25 18:38:18 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Wed, 25 Nov 2020 13:38:18 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fbea49a63f79_86c879fa9c25102a@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 2ca883f5 by Shayne Fletcher at 2020-11-25T13:37:53-05:00 Record dot syntax - - - - - 27 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3727,6 +3727,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate {pb_fIELDS = flds, pb_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -457,6 +479,50 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_fIELD :: Located FastString + , gf_getField :: LHsExpr p -- Equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_fIELDS :: [Located FastString] + , proj_projection :: LHsExpr p -- Equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -580,6 +646,10 @@ data RecordUpdTc = RecordUpdTc , rupd_wrap :: HsWrapper -- See note [Record Update HsWrapper] } +data GetFieldTc = GetFieldTc +data ProjectionTc = ProjectionTc +data RecordDotUpdTc = RecordDotUpdTc + -- | HsWrap appears only in typechecker output -- Invariant: The contained Expr is *NOT* itself an HsWrap. -- See Note [Detecting forced eta expansion] in "GHC.HsToCore.Expr". @@ -648,6 +718,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1193,6 +1275,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_fIELDS = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1347,6 +1437,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -555,6 +555,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -345,6 +345,8 @@ deriving instance Data (ArithSeqInfo GhcTc) deriving instance Data RecordConTc deriving instance Data RecordUpdTc +deriving instance Data GetFieldTc +deriving instance Data ProjectionTc deriving instance Data CmdTopTc deriving instance Data PendingRnSplice deriving instance Data PendingTcSplice ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -269,6 +269,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,6 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -68,7 +71,7 @@ import GHC.Prelude -- compiler/basicTypes import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore, mkVarOcc, occNameString, occNameFS ) import GHC.Core.DataCon ( DataCon, dataConName ) import GHC.Types.SrcLoc import GHC.Unit.Module @@ -95,7 +98,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nil manyDataConTyCon) } -%expect 232 -- shift/reduce conflicts +%expect 234 -- shift/reduce conflicts {- Last updated: 08 June 2020 @@ -551,6 +554,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } '{' { L _ ITocurly } -- special symbols @@ -2610,6 +2615,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2699,10 +2720,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2730,6 +2753,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2778,6 +2809,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3193,33 +3232,64 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError l $ + text "For this to work, enable NamedFieldPuns." + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3512,6 +3582,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -618,6 +618,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -779,6 +792,7 @@ data Token | ITtypeApp -- Prefix (@) only, e.g. f @t | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1585,6 +1599,9 @@ varsym_prefix = sym $ \exts s -> | s == fsLit "-" -- Only when LexicalNegation is on, otherwise we get ITminus and -- don't hit this code path. See Note [Minus tokens] -> return ITprefixminus + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> return (ITvarsym s) @@ -1594,17 +1611,28 @@ varsym_suffix :: Action varsym_suffix = sym $ \_ s -> if | s == fsLit "@" -> failMsgP "Suffix occurrence of @. For an as-pattern, remove the leading whitespace." + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \_ s -> - if | s == fsLit "@" -> return ITat +varsym_tight_infix = sym $ \exts s -> + if | s == fsLit "@" + -> return ITat + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj False) + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_exts s -> return $ ITconsym s) @@ -1612,8 +1640,13 @@ consym = sym (\_exts s -> return $ ITconsym s) sym :: (ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2619,6 +2652,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2709,6 +2744,8 @@ mkParserFlags' warningFlags extensionFlags homeUnitId .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,6 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -31,7 +32,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkLHsSigType, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -137,6 +138,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Session ( WarningFlag(..), DynFlags ) @@ -151,6 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1385,6 +1403,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1441,10 +1461,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1463,7 +1484,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1512,6 +1532,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1545,8 +1566,12 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1575,6 +1600,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1604,8 +1630,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (mkLHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1662,6 +1688,9 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e + mkHsProjUpdatePV l _ _ = + addFatalError l $ + text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ text "Lambda-syntax in pattern." $$ text "Pattern matching on functions is not possible." @@ -1692,9 +1721,14 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text " Use of RecordDotSyntax `.' not valid.") + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2331,17 +2365,51 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2353,10 +2421,9 @@ mkRdrRecordCon :: Located RdrName -> HsRecordBinds GhcPs -> HsExpr GhcPs mkRdrRecordCon con flds = RecordCon { rcon_ext = noExtField, rcon_con_name = con, rcon_flds = flds } -mk_rec_fields :: [Located (HsRecField (GhcPass p) arg)] -> Maybe SrcSpan -> HsRecFields (GhcPass p) arg -mk_rec_fields fs Nothing = HsRecFields { rec_flds = fs, rec_dotdot = Nothing } -mk_rec_fields fs (Just s) = HsRecFields { rec_flds = fs - , rec_dotdot = Just (L s (length fs)) } +mk_rec_fields :: [LHsRecField GhcPs (Located b)] -> Maybe SrcSpan -> HsRecFields GhcPs (Located b) +mk_rec_fields flds Nothing = HsRecFields { rec_flds = flds, rec_dotdot = Nothing } +mk_rec_fields flds (Just s) = HsRecFields { rec_flds = flds, rec_dotdot = Just (L s (length flds)) } mk_rec_upd_field :: HsRecField GhcPs (LHsExpr GhcPs) -> HsRecUpdField GhcPs mk_rec_upd_field (HsRecField (L loc (FieldOcc _ rdr)) arg pun) @@ -2885,3 +2952,161 @@ starSym False = "*" forallSym :: Bool -> String forallSym True = "∀" forallSym False = "forall" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fIELDS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @fIELD x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (fIELD : fIELDS) = foldl' f (proj fIELD) fIELDS + where + f acc fIELD = (mkParen . mkOpApp (proj fIELD) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- -- mkProj rhs fIELD calculates a projection. +-- -- e.g. .x = mkProj Nothing x = \z -> z.x = \z -> (getField @fIELD x) +-- -- .x.y = mkProj Just(.x) y = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +-- mkProj :: Maybe (LHsExpr GhcPs) -> Located FastString -> LHsExpr GhcPs +-- mkProj rhs fIELD = +-- let body = mkGet zVar fIELD +-- grhs = noLoc $ GRHS noExtField [] body +-- ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) +-- m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} +-- lhs = mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) in +-- maybe lhs (mkParen . mkOpApp lhs circ) rhs + +-- mkGet arg fIELD calcuates a get_field @fIELD arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg fIELD = head $ mkGet' [arg] fIELD +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ fIELD) = get_field `mkAppType` mkSelector fIELD `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg fIELD = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_fIELD = fIELD + , gf_getField = mkGet arg fIELD + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible happened" +mkProjection loc fIELDS = + L loc Projection { + proj_ext = noExtField + , proj_fIELDS = fIELDS + , proj_projection = mkProj fIELDS + } + +-- mkSet a fIELD b calculates a set_field @fIELD expression. +-- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b + +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate -- e.g {foo.bar.baz.quux = 43} + l + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) + = let { + ; final = last fIELDS -- quux + ; fields = init fIELDS -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + +-- -- mkProjUpdate calculates functions representing dot notation record updates. +-- mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +-- mkProjUpdate -- e.g {foo.bar.baz.quux = 43} +-- l +-- fIELDS -- [foo, bar, baz, quux] +-- arg -- This is 'texp' (43 in the example). +-- = let { +-- ; final = last fIELDS -- quux +-- ; fields = init fIELDS -- [foo, bar, baz] +-- ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. +-- -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] +-- ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. +-- -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] +-- } +-- in L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg, pb_func=(\a -> foldl' mkSet' arg (zips a))} +-- -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) +-- where +-- mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs +-- mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1029,6 +1029,17 @@ tcExpr e@(HsRecFld _ f) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -499,6 +499,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -511,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -173,3 +173,8 @@ test('T18251c', normal, compile_fail, ['']) test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ca883f516e398fe90b13d24213a0ed1481d2e7b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ca883f516e398fe90b13d24213a0ed1481d2e7b 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 Wed Nov 25 18:59:47 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Wed, 25 Nov 2020 13:59:47 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fbea9a354b18_86c11450e282512f5@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: acb1d068 by Shayne Fletcher at 2020-11-25T13:59:27-05:00 Record dot syntax - - - - - 27 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3727,6 +3727,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate {pb_fIELDS = flds, pb_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -457,6 +479,50 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_fIELD :: Located FastString + , gf_getField :: LHsExpr p -- Equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_fIELDS :: [Located FastString] + , proj_projection :: LHsExpr p -- Equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -580,6 +646,10 @@ data RecordUpdTc = RecordUpdTc , rupd_wrap :: HsWrapper -- See note [Record Update HsWrapper] } +data GetFieldTc = GetFieldTc +data ProjectionTc = ProjectionTc +data RecordDotUpdTc = RecordDotUpdTc + -- | HsWrap appears only in typechecker output -- Invariant: The contained Expr is *NOT* itself an HsWrap. -- See Note [Detecting forced eta expansion] in "GHC.HsToCore.Expr". @@ -648,6 +718,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1193,6 +1275,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_fIELDS = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1347,6 +1437,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -555,6 +555,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -345,6 +345,8 @@ deriving instance Data (ArithSeqInfo GhcTc) deriving instance Data RecordConTc deriving instance Data RecordUpdTc +deriving instance Data GetFieldTc +deriving instance Data ProjectionTc deriving instance Data CmdTopTc deriving instance Data PendingRnSplice deriving instance Data PendingTcSplice ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -269,6 +269,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,6 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -68,7 +71,7 @@ import GHC.Prelude -- compiler/basicTypes import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore, mkVarOcc, occNameString, occNameFS ) import GHC.Core.DataCon ( DataCon, dataConName ) import GHC.Types.SrcLoc import GHC.Unit.Module @@ -95,7 +98,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nil manyDataConTyCon) } -%expect 232 -- shift/reduce conflicts +%expect 234 -- shift/reduce conflicts {- Last updated: 08 June 2020 @@ -551,6 +554,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } '{' { L _ ITocurly } -- special symbols @@ -2610,6 +2615,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2699,10 +2720,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2730,6 +2753,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2778,6 +2809,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3193,33 +3232,64 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError l $ + text "For this to work, enable NamedFieldPuns." + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3512,6 +3582,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -618,6 +618,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -779,6 +792,7 @@ data Token | ITtypeApp -- Prefix (@) only, e.g. f @t | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1585,6 +1599,9 @@ varsym_prefix = sym $ \exts s -> | s == fsLit "-" -- Only when LexicalNegation is on, otherwise we get ITminus and -- don't hit this code path. See Note [Minus tokens] -> return ITprefixminus + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> return (ITvarsym s) @@ -1594,17 +1611,28 @@ varsym_suffix :: Action varsym_suffix = sym $ \_ s -> if | s == fsLit "@" -> failMsgP "Suffix occurrence of @. For an as-pattern, remove the leading whitespace." + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \_ s -> - if | s == fsLit "@" -> return ITat +varsym_tight_infix = sym $ \exts s -> + if | s == fsLit "@" + -> return ITat + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj False) + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_exts s -> return $ ITconsym s) @@ -1612,8 +1640,13 @@ consym = sym (\_exts s -> return $ ITconsym s) sym :: (ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2619,6 +2652,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2709,6 +2744,8 @@ mkParserFlags' warningFlags extensionFlags homeUnitId .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,6 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -31,7 +32,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkLHsSigType, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -137,6 +138,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Session ( WarningFlag(..), DynFlags ) @@ -151,6 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1385,6 +1403,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1441,10 +1461,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1463,7 +1484,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1512,6 +1532,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1545,8 +1566,12 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1575,6 +1600,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1604,8 +1630,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (mkLHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1662,6 +1688,9 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e + mkHsProjUpdatePV l _ _ = + addFatalError l $ + text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ text "Lambda-syntax in pattern." $$ text "Pattern matching on functions is not possible." @@ -1692,9 +1721,14 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text " Use of RecordDotSyntax `.' not valid.") + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2331,17 +2365,51 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2885,3 +2953,129 @@ starSym False = "*" forallSym :: Bool -> String forallSym True = "∀" forallSym False = "forall" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fIELDS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @fIELD x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (fIELD : fIELDS) = foldl' f (proj fIELD) fIELDS + where + f acc fIELD = (mkParen . mkOpApp (proj fIELD) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg fIELD calcuates a get_field @fIELD arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg fIELD = head $ mkGet' [arg] fIELD +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ fIELD) = get_field `mkAppType` mkSelector fIELD `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg fIELD = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_fIELD = fIELD + , gf_getField = mkGet arg fIELD + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible happened" +mkProjection loc fIELDS = + L loc Projection { + proj_ext = noExtField + , proj_fIELDS = fIELDS + , proj_projection = mkProj fIELDS + } + +-- mkSet a fIELD b calculates a set_field @fIELD expression. +-- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b + +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate -- e.g {foo.bar.baz.quux = 43} + l + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) + = let { + ; final = last fIELDS -- quux + ; fields = init fIELDS -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1029,6 +1029,17 @@ tcExpr e@(HsRecFld _ f) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -499,6 +499,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -511,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -173,3 +173,8 @@ test('T18251c', normal, compile_fail, ['']) test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/acb1d068125f82ac8a6237b6b291bef28a8d553e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/acb1d068125f82ac8a6237b6b291bef28a8d553e 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 Wed Nov 25 19:10:35 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Wed, 25 Nov 2020 14:10:35 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fbeac2bc84e3_86c111d4a0025161d@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: bbd6dff0 by Shayne Fletcher at 2020-11-25T14:10:18-05:00 Record dot syntax - - - - - 26 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3727,6 +3727,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate {pb_fIELDS = flds, pb_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -457,6 +479,50 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_fIELD :: Located FastString + , gf_getField :: LHsExpr p -- Equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_fIELDS :: [Located FastString] + , proj_projection :: LHsExpr p -- Equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -648,6 +714,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1193,6 +1271,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_fIELDS = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1347,6 +1433,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -555,6 +555,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -269,6 +269,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,6 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -68,7 +71,7 @@ import GHC.Prelude -- compiler/basicTypes import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore, mkVarOcc, occNameString, occNameFS ) import GHC.Core.DataCon ( DataCon, dataConName ) import GHC.Types.SrcLoc import GHC.Unit.Module @@ -95,7 +98,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nil manyDataConTyCon) } -%expect 232 -- shift/reduce conflicts +%expect 234 -- shift/reduce conflicts {- Last updated: 08 June 2020 @@ -551,6 +554,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } '{' { L _ ITocurly } -- special symbols @@ -2610,6 +2615,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2699,10 +2720,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2730,6 +2753,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2778,6 +2809,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3193,33 +3232,64 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError l $ + text "For this to work, enable NamedFieldPuns." + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3512,6 +3582,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -618,6 +618,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -779,6 +792,7 @@ data Token | ITtypeApp -- Prefix (@) only, e.g. f @t | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1585,6 +1599,9 @@ varsym_prefix = sym $ \exts s -> | s == fsLit "-" -- Only when LexicalNegation is on, otherwise we get ITminus and -- don't hit this code path. See Note [Minus tokens] -> return ITprefixminus + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> return (ITvarsym s) @@ -1594,17 +1611,28 @@ varsym_suffix :: Action varsym_suffix = sym $ \_ s -> if | s == fsLit "@" -> failMsgP "Suffix occurrence of @. For an as-pattern, remove the leading whitespace." + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \_ s -> - if | s == fsLit "@" -> return ITat +varsym_tight_infix = sym $ \exts s -> + if | s == fsLit "@" + -> return ITat + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj False) + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_exts s -> return $ ITconsym s) @@ -1612,8 +1640,13 @@ consym = sym (\_exts s -> return $ ITconsym s) sym :: (ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2619,6 +2652,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2709,6 +2744,8 @@ mkParserFlags' warningFlags extensionFlags homeUnitId .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,6 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -31,7 +32,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkLHsSigType, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -137,6 +138,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Session ( WarningFlag(..), DynFlags ) @@ -151,6 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1385,6 +1403,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1441,10 +1461,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1463,7 +1484,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1512,6 +1532,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1545,8 +1566,12 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1575,6 +1600,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1604,8 +1630,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (mkLHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1662,6 +1688,9 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e + mkHsProjUpdatePV l _ _ = + addFatalError l $ + text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ text "Lambda-syntax in pattern." $$ text "Pattern matching on functions is not possible." @@ -1692,9 +1721,14 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text " Use of RecordDotSyntax `.' not valid.") + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2331,17 +2365,51 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2885,3 +2953,129 @@ starSym False = "*" forallSym :: Bool -> String forallSym True = "∀" forallSym False = "forall" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fIELDS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @fIELD x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (fIELD : fIELDS) = foldl' f (proj fIELD) fIELDS + where + f acc fIELD = (mkParen . mkOpApp (proj fIELD) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg fIELD calcuates a get_field @fIELD arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg fIELD = head $ mkGet' [arg] fIELD +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ fIELD) = get_field `mkAppType` mkSelector fIELD `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg fIELD = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_fIELD = fIELD + , gf_getField = mkGet arg fIELD + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible happened" +mkProjection loc fIELDS = + L loc Projection { + proj_ext = noExtField + , proj_fIELDS = fIELDS + , proj_projection = mkProj fIELDS + } + +-- mkSet a fIELD b calculates a set_field @fIELD expression. +-- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b + +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate -- e.g {foo.bar.baz.quux = 43} + l + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) + = let { + ; final = last fIELDS -- quux + ; fields = init fIELDS -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1029,6 +1029,17 @@ tcExpr e@(HsRecFld _ f) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -499,6 +499,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -511,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -173,3 +173,8 @@ test('T18251c', normal, compile_fail, ['']) test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bbd6dff0e7f81200d88bc24423d6906b55c8db28 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bbd6dff0e7f81200d88bc24423d6906b55c8db28 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 Wed Nov 25 19:26:12 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Wed, 25 Nov 2020 14:26:12 -0500 Subject: [Git][ghc/ghc][wip/andreask/raPlatform_fix] RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Message-ID: <5fbeafd41b4d2_86c7d592402533be@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/raPlatform_fix at Glasgow Haskell Compiler / GHC Commits: 4f8929a8 by Andreas Klebinger at 2020-11-25T20:24:53+01:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - 2 changed files: - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -283,7 +283,8 @@ regAlloc_spin config spinCount triv regsFree slotsFree slotsCount debug_codeGrap , raCoalesced = rmCoalesce , raSpillStats = spillStats , raSpillCosts = spillCosts - , raSpilled = code_spilled } + , raSpilled = code_spilled + , raPlatform = platform } -- Bundle up all the register allocator statistics. -- .. but make sure to drop them on the floor if they're not ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs ===================================== @@ -79,7 +79,11 @@ data RegAllocStats statics instr , raSpillCosts :: SpillCostInfo -- | Code with spill instructions added. - , raSpilled :: [LiveCmmDecl statics instr] } + , raSpilled :: [LiveCmmDecl statics instr] + + -- | Target platform + , raPlatform :: !Platform + } -- a successful coloring View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f8929a82f4bf363b60bad959833b58b7c616388 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f8929a82f4bf363b60bad959833b58b7c616388 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 Wed Nov 25 19:41:09 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Wed, 25 Nov 2020 14:41:09 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] 7 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fbeb35533304_86c7d59240257869@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - c4958d33 by Moritz Angermann at 2020-11-25T12:08:44-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 24e0ea5e by John Ericson at 2020-11-25T13:38:35-05:00 Make primop handler indentation more consistent - - - - - cd935e98 by John Ericson at 2020-11-25T14:21:52-05:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/array - libraries/base/Debug/Trace.hs - libraries/base/GHC/Float.hs - libraries/base/GHC/IO/Encoding/CodePage.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/58a37f8bf3afaee2407ef772af711e27f6da54b0...cd935e98c4297aa1fd14b057df381c28dcac90e2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/58a37f8bf3afaee2407ef772af711e27f6da54b0...cd935e98c4297aa1fd14b057df381c28dcac90e2 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 Wed Nov 25 19:43:00 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Wed, 25 Nov 2020 14:43:00 -0500 Subject: [Git][ghc/ghc][wip/fixed-width-lits] 8 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fbeb3c453a3b_86c879fa9c2583e7@gitlab.mail> John Ericson pushed to branch wip/fixed-width-lits at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - c4958d33 by Moritz Angermann at 2020-11-25T12:08:44-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 24e0ea5e by John Ericson at 2020-11-25T13:38:35-05:00 Make primop handler indentation more consistent - - - - - cd935e98 by John Ericson at 2020-11-25T14:21:52-05:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - 9ffabc57 by Sylvain Henry at 2020-11-25T14:38:43-05:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - ghc/ghc-bin.cabal.in - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/array - libraries/base/Debug/Trace.hs - libraries/base/GHC/Float.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cfb672c49dc9081982f9284abf6302fd202f4eea...9ffabc576acc84fd8429a12f32e76b84ef7a0003 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cfb672c49dc9081982f9284abf6302fd202f4eea...9ffabc576acc84fd8429a12f32e76b84ef7a0003 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 Wed Nov 25 20:02:22 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 25 Nov 2020 15:02:22 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] Improve comments Message-ID: <5fbeb84edb304_86c113a5b2c26252a@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 57609069 by Richard Eisenberg at 2020-11-25T15:00:36-05:00 Improve comments - - - - - 5 changed files: - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Solver.hs - compiler/GHC/Tc/Solver/Canonical.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs Changes: ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -3939,6 +3939,8 @@ more. So I use a HACK: Result works fine, but it may eventually bite us. +See also Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver for +information about how these are printed. ************************************************************************ * * ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -2120,7 +2120,8 @@ the example for why (partial-sigs/should_compile/T12844): GHC correctly infers that the extra-constraints wildcard on `bar` should be (Head rngs ~ '(r, r'), Foo rngs). It then adds this constraint -as a Given on the implication constraint for `bar`. The Hole for +as a Given on the implication constraint for `bar`. (This implication is +created by mkResidualConstraints in simplifyInfer.) The Hole for the _ is stored within the implication's WantedConstraints. When simplifyHoles is called, that constraint is already assumed as a Given. Simplifying with respect to it turns it into @@ -2135,6 +2136,9 @@ is simple: just don't simplify extra-constraints wildcards. This is the only reason we need to track ConstraintHole separately from TypeHole in HoleSort. +See also Note [Extra-constraint holes in partial type signatures] +in GHC.Tc.Gen.HsType. + Note [Tracking redundant constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ With Opt_WarnRedundantConstraints, GHC can report which ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -2524,38 +2524,39 @@ Wrinkles: must be sure to kick out any such CIrredCan constraints that mention coercion holes when those holes get filled in, so that the unification step can now proceed. - (2a) We must now kick out any constraints that mention a newly-filled-in - coercion hole, but only if there are no more remaining coercion - holes. This is done in kickOutAfterFillingCoercionHole. The extra - check that there are no more remaining holes avoids needless work - when rewriting evidence (which fills coercion holes) and aids - efficiency. - - Moreover, kicking out when there are remaining unfilled holes can - cause a loop in the solver in this case: - [W] w1 :: (ty1 :: F a) ~ (ty2 :: s) - After canonicalisation, we discover that this equality is heterogeneous. - So we emit - [W] co_abc :: F a ~ s - and preserve the original as - [W] w2 :: (ty1 |> co_abc) ~ ty2 (blocked on co_abc) - Then, co_abc comes becomes the work item. It gets swapped in - canEqCanLHS2 and then back again in canEqTyVarFunEq. We thus get - co_abc := sym co_abd, and then co_abd := sym co_abe, with - [W] co_abe :: F a ~ s - This process has filled in co_abc. Suppose w2 were kicked out. - When it gets processed, - would get this whole chain going again. The solution is to - kick out a blocked constraint only when the result of filling - in the blocking coercion involves no further blocking coercions. - Alternatively, we could be careful not to do unnecessary swaps during - canonicalisation, but that seems hard to do, in general. + The kicking out is done in kickOutAfterFillingCoercionHole. + + However, we must be careful: we kick out only when no coercion holes are + left. The holes in the type are stored in the BlockedCIS CtIrredStatus. + The extra check that there are no more remaining holes avoids + needless work when rewriting evidence (which fills coercion holes) and + aids efficiency. + + Moreover, kicking out when there are remaining unfilled holes can + cause a loop in the solver in this case: + [W] w1 :: (ty1 :: F a) ~ (ty2 :: s) + After canonicalisation, we discover that this equality is heterogeneous. + So we emit + [W] co_abc :: F a ~ s + and preserve the original as + [W] w2 :: (ty1 |> co_abc) ~ ty2 (blocked on co_abc) + Then, co_abc comes becomes the work item. It gets swapped in + canEqCanLHS2 and then back again in canEqTyVarFunEq. We thus get + co_abc := sym co_abd, and then co_abd := sym co_abe, with + [W] co_abe :: F a ~ s + This process has filled in co_abc. Suppose w2 were kicked out. + When it gets processed, + would get this whole chain going again. The solution is to + kick out a blocked constraint only when the result of filling + in the blocking coercion involves no further blocking coercions. + Alternatively, we could be careful not to do unnecessary swaps during + canonicalisation, but that seems hard to do, in general. (3) Suppose we have [W] (a :: k1) ~ (rhs :: k2). We duly follow the algorithm detailed here, producing [W] co :: k2 ~ k1, and adding [W] (a :: k1) ~ ((rhs |> co) :: k1) to the irreducibles. Some time later, we solve co, and fill in co's coercion hole. This kicks out - the irreducible as described in (2a). + the irreducible as described in (2). But now, during canonicalization, we see the cast and remove it, in canEqCast. By the time we get into canEqCanLHS, the equality is heterogeneous again, and the process repeats. @@ -2832,9 +2833,10 @@ Details: they originally stood for (e.g. cbv1 := TF a, cbv2 := TF Int), not what may be in a rewritten constraint. - Not breaking cycles fursther makes sense, because - we only want to break cycles for user-written loopy Givens, and - a CycleBreakerTv certainly isn't user-written. + Not breaking cycles further (which would mean changing TF cbv1 to cbv3 + and TF cbv2 to cbv4) makes sense, because we only want to break cycles + for user-written loopy Givens, and a CycleBreakerTv certainly isn't + user-written. NB: This same situation (an equality like b ~ Maybe (F b)) can arise with Wanteds, but we have no concrete case incentivising special treatment. It ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -1817,7 +1817,7 @@ kickOutAfterUnification new_tv ; setInertCans ics2 ; return n_kicked } --- See Wrinkle (2a) in Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Canonical +-- See Wrinkle (2) in Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Canonical kickOutAfterFillingCoercionHole :: CoercionHole -> Coercion -> TcS () kickOutAfterFillingCoercionHole hole filled_co = do { ics <- getInertCans ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -298,7 +298,7 @@ data CtIrredStatus | BlockedCIS HoleSet -- this constraint is blocked on the coercion hole(s) listed -- See Note [Equalities with incompatible kinds] in GHC.Tc.Solver.Canonical - -- Wrinkle (4a). Why store the HoleSet? See Wrinkle (2a) of that + -- Wrinkle (4a). Why store the HoleSet? See Wrinkle (2) of that -- same Note. -- INVARIANT: A BlockedCIS is a homogeneous equality whose -- left hand side can fit in a CanEqLHS. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57609069ed365114b38487c97706f3151064b1fa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57609069ed365114b38487c97706f3151064b1fa 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 Wed Nov 25 20:33:05 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 25 Nov 2020 15:33:05 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 151 commits: SMP.h: Add C11-style atomic operations Message-ID: <5fbebf816f6e2_86cfd752bc26403b@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 9f281886 by Richard Eisenberg at 2020-11-25T15:26:41-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into GHC.Core.Map.Type and GHC.Core.Map.Expr, in order to avoid module import cycles with GHC.Core. - - - - - 40309d89 by Richard Eisenberg at 2020-11-25T15:26:42-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - 6012b3ce by Richard Eisenberg at 2020-11-25T15:32:39-05:00 Write commit message here. - - - - - 3272ecf4 by Richard Eisenberg at 2020-11-25T15:32:45-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57609069ed365114b38487c97706f3151064b1fa...3272ecf4142476803b1f62ec67cb9d999a59bdcd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57609069ed365114b38487c97706f3151064b1fa...3272ecf4142476803b1f62ec67cb9d999a59bdcd 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 Wed Nov 25 21:38:24 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Wed, 25 Nov 2020 16:38:24 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 15 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fbeced0e47da_86c3fc6ab4f115c280020@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - c4958d33 by Moritz Angermann at 2020-11-25T12:08:44-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 24e0ea5e by John Ericson at 2020-11-25T13:38:35-05:00 Make primop handler indentation more consistent - - - - - cd935e98 by John Ericson at 2020-11-25T14:21:52-05:00 Cleanup some primop-related identifers - Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) - - - - - 9ffabc57 by Sylvain Henry at 2020-11-25T14:38:43-05:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 879d4151 by John Ericson at 2020-11-25T20:41:26+00:00 Merge branch 'wip/fix-64-toArgRep' into HEAD - - - - - 8a78e01f by John Ericson at 2020-11-25T21:27:05+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 15882d21 by John Ericson at 2020-11-25T21:27:06+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - a6c6ed4c by Sylvain Henry at 2020-11-25T21:37:46+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 6cfc5461 by John Ericson at 2020-11-25T21:37:48+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 5b32b6e2 by John Ericson at 2020-11-25T21:37:48+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 4a714538 by John Ericson at 2020-11-25T21:37:48+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7e057ab98551b7f49e0d336700c3312a74f90610...4a7145381124af853815639a48b752b9ac995d2a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7e057ab98551b7f49e0d336700c3312a74f90610...4a7145381124af853815639a48b752b9ac995d2a 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 Wed Nov 25 23:15:24 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Wed, 25 Nov 2020 18:15:24 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/interal-primop-naming-consistency Message-ID: <5fbee58c14cb6_86c11450e28290329@gitlab.mail> John Ericson pushed new branch wip/interal-primop-naming-consistency at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/interal-primop-naming-consistency 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 Wed Nov 25 23:35:03 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Wed, 25 Nov 2020 18:35:03 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] 2 commits: Cleanup some primop constructor names Message-ID: <5fbeea27b3301_86ce89fc5c2948d0@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: 3d9b490f by John Ericson at 2020-11-25T23:07:32+00:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - f0a3896b by John Ericson at 2020-11-25T23:09:45+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/ghci/GHCi/BreakArray.hs - testsuite/tests/array/should_run/arr020.hs - testsuite/tests/cmm/opt/T18141.hs - testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_run/cgrun070.hs - testsuite/tests/codeGen/should_run/cgrun072.hs - testsuite/tests/codeGen/should_run/cgrun075.hs - testsuite/tests/codeGen/should_run/cgrun076.hs - testsuite/tests/codeGen/should_run/compareByteArrays.hs - testsuite/tests/ffi/should_run/PrimFFIInt16.hs - testsuite/tests/ffi/should_run/PrimFFIInt8.hs - testsuite/tests/ffi/should_run/PrimFFIWord16.hs - testsuite/tests/ffi/should_run/PrimFFIWord8.hs - testsuite/tests/ffi/should_run/T16650a.hs - testsuite/tests/ffi/should_run/T16650b.hs - testsuite/tests/ffi/should_run/UnliftedNewtypesByteArrayOffset.hs - testsuite/tests/lib/integer/integerImportExport.hs - testsuite/tests/numeric/should_compile/T16402.stderr-ws-32 The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cd935e98c4297aa1fd14b057df381c28dcac90e2...f0a3896b9a845bf00283eb8c961bdb0c96c80f86 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cd935e98c4297aa1fd14b057df381c28dcac90e2...f0a3896b9a845bf00283eb8c961bdb0c96c80f86 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 Nov 26 02:38:40 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Wed, 25 Nov 2020 21:38:40 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fbf15308bf58_86c113a5b2c3039d8@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 1d0b97e8 by Shayne Fletcher at 2020-11-25T21:38:23-05:00 Record dot syntax - - - - - 26 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3727,6 +3727,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pb_fIELDS :: [Located FastString] + , pb_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate {pb_fIELDS = flds, pb_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -457,6 +479,51 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_fIELD :: Located FastString + , gf_getField :: LHsExpr p -- Equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnComma, 'GHC.Parser.Annotation.AnnDot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_fIELDS :: [Located FastString] + , proj_projection :: LHsExpr p -- Equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -648,6 +715,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1193,6 +1272,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_fIELD = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_fIELDS = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1347,6 +1434,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -555,6 +555,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -269,6 +269,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,6 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -68,7 +71,7 @@ import GHC.Prelude -- compiler/basicTypes import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore, mkVarOcc, occNameString, occNameFS ) import GHC.Core.DataCon ( DataCon, dataConName ) import GHC.Types.SrcLoc import GHC.Unit.Module @@ -95,7 +98,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nil manyDataConTyCon) } -%expect 232 -- shift/reduce conflicts +%expect 234 -- shift/reduce conflicts {- Last updated: 08 June 2020 @@ -551,6 +554,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } '{' { L _ ITocurly } -- special symbols @@ -2610,6 +2615,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2699,10 +2720,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2730,6 +2753,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2778,6 +2809,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3193,33 +3232,64 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError l $ + text "For this to work, enable NamedFieldPuns." + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3512,6 +3582,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -618,6 +618,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -779,6 +792,7 @@ data Token | ITtypeApp -- Prefix (@) only, e.g. f @t | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1585,6 +1599,9 @@ varsym_prefix = sym $ \exts s -> | s == fsLit "-" -- Only when LexicalNegation is on, otherwise we get ITminus and -- don't hit this code path. See Note [Minus tokens] -> return ITprefixminus + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> return (ITvarsym s) @@ -1594,17 +1611,28 @@ varsym_suffix :: Action varsym_suffix = sym $ \_ s -> if | s == fsLit "@" -> failMsgP "Suffix occurrence of @. For an as-pattern, remove the leading whitespace." + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \_ s -> - if | s == fsLit "@" -> return ITat +varsym_tight_infix = sym $ \exts s -> + if | s == fsLit "@" + -> return ITat + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj False) + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_exts s -> return $ ITconsym s) @@ -1612,8 +1640,13 @@ consym = sym (\_exts s -> return $ ITconsym s) sym :: (ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2619,6 +2652,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2709,6 +2744,8 @@ mkParserFlags' warningFlags extensionFlags homeUnitId .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,6 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -31,7 +32,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkLHsSigType, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -137,6 +138,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Session ( WarningFlag(..), DynFlags ) @@ -151,6 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1385,6 +1403,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1441,10 +1461,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1463,7 +1484,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1512,6 +1532,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1545,8 +1566,12 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1575,6 +1600,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1604,8 +1630,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (mkLHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1662,6 +1688,9 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e + mkHsProjUpdatePV l _ _ = + addFatalError l $ + text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ text "Lambda-syntax in pattern." $$ text "Pattern matching on functions is not possible." @@ -1692,9 +1721,14 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text " Use of RecordDotSyntax `.' not valid.") + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2331,17 +2365,51 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2885,3 +2953,129 @@ starSym False = "*" forallSym :: Bool -> String forallSym True = "∀" forallSym False = "forall" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fIELDS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @fIELD x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (fIELD : fIELDS) = foldl' f (proj fIELD) fIELDS + where + f acc fIELD = (mkParen . mkOpApp (proj fIELD) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg fIELD calcuates a get_field @fIELD arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg fIELD = head $ mkGet' [arg] fIELD +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ fIELD) = get_field `mkAppType` mkSelector fIELD `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg fIELD = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_fIELD = fIELD + , gf_getField = mkGet arg fIELD + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible happened" +mkProjection loc fIELDS = + L loc Projection { + proj_ext = noExtField + , proj_fIELDS = fIELDS + , proj_projection = mkProj fIELDS + } + +-- mkSet a fIELD b calculates a set_field @fIELD expression. +-- e.g mkSet a fIELD b = set_field @"fIELD" a b (read as "set field 'fIELD' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ fIELD) b = set_field `mkAppType` mkSelector fIELD `mkApp` a `mkApp` b + +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate -- e.g {foo.bar.baz.quux = 43} + l + fIELDS + arg = L l $ ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pb_fIELDS=fIELDS, pb_arg=arg} )) + = let { + ; final = last fIELDS -- quux + ; fields = init fIELDS -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (fIELD, g) = mkSet (mkParen g) fIELD (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pb_fIELDS = fs, pb_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1029,6 +1029,17 @@ tcExpr e@(HsRecFld _ f) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -499,6 +499,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -511,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -173,3 +173,8 @@ test('T18251c', normal, compile_fail, ['']) test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d0b97e843ec8aefa7e394ce35c843c6cc1808fa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d0b97e843ec8aefa7e394ce35c843c6cc1808fa 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 Nov 26 03:35:19 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Wed, 25 Nov 2020 22:35:19 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-ncg] 179 commits: rts/linker: Fix relocation overflow in PE linker Message-ID: <5fbf22779b90_86cfd752bc30417e@gitlab.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC Commits: d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - aeef1eb6 by Moritz Angermann at 2020-11-26T10:25:21+08:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - 38be4fb5 by Moritz Angermann at 2020-11-26T10:25:23+08:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. - - - - - be61cae2 by Moritz Angermann at 2020-11-26T10:31:10+08:00 Initial NCG - - - - - 1ec438ea by Moritz Angermann at 2020-11-26T10:31:21+08:00 Address Takenobu's comments - - - - - 5249fd2c by Moritz Angermann at 2020-11-26T10:31:21+08:00 Fix floating points handling of NaNs - - - - - 4eb48320 by Moritz Angermann at 2020-11-26T10:32:19+08:00 Add basic Graph Coloring support - - - - - 5e4c2950 by Moritz Angermann at 2020-11-26T10:32:27+08:00 Drop debug - - - - - b5f4ad2f by Moritz Angermann at 2020-11-26T10:32:27+08:00 Add primops_match.cmm testsuite - - - - - ed04b45d by Moritz Angermann at 2020-11-26T10:32:27+08:00 Fix -NaN for real this time. - - - - - 886c87a7 by Moritz Angermann at 2020-11-26T10:32:28+08:00 Adds nan test. - - - - - 6fe442d1 by Moritz Angermann at 2020-11-26T10:32:28+08:00 no show - - - - - b52e8e3d by Moritz Angermann at 2020-11-26T10:32:28+08:00 Some notes on PIC - - - - - aeebd433 by Moritz Angermann at 2020-11-26T10:32:28+08:00 Properly load W32 with bit 31 set. - - - - - a911ac0b by Moritz Angermann at 2020-11-26T10:32:28+08:00 better relocation logging - - - - - 4d18232e by Moritz Angermann at 2020-11-26T10:32:29+08:00 Add AsmOpt Flags - - - - - 071977f5 by Moritz Angermann at 2020-11-26T10:32:29+08:00 Adds ANN instruction. I wish I had a `pad n` function for SDoc, that would interact with the layout, and just pad what ever was printed so far to `n` chars. - - - - - c17df046 by Moritz Angermann at 2020-11-26T10:32:29+08:00 Drop dead 32bit logic. - - - - - 371543b3 by Moritz Angermann at 2020-11-26T10:32:29+08:00 Add Show CmmExpr instances. Why would we want this, when we have Outputtable CmmExpr? Quite often when working on Code Generators, we want to structurally match on a Cmm Expression. Having to recover the Cmm Expression from its Outputtable text is not always trivial, and requires substantial effort. By having a Show instance, we can almost copy the definition to match on. - - - - - 9d69880d by Moritz Angermann at 2020-11-26T10:32:29+08:00 Drop duplicate show instance for CLabel now. - - - - - b44f5789 by Moritz Angermann at 2020-11-26T10:32:30+08:00 Add link, lest I keep forgetting it. - - - - - 41f4a929 by Moritz Angermann at 2020-11-26T10:32:30+08:00 inline comments with // - - - - - 76d9eed9 by Moritz Angermann at 2020-11-26T10:32:30+08:00 Some optimizations; not yet sure if safe or not. - - - - - defc3bf9 by Moritz Angermann at 2020-11-26T10:32:30+08:00 Add latest opt changes. - - - - - 6c2a06b0 by Moritz Angermann at 2020-11-26T10:32:30+08:00 Address Takenobu Tani's comments. Thanks! - - - - - d241b467 by Moritz Angermann at 2020-11-26T10:32:31+08:00 Fix gcd :blush: - - - - - 0e47ccb8 by Moritz Angermann at 2020-11-26T10:32:31+08:00 Overflow guard - - - - - 1c3dce44 by Moritz Angermann at 2020-11-26T10:32:31+08:00 More annotations. - - - - - 0eb68c0b by Moritz Angermann at 2020-11-26T10:32:31+08:00 Revert "Overflow guard" They are Integers not Ints. This reverts commit 3ef94e593a2848cf2bdc4251f5be34536642675f. Signed-off-by: Moritz Angermann <moritz.angermann at gmail.com> - - - - - d083c640 by Moritz Angermann at 2020-11-26T10:32:32+08:00 Add CmmAssign and CmmStore comments - - - - - 41cf9597 by Moritz Angermann at 2020-11-26T10:32:32+08:00 Minor address mode changes - - - - - 21ecf30f by Moritz Angermann at 2020-11-26T10:32:32+08:00 More Amode optimizations - - - - - d43f39dc by Moritz Angermann at 2020-11-26T10:32:32+08:00 I think this shoudl work for all Registers, not just CmmGlobal - - - - - 9f96440c by Moritz Angermann at 2020-11-26T10:32:32+08:00 Opt <<, >> - - - - - 1df13b8b by Moritz Angermann at 2020-11-26T10:32:33+08:00 Opt &&, || - - - - - 669f0cdc by Moritz Angermann at 2020-11-26T10:32:33+08:00 Add branch ANNotations. - - - - - b38a1958 by Moritz Angermann at 2020-11-26T10:32:33+08:00 Disable Opt &&, ||, due to mask immediate - - - - - b3fe0f6b by Moritz Angermann at 2020-11-26T10:32:33+08:00 Opt: Adds CBZ, CBNZ - - - - - 33f9f791 by Moritz Angermann at 2020-11-26T10:32:33+08:00 More generic CBZ, CBNZ - - - - - b154bf06 by Moritz Angermann at 2020-11-26T10:32:34+08:00 Fixup - - - - - b0ac8284 by Moritz Angermann at 2020-11-26T10:32:34+08:00 very rudimentary bitmask support. - - - - - 5950b537 by Moritz Angermann at 2020-11-26T10:32:34+08:00 Add some more bitmasks - - - - - d8326544 by Moritz Angermann at 2020-11-26T10:32:34+08:00 Opt STR - - - - - 00150171 by Moritz Angermann at 2020-11-26T10:32:34+08:00 Fixup - - - - - bd9dda04 by Moritz Angermann at 2020-11-26T10:32:35+08:00 Fix MO_SF_Conv - - - - - 812c2004 by Moritz Angermann at 2020-11-26T10:32:35+08:00 Add Comment re MO_Memcpy - - - - - a1205688 by Moritz Angermann at 2020-11-26T10:32:35+08:00 Always PIC via GOT - - - - - 14dd4b28 by Moritz Angermann at 2020-11-26T10:32:35+08:00 Fix up generated assembly. Don't generate identity moves e.g. mov x18, x18 - - - - - 21eb4ed0 by Moritz Angermann at 2020-11-26T10:32:35+08:00 Drop superfulous alignment generation. - - - - - c29df435 by Moritz Angermann at 2020-11-26T10:32:36+08:00 Hadrian :fire: - - - - - b771b292 by Moritz Angermann at 2020-11-26T10:32:36+08:00 Address Tekenobus comments. Thanks! - - - - - b225e4ba by Moritz Angermann at 2020-11-26T10:32:36+08:00 Adds J to distinguish jumps from B. Maybe this would be better handled with a phantom type? - - - - - b855d5f0 by Moritz Angermann at 2020-11-26T10:32:36+08:00 Make sp an Operand - - - - - a32735b1 by Moritz Angermann at 2020-11-26T10:32:36+08:00 allocMoreStack This is still broken, as we can't spill into arbitrary ranges. Hence while we can allocate extra space, we can't really spill past 4096 offsets due to the immediat having to be encoded. This leaves us with a max of 512 spill slots. We *can* work around this if we change the sp though. - - - - - 72ad0110 by Moritz Angermann at 2020-11-26T10:32:37+08:00 [Spill/Reload] Spill Around :fire: - - - - - f60dbd82 by Moritz Angermann at 2020-11-26T10:32:37+08:00 Address Takenobus observations! Thanks! - - - - - 59303597 by Moritz Angermann at 2020-11-26T10:32:37+08:00 :sob: - - - - - b022e7a9 by Moritz Angermann at 2020-11-26T10:32:37+08:00 Revert the Spill/Reload fix; undo :got: loads. This breaks dynamic, however we can build a working stage2 compiler with the following mk/build.mk BuildFlavour = quick ifneq "$(BuildFlavour)" "" include mk/flavours/$(BuildFlavour).mk endif STRIP_CMD = : DYNAMIC_BY_DEFAULT = NO DYNAMIC_GHC_PROGRAMS = NO - - - - - e9c1def9 by Moritz Angermann at 2020-11-26T10:32:37+08:00 Disable trivial deadlock detection - - - - - f9011088 by Moritz Angermann at 2020-11-26T10:32:38+08:00 Adds some annotations - - - - - 31f2545f by Moritz Angermann at 2020-11-26T10:32:38+08:00 Trying to get PIC right. - - - - - 23bfce96 by Moritz Angermann at 2020-11-26T10:32:38+08:00 [aarch64] Fix spill/reload - - - - - 3a386bcc by Moritz Angermann at 2020-11-26T10:32:38+08:00 Try to get PIC right. - - - - - 8dfd6bd6 by Moritz Angermann at 2020-11-26T10:32:39+08:00 Spill/Reload only need a smaller window - - - - - 93e2f834 by Moritz Angermann at 2020-11-26T10:32:39+08:00 Drop bad/useless optimisation This was due to not handling PIC symbols correctly and injecting CmmLoad as we do on other platforms, but this doesn't translate to aarch64's got lookups. - - - - - 83d181c6 by Moritz Angermann at 2020-11-26T10:32:39+08:00 B is b - - - - - c917632b by Moritz Angermann at 2020-11-26T10:32:39+08:00 Fix CCall |Now mark used registers properly for the Register Allocator. - - - - - 3213ddc8 by Moritz Angermann at 2020-11-26T10:32:39+08:00 :sob: - - - - - dd1fe55d by Moritz Angermann at 2020-11-26T10:32:40+08:00 :sob: :sob: - - - - - 4c6763c7 by Moritz Angermann at 2020-11-26T10:32:40+08:00 :sob: Segfault no 3. This showed up in T4114 - - - - - 6f341c48 by Moritz Angermann at 2020-11-26T10:32:40+08:00 Add mkComment to `Instruction` - - - - - 584d3478 by Moritz Angermann at 2020-11-26T10:32:40+08:00 Use mkComment for debugging - - - - - d745f69d by Moritz Angermann at 2020-11-26T10:32:40+08:00 Fix T4114 crashes T4114 causes this codepath to show up. - - - - - 7e15dcbf by Moritz Angermann at 2020-11-26T10:32:41+08:00 Cleanup some compiler warnings - - - - - fb2206ba by Moritz Angermann at 2020-11-26T10:32:41+08:00 [Aarch64] No div-by-zero; disable test. - - - - - 1c1538ff by Moritz Angermann at 2020-11-26T10:32:41+08:00 Simplify aarch64 StgRun We don't need to do the callee save register dance. The compiler will do this for us already: 0000000000000000 <StgRun>: 0: a9b653f3 stp x19, x20, [sp, #-160]! 4: a9015bf5 stp x21, x22, [sp, #16] 8: a90263f7 stp x23, x24, [sp, #32] c: a9036bf9 stp x25, x26, [sp, #48] 10: a90473fb stp x27, x28, [sp, #64] 14: f9002bfe str x30, [sp, #80] 18: 6d0627e8 stp d8, d9, [sp, #96] 1c: 6d072fea stp d10, d11, [sp, #112] 20: 6d0837ec stp d12, d13, [sp, #128] 24: 6d093fee stp d14, d15, [sp, #144] 28: a9bf47f0 stp x16, x17, [sp, #-16]! 2c: d14013ff sub sp, sp, #0x4, lsl #12 30: aa0103f3 mov x19, x1 34: d61f0000 br x0 0000000000000038 <StgReturn>: 38: 914013ff add sp, sp, #0x4, lsl #12 3c: aa1603e0 mov x0, x22 40: a8c147f0 ldp x16, x17, [sp], #16 44: a9415bf5 ldp x21, x22, [sp, #16] 48: a94263f7 ldp x23, x24, [sp, #32] 4c: a9436bf9 ldp x25, x26, [sp, #48] 50: a94473fb ldp x27, x28, [sp, #64] 54: f9402bfe ldr x30, [sp, #80] 58: 6d4627e8 ldp d8, d9, [sp, #96] 5c: 6d472fea ldp d10, d11, [sp, #112] 60: 6d4837ec ldp d12, d13, [sp, #128] 64: 6d493fee ldp d14, d15, [sp, #144] 68: a8ca53f3 ldp x19, x20, [sp], #160 6c: d65f03c0 ret - - - - - 2c75c03b by Moritz Angermann at 2020-11-26T10:32:41+08:00 Use ip0 for spills/reloads - - - - - 34ed36f1 by Moritz Angermann at 2020-11-26T10:33:57+08:00 :broom: Cleanup - - - - - 6f5776da by Moritz Angermann at 2020-11-26T10:34:22+08:00 Add validate as well. - - - - - e4f94ba8 by Moritz Angermann at 2020-11-26T10:34:22+08:00 Revert "Simplify aarch64 StgRun" This reverts commit f27472c0483db2382344f4a8f4c1b2a192d98725. - - - - - f620f0af by Moritz Angermann at 2020-11-26T10:34:22+08:00 Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md - - - - - 7c85f53a by Moritz Angermann at 2020-11-26T10:34:22+08:00 Apply suggestion to compiler/GHC/CmmToAsm/AArch64/README.md - - - - - 53b7f2ec by Moritz Angermann at 2020-11-26T10:34:39+08:00 Add CLabel logic - - - - - 7078f25d by Moritz Angermann at 2020-11-26T10:35:40+08:00 [configure] make arm64-apple-darwin an LLVM Target This is required as the llvm toolchain doesn't like aarch64-apple-darwin, and only accepts arm64-apple-darwin. - - - - - 291dd625 by Moritz Angermann at 2020-11-26T10:36:29+08:00 [arm64/mach-o] adrp/ldr symbol names This will break elf. We need to find a better solution for this symbol naming is platform dependent here. :got: / @gotpage :got_lo12: / @gotpageoff :lo12: / @pageoff - - - - - 69c88134 by Moritz Angermann at 2020-11-26T10:38:04+08:00 [WIP] symbol garbage Naming is hard. Supporting assembler and linker even harder. L is the assembly local prefix l is the linker local prefix L is not relocated at all. l is relocated, but fails to for conditional branches. Send help! - - - - - 455627e4 by Moritz Angermann at 2020-11-26T10:38:16+08:00 [MachO] cleanup compiler warnings - - - - - 99f823a6 by Moritz Angermann at 2020-11-26T10:38:29+08:00 [Storage/Adjustor] Drop size check in allocExec This is violated by ghci, in InfoTable.hsc we call _allocateExec with a size that does not guarantee to be of ffi_closure size. Other allocateExec implementations do not have this check either; I highly doubt it's sensible to have this check in the presence of ghci's allocateExec calls. - - - - - b313ebfc by Moritz Angermann at 2020-11-26T10:38:30+08:00 [linker/elf] better errors (with error message) - - - - - 6c1f47e0 by Moritz Angermann at 2020-11-26T10:38:41+08:00 [aarch64/codegen] pack ccall arguments on darwin This is annoying, but the darwinpcs does not match the default aapcs :facepalm: - - - - - 6ca8a6f4 by Moritz Angermann at 2020-11-26T10:38:41+08:00 [linker:MachO] split PLT logic out. Why was this missing in the first place? It's now a bit more aligned to the elf plt logic. - - - - - eea02e96 by Moritz Angermann at 2020-11-26T10:39:57+08:00 [configure] fix LLVMTarget when native uname -p return "arm", hence we can't work with target_cpu, but need to match on the target triple. - - - - - 5357f0e5 by Moritz Angermann at 2020-11-26T10:40:00+08:00 [testsuite] fix subsections_via_symbols test - - - - - f7c0b975 by Moritz Angermann at 2020-11-26T10:40:00+08:00 [testsuite] FixT11649 - - - - - 3dbace0c by Moritz Angermann at 2020-11-26T10:40:00+08:00 Fix conc059 test - - - - - 097c3f0a by Moritz Angermann at 2020-11-26T10:40:01+08:00 WIP: fix ghci adjustors on aarch64/arm (infotables) - - - - - 75891882 by Moritz Angermann at 2020-11-26T10:42:18+08:00 [DWARF] Enable only on elf platforms - - - - - 731693b8 by Moritz Angermann at 2020-11-26T10:42:27+08:00 [Testsuite/LLVM] Fix T5681, T7571, T8131b - - - - - 9ee45a21 by Moritz Angermann at 2020-11-26T10:42:27+08:00 [testsuite/darwin] fix tests ghcilink003, ghcilink006 - - - - - ea1573ce by Moritz Angermann at 2020-11-26T10:45:21+08:00 Fix linker_error2 - - - - - 699cac12 by Moritz Angermann at 2020-11-26T10:46:28+08:00 Sized Hints - - - - - f9b81d24 by Moritz Angermann at 2020-11-26T10:46:28+08:00 [Testsuite/arm64] Fix test derefnull - - - - - ed09064e by Moritz Angermann at 2020-11-26T10:46:29+08:00 [testsuite/arm64] fix section_alignment - - - - - ff0c6f6e by Moritz Angermann at 2020-11-26T10:46:29+08:00 [macOS/arm64] darwinpcs :facepalm: - - - - - 2c5125c4 by Moritz Angermann at 2020-11-26T10:46:29+08:00 [aarch64/darwin] ifdef for got lables. This should ideally be some runtime flag, but it would need access to the platform. - - - - - 588c1701 by Moritz Angermann at 2020-11-26T10:46:29+08:00 [aarch64/rts] fix missing prototypes - - - - - 13fd1ddc by Moritz Angermann at 2020-11-26T10:46:29+08:00 Int has Word size in Haskell. - - - - - 7d63f163 by Moritz Angermann at 2020-11-26T10:46:30+08:00 [debug only] warn on hint/arg mismatch - - - - - 90300544 by Moritz Angermann at 2020-11-26T10:46:30+08:00 [AArch64 NCG] User argument format rather than hint. - - - - - d5406765 by Moritz Angermann at 2020-11-26T10:46:30+08:00 [Debug] Fix CmmFloat warnings. - - - - - efe4144f by Moritz Angermann at 2020-11-26T10:46:30+08:00 [aarch64/elf] fixup elf symbols - - - - - fbec2538 by Moritz Angermann at 2020-11-26T10:46:30+08:00 :facepalm: - - - - - d9693ad5 by Moritz Angermann at 2020-11-26T10:46:31+08:00 :facepalm: - - - - - 8df5d41f by Moritz Angermann at 2020-11-26T10:46:31+08:00 [Adjustors] Proper allocator handling. - - - - - a493e703 by Moritz Angermann at 2020-11-26T10:46:31+08:00 Revert "[AArch64] Aarch64 Always PIC" This reverts commit 921276592218211f441fcf011fc52441e3a2f0a6. - - - - - 5f86875c by Moritz Angermann at 2020-11-26T10:46:31+08:00 Revert "[Storage/Adjustor] Drop size check in allocExec" This reverts commit 37a62ae956a25e5832fbe125a4d8ee556fd11042. - - - - - fb197813 by Moritz Angermann at 2020-11-26T10:46:31+08:00 [Storage] Reinstate check; add comment. - - - - - 615d2b26 by Moritz Angermann at 2020-11-26T10:46:32+08:00 [AArch64] Aarch64 Always PIC - - - - - 81e93c4d by Moritz Angermann at 2020-11-26T10:46:32+08:00 [testsuite] static001 is not broken anymore. - - - - - 2b95a984 by Moritz Angermann at 2020-11-26T10:46:32+08:00 Revert "Sized Hints" This reverts commit 65cbfcc10e7ad32dd04ebce011860f5b557eacac. - - - - - 1dabc1b3 by Moritz Angermann at 2020-11-26T10:47:20+08:00 fix up rebase - - - - - 18 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Type.hs - compiler/GHC/Cmm/Utils.hs - compiler/GHC/CmmToAsm.hs - + compiler/GHC/CmmToAsm/AArch64.hs - + compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - + compiler/GHC/CmmToAsm/AArch64/Cond.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cc7cdb3645892e98daddfafc56ad1c0b597688c...1dabc1b32f71c5744caea510fca146a70d517863 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cc7cdb3645892e98daddfafc56ad1c0b597688c...1dabc1b32f71c5744caea510fca146a70d517863 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 Nov 26 04:20:20 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 25 Nov 2020 23:20:20 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 2 commits: Write commit message here. Message-ID: <5fbf2d04a53cd_86c11450e283060e@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: 51c0d143 by Richard Eisenberg at 2020-11-25T23:19:37-05:00 Write commit message here. - - - - - c51fd46e by Richard Eisenberg at 2020-11-25T23:19:37-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - 30 changed files: - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3272ecf4142476803b1f62ec67cb9d999a59bdcd...c51fd46ec10935953cc19747e41808f05294164f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3272ecf4142476803b1f62ec67cb9d999a59bdcd...c51fd46ec10935953cc19747e41808f05294164f 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 Nov 26 04:55:26 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Wed, 25 Nov 2020 23:55:26 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 2 commits: Remove flattening variables Message-ID: <5fbf353e6b000_86ce89fc5c307450@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: f9ab3c45 by Richard Eisenberg at 2020-11-25T23:53:55-05:00 Remove flattening variables This patch redesigns the flattener to simplify type family applications directly instead of using flattening meta-variables and skolems. The key new innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS is either a type variable or exactly-saturated type family application; either can now be rewritten using a CEqCan constraint in the inert set. Because the flattener no longer reduces all type family applications to variables, there was some performance degradation if a lengthy type family application is now flattened over and over (not making progress). To compensate, this patch contains some extra optimizations in the flattener, leading to a number of performance improvements. Close #18875. Close #18910. There are many extra parts of the compiler that had to be affected in writing this patch: * The family-application cache (formerly the flat-cache) sometimes stores coercions built from Given inerts. When these inerts get kicked out, we must kick out from the cache as well. (This was, I believe, true previously, but somehow never caused trouble.) Kicking out from the cache requires adding a filterTM function to TrieMap. * This patch obviates the need to distinguish "blocking" coercion holes from non-blocking ones (which, previously, arose from CFunEqCans). There is thus some simplification around coercion holes. * Extra commentary throughout parts of the code I read through, to preserve the knowledge I gained while working. * A change in the pure unifier around unifying skolems with other types. Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented in Note [Binding when looking up instances] in GHC.Core.InstEnv. * Some more use of MCoercion where appropriate. * Previously, class-instance lookup automatically noticed that e.g. C Int was a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to a variable. Now, a little more care must be taken around checking for unifying instances. * Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly, because (=>) is not a tycon in Haskell. Fixed now, but there are some knock-on changes in e.g. TrieMap code and in the canonicaliser. * New function anyFreeVarsOf{Type,Co} to check whether a free variable satisfies a certain predicate. * Type synonyms now remember whether or not they are "forgetful"; a forgetful synonym drops at least one argument. This is useful when flattening; see flattenView. * The pattern-match completeness checker invokes the solver. This invocation might need to look through newtypes when checking representational equality. Thus, the desugarer needs to keep track of the in-scope variables to know what newtype constructors are in scope. I bet this bug was around before but never noticed. * Extra-constraints wildcards are no longer simplified before printing. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. * Whether or not there are Given equalities has become slightly subtler. See the new HasGivenEqs datatype. * Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical explains a significant new wrinkle in the new approach. * See Note [What might match later?] in GHC.Tc.Solver.Interact, which explains the fix to #18910. Though I (Richard) did the implementation, Simon PJ was very involved in design and review. - - - - - faad5f02 by Richard Eisenberg at 2020-11-25T23:53:55-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - 30 changed files: - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Instance/Family.hs - compiler/GHC/Tc/Plugin.hs - compiler/GHC/Tc/Solver.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c51fd46ec10935953cc19747e41808f05294164f...faad5f02b2728c022c69d930679cee16707956ad -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c51fd46ec10935953cc19747e41808f05294164f...faad5f02b2728c022c69d930679cee16707956ad 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 Nov 26 08:39:51 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 26 Nov 2020 03:39:51 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fbf69d7d252d_86ce89fc5c3283a0@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 3cc388ff by Moritz Angermann at 2020-11-26T03:39:33-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - 8c6a9221 by David Eichmann at 2020-11-26T03:39:33-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fae0c218 by Andreas Klebinger at 2020-11-26T03:39:34-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - d4f2bb87 by Sylvain Henry at 2020-11-26T03:39:34-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - c166c1e0 by Tim Barnes at 2020-11-26T03:39:36-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 5d628c26 by Ben Gamari at 2020-11-26T03:39:36-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - e08089a9 by Matthew Pickering at 2020-11-26T03:39:37-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - dc11a747 by Matthew Pickering at 2020-11-26T03:39:37-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/526a166544007a4ded1d3e01ca2a46a17f1406b2...dc11a747f6dae269e90fbf4547471cc05cd8e530 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/526a166544007a4ded1d3e01ca2a46a17f1406b2...dc11a747f6dae269e90fbf4547471cc05cd8e530 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 Nov 26 14:10:11 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 26 Nov 2020 09:10:11 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fbfb743eabb1_86c3fc6ab4f115c386936@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: adfecf42 by Moritz Angermann at 2020-11-26T09:10:00-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - b424acdf by Andreas Klebinger at 2020-11-26T09:10:00-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - d23bb143 by Sylvain Henry at 2020-11-26T09:10:00-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - 0c6d2abf by Tim Barnes at 2020-11-26T09:10:01-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - c3c7520b by Ben Gamari at 2020-11-26T09:10:02-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 567a8d5f by Matthew Pickering at 2020-11-26T09:10:02-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - 3233e536 by Matthew Pickering at 2020-11-26T09:10:02-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 62b56d33 by Andreas Klebinger at 2020-11-26T09:10:03-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc11a747f6dae269e90fbf4547471cc05cd8e530...62b56d3358bf12cf364474aa4b5dc27cc973a01f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc11a747f6dae269e90fbf4547471cc05cd8e530...62b56d3358bf12cf364474aa4b5dc27cc973a01f 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 Nov 26 14:22:51 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Thu, 26 Nov 2020 09:22:51 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] Rts/elf-linker: Use proper format string. Message-ID: <5fbfba3b242b1_86c111d4a003965bc@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: e818856f by Andreas Klebinger at 2020-11-26T15:22:32+01:00 Rts/elf-linker: Use proper format string. - - - - - 1 changed file: - rts/linker/Elf.c Changes: ===================================== rts/linker/Elf.c ===================================== @@ -904,7 +904,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ASSERT(common_used <= common_size); IF_DEBUG(linker, - debugBelch("COMMON symbol, size %lu name %s allocated at %p\n", + debugBelch("COMMON symbol, size %u name %s allocated at %p\n", symbol->elf_sym->st_size, nm, symbol->addr)); /* Pointless to do addProddableBlock() for this area, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e818856f88097a9d58a4997bf6947a16651e2bfb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e818856f88097a9d58a4997bf6947a16651e2bfb 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 Nov 26 15:02:47 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Thu, 26 Nov 2020 10:02:47 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fbfc3971e3b3_86cfd752bc400514@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: db6de429 by Shayne Fletcher at 2020-11-26T10:02:30-05:00 Record dot syntax - - - - - 26 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3727,6 +3727,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pu_flds :: [Located FastString] + , pu_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate { pu_flds = flds, pu_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -457,6 +479,51 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_field :: Located FastString + , gf_getField :: LHsExpr p -- Equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnComma, 'GHC.Parser.Annotation.AnnDot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_flds :: [Located FastString] + , proj_projection :: LHsExpr p -- Equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -648,6 +715,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1193,6 +1272,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_field = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_flds = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1347,6 +1434,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -555,6 +555,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -269,6 +269,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,6 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -68,7 +71,7 @@ import GHC.Prelude -- compiler/basicTypes import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore, mkVarOcc, occNameString, occNameFS ) import GHC.Core.DataCon ( DataCon, dataConName ) import GHC.Types.SrcLoc import GHC.Unit.Module @@ -95,7 +98,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nil manyDataConTyCon) } -%expect 232 -- shift/reduce conflicts +%expect 234 -- shift/reduce conflicts {- Last updated: 08 June 2020 @@ -551,6 +554,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } '{' { L _ ITocurly } -- special symbols @@ -2610,6 +2615,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2699,10 +2720,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2730,6 +2753,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2778,6 +2809,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3193,33 +3232,64 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError l $ + text "For this to work, enable NamedFieldPuns." + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3512,6 +3582,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -618,6 +618,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -779,6 +792,7 @@ data Token | ITtypeApp -- Prefix (@) only, e.g. f @t | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1585,6 +1599,9 @@ varsym_prefix = sym $ \exts s -> | s == fsLit "-" -- Only when LexicalNegation is on, otherwise we get ITminus and -- don't hit this code path. See Note [Minus tokens] -> return ITprefixminus + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> return (ITvarsym s) @@ -1594,17 +1611,28 @@ varsym_suffix :: Action varsym_suffix = sym $ \_ s -> if | s == fsLit "@" -> failMsgP "Suffix occurrence of @. For an as-pattern, remove the leading whitespace." + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \_ s -> - if | s == fsLit "@" -> return ITat +varsym_tight_infix = sym $ \exts s -> + if | s == fsLit "@" + -> return ITat + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj False) + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_exts s -> return $ ITconsym s) @@ -1612,8 +1640,13 @@ consym = sym (\_exts s -> return $ ITconsym s) sym :: (ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2619,6 +2652,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2709,6 +2744,8 @@ mkParserFlags' warningFlags extensionFlags homeUnitId .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,6 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -31,7 +32,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkLHsSigType, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -137,6 +138,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Session ( WarningFlag(..), DynFlags ) @@ -151,6 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1385,6 +1403,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1441,10 +1461,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1463,7 +1484,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1512,6 +1532,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1545,8 +1566,12 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1575,6 +1600,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1604,8 +1630,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (mkLHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1662,6 +1688,9 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e + mkHsProjUpdatePV l _ _ = + addFatalError l $ + text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ text "Lambda-syntax in pattern." $$ text "Pattern matching on functions is not possible." @@ -1692,9 +1721,14 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text " Use of RecordDotSyntax `.' not valid.") + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2331,17 +2365,51 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2885,3 +2953,127 @@ starSym False = "*" forallSym :: Bool -> String forallSym True = "∀" forallSym False = "forall" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fieldS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @field x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (field : fieldS) = foldl' f (proj field) fieldS + where + f acc field = (mkParen . mkOpApp (proj field) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg field calcuates a get_field @field arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg field = head $ mkGet' [arg] field +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ field) = get_field `mkAppType` mkSelector field `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg field = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_field = field + , gf_getField = mkGet arg field + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible happened" +mkProjection loc flds = + L loc Projection { + proj_ext = noExtField + , proj_flds = flds + , proj_projection = mkProj flds + } + +-- mkSet a field b calculates a set_field @field expression. +-- e.g mkSet a field b = set_field @"field" a b (read as "set field 'field' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ field) b = set_field `mkAppType` mkSelector field `mkApp` a `mkApp` b + + -- e.g foo.bar.baz.quux = 43 +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate l flds arg = L l $ ProjUpdate { pu_flds = flds, pu_arg = arg } + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pu_flds = flds, pu_arg = arg } )) + = let { + ; final = last flds -- quux + ; fields = init flds -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (field, g) = mkSet (mkParen g) field (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pu_flds = fs, pu_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1029,6 +1029,17 @@ tcExpr e@(HsRecFld _ f) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -499,6 +499,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -511,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -173,3 +173,8 @@ test('T18251c', normal, compile_fail, ['']) test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/db6de42975d6272e38268e19af4057985fe72952 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/db6de42975d6272e38268e19af4057985fe72952 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 Nov 26 15:14:37 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Thu, 26 Nov 2020 10:14:37 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fbfc65dc9feb_86c3fc6ab4f115c400780@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: b55cfb67 by Shayne Fletcher at 2020-11-26T10:14:18-05:00 Record dot syntax - - - - - 26 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3727,6 +3727,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} @@ -239,6 +241,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pu_flds :: [Located FastString] + , pu_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate { pu_flds = flds, pu_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -457,6 +479,51 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_field :: Located FastString + , gf_getField :: LHsExpr p -- Desugared equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnComma, 'GHC.Parser.Annotation.AnnDot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Desugared equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_flds :: [Located FastString] + , proj_proj :: LHsExpr p -- Desugared equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -648,6 +715,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1193,6 +1272,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_field = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_flds = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1347,6 +1434,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -555,6 +555,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -269,6 +269,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1162,6 +1162,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -68,7 +71,7 @@ import GHC.Prelude -- compiler/basicTypes import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, startsWithUnderscore, mkVarOcc, occNameString, occNameFS ) import GHC.Core.DataCon ( DataCon, dataConName ) import GHC.Types.SrcLoc import GHC.Unit.Module @@ -95,7 +98,7 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, tupleTyCon, tupleDataCon, nil manyDataConTyCon) } -%expect 232 -- shift/reduce conflicts +%expect 234 -- shift/reduce conflicts {- Last updated: 08 June 2020 @@ -551,6 +554,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } '{' { L _ ITocurly } -- special symbols @@ -2610,6 +2615,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2699,10 +2720,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2730,6 +2753,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2778,6 +2809,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3193,33 +3232,64 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError l $ + text "For this to work, enable NamedFieldPuns." + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3512,6 +3582,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -618,6 +618,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -779,6 +792,7 @@ data Token | ITtypeApp -- Prefix (@) only, e.g. f @t | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1585,6 +1599,9 @@ varsym_prefix = sym $ \exts s -> | s == fsLit "-" -- Only when LexicalNegation is on, otherwise we get ITminus and -- don't hit this code path. See Note [Minus tokens] -> return ITprefixminus + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> return (ITvarsym s) @@ -1594,17 +1611,28 @@ varsym_suffix :: Action varsym_suffix = sym $ \_ s -> if | s == fsLit "@" -> failMsgP "Suffix occurrence of @. For an as-pattern, remove the leading whitespace." + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \_ s -> - if | s == fsLit "@" -> return ITat +varsym_tight_infix = sym $ \exts s -> + if | s == fsLit "@" + -> return ITat + | RecordDotSyntaxBit `xtest` exts, s == fsLit "." + -> return (ITproj False) + | s == fsLit "." + -> return ITdot | otherwise -> return (ITvarsym s) -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_exts s -> return $ ITconsym s) @@ -1612,8 +1640,13 @@ consym = sym (\_exts s -> return $ ITconsym s) sym :: (ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2619,6 +2652,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2709,6 +2744,8 @@ mkParserFlags' warningFlags extensionFlags homeUnitId .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -19,6 +19,7 @@ {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -31,7 +32,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkLHsSigType, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -137,6 +138,7 @@ import GHC.Data.FastString import GHC.Data.Maybe import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Session ( WarningFlag(..), DynFlags ) @@ -151,6 +153,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1385,6 +1403,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1441,10 +1461,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1463,7 +1484,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1512,6 +1532,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = cmdFail l (text "Use of RecordDotSyntax `.' not valid.") mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1545,8 +1566,12 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1575,6 +1600,7 @@ instance DisambECP (HsExpr GhcPs) where nest 2 (ppr c) ] return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1604,8 +1630,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (mkLHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1662,6 +1688,9 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError l $ text "Expression syntax in pattern:" <+> ppr e + mkHsProjUpdatePV l _ _ = + addFatalError l $ + text "Use of RecordDotSyntax `.' not valid." mkHsLamPV l _ = addFatalError l $ text "Lambda-syntax in pattern." $$ text "Pattern matching on functions is not possible." @@ -1692,9 +1721,14 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text " Use of RecordDotSyntax `.' not valid.") + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2331,17 +2365,51 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _ (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError (getLoc (head ps)) + (text "Use of RecordDotSyntax `.' not valid.") + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError dd_loc (text "You cannot use `..' in a record update") - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2885,3 +2953,132 @@ starSym False = "*" forallSym :: Bool -> String forallSym True = "∀" forallSym False = "forall" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fieldS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @field x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (field : fieldS) = foldl' f (proj field) fieldS + where + f acc field = (mkParen . mkOpApp (proj field) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg field calcuates a get_field @field arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg field = head $ mkGet' [arg] field +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ field) = get_field `mkAppType` mkSelector field `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg field = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_field = field + , gf_getField = mkGet arg field + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible has happened!" +mkProjection loc flds = + L loc Projection { + proj_ext = noExtField + , proj_flds = flds + , proj_proj = mkProj flds + } + +-- e.g. foo.bar.baz.quux = 1 +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate _ [] _ = panic "mkProjUpdate: The impossible has happened!" +mkProjUpdate loc flds arg = + L loc ProjUpdate { + pu_flds = flds + , pu_arg = arg + } + +-- mkSet a field b calculates a set_field @field expression. +-- e.g mkSet a field b = set_field @"field" a b (read as "set field 'field' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ field) b = set_field `mkAppType` mkSelector field `mkApp` a `mkApp` b + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pu_flds = flds, pu_arg = arg } )) + = let { + ; final = last flds -- quux + ; fields = init flds -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (field, g) = mkSet (mkParen g) field (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pu_flds = fs, pu_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1029,6 +1029,17 @@ tcExpr e@(HsRecFld _ f) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -499,6 +499,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -511,6 +513,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -173,3 +173,8 @@ test('T18251c', normal, compile_fail, ['']) test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b55cfb6777e4d32be25d2c4f6ea67a0f03be049b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b55cfb6777e4d32be25d2c4f6ea67a0f03be049b 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 Nov 26 15:24:59 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Thu, 26 Nov 2020 10:24:59 -0500 Subject: [Git][ghc/ghc][wip/con-info] 4 commits: Turn on SourceNotes without -g Message-ID: <5fbfc8cbe39a4_86c3fc6ab4f115c4012cc@gitlab.mail> Matthew Pickering pushed to branch wip/con-info at Glasgow Haskell Compiler / GHC Commits: 55da5b4d by Matthew Pickering at 2020-11-26T10:32:59+00:00 Turn on SourceNotes without -g - - - - - f57343e5 by Matthew Pickering at 2020-11-26T15:14:38+00:00 release notes - - - - - db0274b4 by Matthew Pickering at 2020-11-26T15:14:51+00:00 debug info docs - - - - - 10d7be01 by Matthew Pickering at 2020-11-26T15:24:51+00:00 Some more comments - - - - - 4 changed files: - compiler/GHC/HsToCore/Coverage.hs - compiler/GHC/Types/IPE.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/debug-info.rst Changes: ===================================== compiler/GHC/HsToCore/Coverage.hs ===================================== @@ -1044,13 +1044,17 @@ data TickTransEnv = TTE { fileName :: FastString data TickishType = ProfNotes | HpcTicks | Breakpoints | SourceNotes deriving (Eq) +sourceNotesEnabled :: DynFlags -> Bool +sourceNotesEnabled dflags = + (debugLevel dflags > 0) || (gopt Opt_InfoTableMap dflags) + coveragePasses :: DynFlags -> [TickishType] coveragePasses dflags = ifa (breakpointsEnabled dflags) Breakpoints $ ifa (gopt Opt_Hpc dflags) HpcTicks $ ifa (sccProfilingEnabled dflags && profAuto dflags /= NoProfAuto) ProfNotes $ - ifa (debugLevel dflags > 0) SourceNotes [] + ifa (sourceNotesEnabled dflags) SourceNotes [] where ifa f x xs | f = x:xs | otherwise = xs ===================================== compiler/GHC/Types/IPE.hs ===================================== @@ -11,12 +11,19 @@ import GHC.Types.Unique.Map -- | A map from a 'Name' to the best approximate source position that -- name arose from. -type ClosureMap = UniqMap - Name -- The binding - (String, RealSrcSpan, String) -- The best approximate source position. +type ClosureMap = UniqMap Name -- The binding + (String, RealSrcSpan, String) + -- The best approximate source position. + -- (rendered type, source position, source note + -- label) -- | A map storing all the different uses of a specific data constructor and the -- approximate source position that usage arose from. +-- The `Int` is an incrementing identifier which distinguishes each usage +-- of a constructor in a module. It is paired with the source position +-- the constructor was used at, if possible and a string which names +-- the source location. This is the same information as is the payload +-- for the `GHC.Core.SourceNote` constructor. type DCMap = UniqMap DataCon [(Int, Maybe (RealSrcSpan, String))] data InfoTableProvMap = InfoTableProvMap ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -46,7 +46,7 @@ Compiler also useful with this flag to give each usage of a data constructor its own unique info table so they can be distinguished in gdb and heap profiles. -- A new heap profiling mode, :ghc-flag:`-hi`, profile by info table allows for +- A new heap profiling mode, :rts-flag:`-hi`, profile by info table allows for fine-grain banding by the info table address of a closure. The profiling mode is intended to be used with :ghc-flag:`-finfo-table-map` and can best be consumed with ``eventlog2html``. This profiling mode does not require a ===================================== docs/users_guide/debug-info.rst ===================================== @@ -356,8 +356,7 @@ to a source location. This lookup table is generated by using the ``-finfo-table This flag enables the generation of a table which maps the address of an info table to an approximate source position of where that - info table statically originated from. You almost certainly want to use this - with :ghc-flag:`-g` to improve the accuracy of the source positions. If you + info table statically originated from. If you also want more precise information about constructor info tables then you should also use :ghc-flag:`-fdistinct-constructor-tables`. @@ -375,7 +374,7 @@ to a source location. This lookup table is generated by using the ``-finfo-table For every usage of a data constructor in the source program a new info table will be created. This is useful with - :ghc-flag:`-finfo-table-map` and the :ghc-flag:`-hi` profiling mode as + :ghc-flag:`-finfo-table-map` and the :rts-flag:`-hi` profiling mode as each info table will correspond to the usage of a data constructor rather than the data constructor itself. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/364ceb537a5010bb4bf2c655dbc4f0cf1f00b95b...10d7be0129954b5e44e3d05552a4aa8f9da16fac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/364ceb537a5010bb4bf2c655dbc4f0cf1f00b95b...10d7be0129954b5e44e3d05552a4aa8f9da16fac 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 Nov 26 15:32:14 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Thu, 26 Nov 2020 10:32:14 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_partial_tso_stack_decode] ghc-heap: partial TSO/STACK decoding Message-ID: <5fbfca7ed4624_86c7d59240402965@gitlab.mail> Matthew Pickering pushed to branch wip/ghc-debug_partial_tso_stack_decode at Glasgow Haskell Compiler / GHC Commits: bb4fc4d4 by David Eichmann at 2020-11-26T15:31:10+00:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22 changed files: - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Runtime/Interpreter.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Heap.c - rts/PrimOps.cmm Changes: ===================================== compiler/GHC/ByteCode/Types.hs ===================================== @@ -37,7 +37,7 @@ import Data.ByteString (ByteString) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.Maybe (catMaybes) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS -- ----------------------------------------------------------------------------- @@ -72,7 +72,7 @@ type ItblEnv = NameEnv (Name, ItblPtr) -- We need the Name in the range so we know which -- elements to filter out when unloading a module -newtype ItblPtr = ItblPtr (RemotePtr StgInfoTable) +newtype ItblPtr = ItblPtr (RemotePtr Heap.StgInfoTable) deriving (Show, NFData) data UnlinkedBCO ===================================== compiler/GHC/Runtime/Interpreter.hs ===================================== @@ -103,7 +103,7 @@ import qualified Data.ByteString.Lazy as LB import Data.Array ((!)) import Data.IORef import Foreign hiding (void) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS (CostCentre,CostCentreStack) import System.Exit import GHC.IO.Handle.Types (Handle) @@ -395,7 +395,7 @@ getBreakpointVar hsc_env ref ix = mb <- iservCmd hsc_env (GetBreakpointVar apStack ix) mapM (mkFinalizedHValue hsc_env) mb -getClosure :: HscEnv -> ForeignHValue -> IO (GenClosure ForeignHValue) +getClosure :: HscEnv -> ForeignHValue -> IO (Heap.GenClosure ForeignHValue) getClosure hsc_env ref = withForeignRef ref $ \hval -> do mb <- iservCmd hsc_env (GetClosure hval) ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -27,6 +27,9 @@ module GHC.Exts.Heap ( , GenClosure(..) , ClosureType(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , HasHeapRep(getClosureData) , getClosureDataFromHeapRep @@ -39,6 +42,12 @@ module GHC.Exts.Heap ( , peekItbl , pokeItbl + -- * Cost Centre (profiling) types + , StgTSOProfInfo(..) + , IndexTable(..) + , CostCentre(..) + , CostCentreStack(..) + -- * Closure inspection , getBoxedClosureData , allClosures @@ -53,12 +62,14 @@ import Prelude import GHC.Exts.Heap.Closures import GHC.Exts.Heap.ClosureTypes import GHC.Exts.Heap.Constants +import GHC.Exts.Heap.ProfInfo.Types #if defined(PROFILING) import GHC.Exts.Heap.InfoTableProf #else import GHC.Exts.Heap.InfoTable #endif import GHC.Exts.Heap.Utils +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures import Control.Monad import Data.Bits @@ -323,6 +334,45 @@ getClosureDataFromHeapRep heapRep infoTablePtr pts = do , finalizer = pts !! 3 , link = pts !! 4 } + TSO | [ u_lnk, u_gbl_lnk, tso_stack, u_trec, u_blk_ex, u_bq] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekTSOFields ptr + pure $ TSOClosure + { info = itbl + , link = u_lnk + , global_link = u_gbl_lnk + , tsoStack = tso_stack + , trec = u_trec + , blocked_exceptions = u_blk_ex + , bq = u_bq + , what_next = FFIClosures.tso_what_next fields + , why_blocked = FFIClosures.tso_why_blocked fields + , flags = FFIClosures.tso_flags fields + , threadId = FFIClosures.tso_threadId fields + , saved_errno = FFIClosures.tso_saved_errno fields + , tso_dirty = FFIClosures.tso_dirty fields + , alloc_limit = FFIClosures.tso_alloc_limit fields + , tot_stack_size = FFIClosures.tso_tot_stack_size fields + , prof = FFIClosures.tso_prof fields + }) + | otherwise + -> fail $ "Expected 6 ptr arguments to TSO, found " + ++ show (length pts) + STACK + | [] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekStackFields ptr + pure $ StackClosure + { info = itbl + , stack_size = FFIClosures.stack_size fields + , stack_dirty = FFIClosures.stack_dirty fields +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking = FFIClosures.stack_marking fields +#endif + }) + | otherwise + -> fail $ "Expected 0 ptr argument to STACK, found " + ++ show (length pts) _ -> pure $ UnsupportedClosure itbl ===================================== libraries/ghc-heap/GHC/Exts/Heap/Closures.hs ===================================== @@ -12,6 +12,9 @@ module GHC.Exts.Heap.Closures ( Closure , GenClosure(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , allClosures #if __GLASGOW_HASKELL__ >= 809 -- The closureSize# primop is unsupported on earlier GHC releases but we @@ -40,6 +43,8 @@ import GHC.Exts.Heap.InfoTable import GHC.Exts.Heap.InfoTableProf () #endif +import GHC.Exts.Heap.ProfInfo.Types + import Data.Bits import Data.Int import Data.Word @@ -100,11 +105,11 @@ type Closure = GenClosure Box -- | This is the representation of a Haskell value on the heap. It reflects -- -- --- The data type is parametrized by the type to store references in. Usually --- this is a 'Box' with the type synonym 'Closure'. +-- The data type is parametrized by `b`: the type to store references in. +-- Usually this is a 'Box' with the type synonym 'Closure'. -- --- All Heap objects have the same basic layout. A header containing a pointer --- to the info table and a payload with various fields. The @info@ field below +-- All Heap objects have the same basic layout. A header containing a pointer to +-- the info table and a payload with various fields. The @info@ field below -- always refers to the info table pointed to by the header. The remaining -- fields are the payload. -- @@ -268,6 +273,39 @@ data GenClosure b , link :: !b -- ^ next weak pointer for the capability, can be NULL. } + -- | Representation of StgTSO: A Thread State Object. The values for + -- 'what_next', 'why_blocked' and 'flags' are defined in @Constants.h at . + | TSOClosure + { info :: !StgInfoTable + -- pointers + , link :: !b + , global_link :: !b + , tsoStack :: !b -- ^ stackobj from StgTSO + , trec :: !b + , blocked_exceptions :: !b + , bq :: !b + -- values + , what_next :: !WhatNext + , why_blocked :: !WhyBlocked + , flags :: ![TsoFlags] + , threadId :: !Word64 + , saved_errno :: !Word32 + , tso_dirty :: !Word32 -- ^ non-zero => dirty + , alloc_limit :: !Int64 + , tot_stack_size :: !Word32 + , prof :: !(Maybe StgTSOProfInfo) + } + + -- | Representation of StgStack: The 'tsoStack ' of a 'TSOClosure'. + | StackClosure + { info :: !StgInfoTable + , stack_size :: !Word32 -- ^ stack size in *words* + , stack_dirty :: !Word8 -- ^ non-zero => dirty +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking :: !Word8 +#endif + } + ------------------------------------------------------------ -- Unboxed unlifted closures @@ -332,6 +370,43 @@ data PrimType | PDouble deriving (Eq, Show, Generic) +data WhatNext + = ThreadRunGHC + | ThreadInterpret + | ThreadKilled + | ThreadComplete + | WhatNextUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data WhyBlocked + = NotBlocked + | BlockedOnMVar + | BlockedOnMVarRead + | BlockedOnBlackHole + | BlockedOnRead + | BlockedOnWrite + | BlockedOnDelay + | BlockedOnSTM + | BlockedOnDoProc + | BlockedOnCCall + | BlockedOnCCall_Interruptible + | BlockedOnMsgThrowTo + | ThreadMigrating + | BlockedOnIOCompletion + | WhyBlockedUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data TsoFlags + = TsoLocked + | TsoBlockx + | TsoInterruptible + | TsoStoppedOnBreakpoint + | TsoMarked + | TsoSqueezed + | TsoAllocLimit + | TsoFlagsUnknownValue Word32 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + -- | For generic code, this function returns all referenced closures. allClosures :: GenClosure b -> [b] allClosures (ConstrClosure {..}) = ptrArgs ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs ===================================== @@ -0,0 +1,47 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.FFIClosures (module Reexport) where + +-- NOTE [hsc and CPP workaround] +-- +-- # Problem +-- +-- Often, .hsc files are used to get the correct offsets of C struct fields. +-- Those structs may be affected by CPP directives e.g. profiled vs not profiled +-- closure headers is affected by the PROFILED cpp define. Since we are building +-- multiple variants of the RTS, we must support all possible offsets e.g. by +-- running hsc2hs with cpp defines corresponding to each RTS flavour. The +-- problem is that GHC's build system runs hsc2hs *only once* per .hsc file +-- without properly setting cpp defines. This results in the same (probably +-- incorrect) offsets into our C structs. +-- +-- +-- # Workaround +-- +-- To work around this issue, we create multiple .hsc files each manually +-- defining thir cpp defines (see e.g. FFIClosures_ProfilingDisabled.hsc and +-- FFIClosures_ProfilingEnabled.hsc). Then we rely on cpp defines working +-- correctly in .hs files and use CPP to switch on which .hsc module to +-- re-export (see below). In each case we import the desired .hsc module as +-- `Reexport` and we import `()` (i.e. nothing) from all other .hsc variants +-- just so that the build system sees all .hsc file as dependencies. +-- +-- +-- # Future Work +-- +-- * Duplication of the code in the .hsc files could be reduced simply by +-- placing the code in a single .hsc.in file and `#include`ing it from each +-- .hsc file. The .hsc files would only be responsible for setting the correct +-- cpp defines. This currently doesn't work as hadrian doesn't know to copy +-- the .hsc.in file to the build directory. +-- * The correct solution would be for the build system to run `hsc2hs` with the +-- correct cpp defines once per RTS flavour. +-- + +#if defined(PROFILING) +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled () +#else +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,131 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingDisabled where + +-- See [hsc and CPP workaround] + +#undef PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } + ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,130 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingEnabled where + +-- See [hsc and CPP workaround] + +#define PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo (module Reexport) where + +-- See [hsc and CPP workaround] + +#if defined(PROFILING) +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled () +#else +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,12 @@ +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled( + peekStgTSOProfInfo +) where + +import Prelude +import Foreign +import GHC.Exts.Heap.ProfInfo.Types + +-- | This implementation is used when PROFILING is undefined. +-- It always returns 'Nothing', because there is no profiling info available. +peekStgTSOProfInfo :: Ptr tsoPtr -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,165 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled( + peekStgTSOProfInfo +) where + +#if __GLASGOW_HASKELL__ >= 811 + +-- See [hsc and CPP workaround] + +#define PROFILING + +#include "Rts.h" +#undef BLOCK_SIZE +#undef MBLOCK_SIZE +#undef BLOCKS_PER_MBLOCK +#include "DerivedConstants.h" + +import Data.IntSet (IntSet) +import qualified Data.IntSet as IntSet +import Data.IntMap.Strict (IntMap) +import qualified Data.IntMap.Strict as IntMap +import Data.IORef (IORef, newIORef, readIORef, writeIORef) +import Foreign +import Foreign.C.String +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.Types +import Prelude + +-- Use Int based containers for pointers (addresses) for better performance. +-- These will be queried a lot! +type AddressSet = IntSet +type AddressMap = IntMap + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo tsoPtr = do + cccs_ptr <- peekByteOff tsoPtr cccsOffset + costCenterCacheRef <- newIORef IntMap.empty + cccs' <- peekCostCentreStack IntSet.empty costCenterCacheRef cccs_ptr + + return $ Just StgTSOProfInfo { + cccs = cccs' + } + +cccsOffset :: Int +cccsOffset = (#const OFFSET_StgTSO_cccs) + (#size StgHeader) + +peekCostCentreStack + :: AddressSet + -> IORef (AddressMap CostCentre) + -> Ptr costCentreStack + -> IO (Maybe CostCentreStack) +peekCostCentreStack _ _ ptr | ptr == nullPtr = return Nothing +peekCostCentreStack loopBreakers _ ptr | IntSet.member (ptrToInt ptr) loopBreakers = return Nothing +peekCostCentreStack loopBreakers costCenterCacheRef ptr = do + ccs_ccsID' <- (#peek struct CostCentreStack_, ccsID) ptr + ccs_cc_ptr <- (#peek struct CostCentreStack_, cc) ptr + ccs_cc' <- peekCostCentre costCenterCacheRef ccs_cc_ptr + ccs_prevStack_ptr <- (#peek struct CostCentreStack_, prevStack) ptr + let loopBreakers' = (IntSet.insert ptrAsInt loopBreakers) + ccs_prevStack' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_prevStack_ptr + ccs_indexTable_ptr <- (#peek struct CostCentreStack_, indexTable) ptr + ccs_indexTable' <- peekIndexTable loopBreakers' costCenterCacheRef ccs_indexTable_ptr + ccs_root_ptr <- (#peek struct CostCentreStack_, root) ptr + ccs_root' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_root_ptr + ccs_depth' <- (#peek struct CostCentreStack_, depth) ptr + ccs_scc_count' <- (#peek struct CostCentreStack_, scc_count) ptr + ccs_selected' <- (#peek struct CostCentreStack_, selected) ptr + ccs_time_ticks' <- (#peek struct CostCentreStack_, time_ticks) ptr + ccs_mem_alloc' <- (#peek struct CostCentreStack_, mem_alloc) ptr + ccs_inherited_alloc' <- (#peek struct CostCentreStack_, inherited_alloc) ptr + ccs_inherited_ticks' <- (#peek struct CostCentreStack_, inherited_ticks) ptr + + return $ Just CostCentreStack { + ccs_ccsID = ccs_ccsID', + ccs_cc = ccs_cc', + ccs_prevStack = ccs_prevStack', + ccs_indexTable = ccs_indexTable', + ccs_root = ccs_root', + ccs_depth = ccs_depth', + ccs_scc_count = ccs_scc_count', + ccs_selected = ccs_selected', + ccs_time_ticks = ccs_time_ticks', + ccs_mem_alloc = ccs_mem_alloc', + ccs_inherited_alloc = ccs_inherited_alloc', + ccs_inherited_ticks = ccs_inherited_ticks' + } + where + ptrAsInt = ptrToInt ptr + +peekCostCentre :: IORef (AddressMap CostCentre) -> Ptr costCentre -> IO CostCentre +peekCostCentre costCenterCacheRef ptr = do + costCenterCache <- readIORef costCenterCacheRef + case IntMap.lookup ptrAsInt costCenterCache of + (Just a) -> return a + Nothing -> do + cc_ccID' <- (#peek struct CostCentre_, ccID) ptr + cc_label_ptr <- (#peek struct CostCentre_, label) ptr + cc_label' <- peekCString cc_label_ptr + cc_module_ptr <- (#peek struct CostCentre_, module) ptr + cc_module' <- peekCString cc_module_ptr + cc_srcloc_ptr <- (#peek struct CostCentre_, srcloc) ptr + cc_srcloc' <- do + if cc_srcloc_ptr == nullPtr then + return Nothing + else + fmap Just (peekCString cc_srcloc_ptr) + cc_mem_alloc' <- (#peek struct CostCentre_, mem_alloc) ptr + cc_time_ticks' <- (#peek struct CostCentre_, time_ticks) ptr + cc_is_caf' <- (#peek struct CostCentre_, is_caf) ptr + cc_link_ptr <- (#peek struct CostCentre_, link) ptr + cc_link' <- if cc_link_ptr == nullPtr then + return Nothing + else + fmap Just (peekCostCentre costCenterCacheRef cc_link_ptr) + + let result = CostCentre { + cc_ccID = cc_ccID', + cc_label = cc_label', + cc_module = cc_module', + cc_srcloc = cc_srcloc', + cc_mem_alloc = cc_mem_alloc', + cc_time_ticks = cc_time_ticks', + cc_is_caf = cc_is_caf', + cc_link = cc_link' + } + + writeIORef costCenterCacheRef (IntMap.insert ptrAsInt result costCenterCache) + + return result + where + ptrAsInt = ptrToInt ptr + +peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable) +peekIndexTable _ _ ptr | ptr == nullPtr = return Nothing +peekIndexTable loopBreakers costCenterCacheRef ptr = do + it_cc_ptr <- (#peek struct IndexTable_, cc) ptr + it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr + it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr + it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr + it_next_ptr <- (#peek struct IndexTable_, next) ptr + it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr + it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr + + return $ Just IndexTable { + it_cc = it_cc', + it_ccs = it_ccs', + it_next = it_next', + it_back_edge = it_back_edge' + } + +-- | casts a @Ptr@ to an @Int@ +ptrToInt :: Ptr a -> Int +ptrToInt (Ptr a##) = I## (addr2Int## a##) + +#else +import Prelude +import Foreign + +import GHC.Exts.Heap.ProfInfo.Types + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs ===================================== @@ -0,0 +1,56 @@ +{-# LANGUAGE DeriveGeneric #-} + +module GHC.Exts.Heap.ProfInfo.Types where + +import Prelude +import Data.Word +import GHC.Generics + +-- | This is a somewhat faithful representation of StgTSOProfInfo. See +-- +-- for more details on this data structure. +data StgTSOProfInfo = StgTSOProfInfo { + cccs :: Maybe CostCentreStack +} deriving (Show, Generic) + +-- | This is a somewhat faithful representation of CostCentreStack. See +-- +-- for more details on this data structure. +data CostCentreStack = CostCentreStack { + ccs_ccsID :: Int, + ccs_cc :: CostCentre, + ccs_prevStack :: Maybe CostCentreStack, + ccs_indexTable :: Maybe IndexTable, + ccs_root :: Maybe CostCentreStack, + ccs_depth :: Word, + ccs_scc_count :: Word64, + ccs_selected :: Word, + ccs_time_ticks :: Word, + ccs_mem_alloc :: Word64, + ccs_inherited_alloc :: Word64, + ccs_inherited_ticks :: Word +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of CostCentre. See +-- +-- for more details on this data structure. +data CostCentre = CostCentre { + cc_ccID :: Int, + cc_label :: String, + cc_module :: String, + cc_srcloc :: Maybe String, + cc_mem_alloc :: Word64, + cc_time_ticks :: Word, + cc_is_caf :: Bool, + cc_link :: Maybe CostCentre +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of IndexTable. See +-- +-- for more details on this data structure. +data IndexTable = IndexTable { + it_cc :: CostCentre, + it_ccs :: Maybe CostCentreStack, + it_next :: Maybe IndexTable, + it_back_edge :: Bool +} deriving (Show, Generic, Eq) ===================================== libraries/ghc-heap/ghc-heap.cabal.in ===================================== @@ -25,6 +25,7 @@ library build-depends: base >= 4.9.0 && < 5.0 , ghc-prim > 0.2 && < 0.8 , rts == 1.0.* + , containers >= 0.6.2.1 && < 0.7 ghc-options: -Wall cmm-sources: cbits/HeapPrim.cmm @@ -39,3 +40,10 @@ library GHC.Exts.Heap.InfoTable.Types GHC.Exts.Heap.InfoTableProf GHC.Exts.Heap.Utils + GHC.Exts.Heap.FFIClosures + GHC.Exts.Heap.FFIClosures_ProfilingDisabled + GHC.Exts.Heap.FFIClosures_ProfilingEnabled + GHC.Exts.Heap.ProfInfo.Types + GHC.Exts.Heap.ProfInfo.PeekProfInfo + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled ===================================== libraries/ghc-heap/tests/TestUtils.hs ===================================== @@ -0,0 +1,7 @@ +{-# LANGUAGE MagicHash #-} +module TestUtils where + +assertEqual :: (Show a, Eq a) => a -> a -> IO () +assertEqual a b + | a /= b = error (show a ++ " /= " ++ show b) + | otherwise = return () ===================================== libraries/ghc-heap/tests/all.T ===================================== @@ -36,3 +36,18 @@ test('closure_size_noopt', ], compile_and_run, ['']) +test('tso_and_stack_closures', + [extra_files(['create_tso.c','create_tso.h','TestUtils.hs']), + only_ways(['profthreaded']), + ignore_stdout, + ignore_stderr + ], + multi_compile_and_run, ['tso_and_stack_closures', [('create_tso.c','')], '']) + +test('parse_tso_flags', + [extra_files(['TestUtils.hs']), + only_ways(['normal']), + ignore_stdout, + ignore_stderr + ], + compile_and_run, ['']) ===================================== libraries/ghc-heap/tests/create_tso.c ===================================== @@ -0,0 +1,82 @@ +#include "Rts.h" +#include "RtsAPI.h" + +// Assumes the rts is paused +void unpack_closure + ( StgClosure * inClosure + , const StgInfoTable ** outInfoTablePtr + , int * outHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outHeapRep // Array of words + , int * outPointersSize // Size of outPointers (in words) + , StgClosure *** outPointers // Array of all pointers of the TSO + ) +{ + *outInfoTablePtr = get_itbl(inClosure); + + // Copy TSO pointers. + StgWord closureSizeW = heap_view_closureSize(inClosure); + int closureSizeB = sizeof(StgWord) * closureSizeW; + StgClosure ** pointers = malloc(closureSizeB); + *outPointersSize = collect_pointers(inClosure, closureSizeW, pointers); + *outPointers = pointers; + + // Copy the heap rep. + StgWord * heapRep = malloc(closureSizeB); + for (int i = 0; i < closureSizeW; i++) + { + heapRep[i] = ((StgWord*)inClosure)[i]; + } + + *outHeapRepSize = closureSizeB; + *outHeapRep = heapRep; +} + +// Must be called from a safe FFI call. +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ) +{ + // Pause RTS + PauseToken * token = rts_pause(); + Capability * cap = pauseTokenCapability(token); + + // Create TSO/Stack + HaskellObj trueClosure = rts_mkBool(cap, 1); + *outTso = createGenThread(cap, 500U, trueClosure); + + // Unpack TSO + unpack_closure( + (StgClosure*)(*outTso), + outTsoInfoTablePtr, + outTsoHeapRepSize, + outTsoHeapRep, + outTsoPointersSize, + outTsoPointers); + + // Unpack STACK + StgClosure * outStackAsClosure = (*outTsoPointers)[2]; + *outStack = (StgTSO *)outStackAsClosure; + unpack_closure( + outStackAsClosure, + outStackInfoTablePtr, + outStackHeapRepSize, + outStackHeapRep, + outStackPointersSize, + outStackPointers); + + // Resume RTS + rts_resume(token); +} ===================================== libraries/ghc-heap/tests/create_tso.h ===================================== @@ -0,0 +1,19 @@ +#include "Rts.h" +#include "RtsAPI.h" + +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ); ===================================== libraries/ghc-heap/tests/parse_tso_flags.hs ===================================== @@ -0,0 +1,17 @@ +import GHC.Exts.Heap.Closures +import GHC.Exts.Heap.FFIClosures +import TestUtils + +main :: IO() +main = do + assertEqual (parseTsoFlags 0) [] + assertEqual (parseTsoFlags 1) [TsoFlagsUnknownValue 1] + assertEqual (parseTsoFlags 2) [TsoLocked] + assertEqual (parseTsoFlags 4) [TsoBlockx] + assertEqual (parseTsoFlags 8) [TsoInterruptible] + assertEqual (parseTsoFlags 16) [TsoStoppedOnBreakpoint] + assertEqual (parseTsoFlags 64) [TsoMarked] + assertEqual (parseTsoFlags 128) [TsoSqueezed] + assertEqual (parseTsoFlags 256) [TsoAllocLimit] + + assertEqual (parseTsoFlags 6) [TsoLocked, TsoBlockx] ===================================== libraries/ghc-heap/tests/tso_and_stack_closures.hs ===================================== @@ -0,0 +1,167 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} + +import Control.Monad (forM_, unless) +import Data.List (find) +import Data.Word +import Foreign +import Foreign.C.Types +import GHC.IO ( IO(..) ) +import GHC.Exts +import GHC.Exts.Heap +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures +import GHC.Word + +import TestUtils + +main :: IO () +main = do + (tso, stack) <- {-# SCC "MyCostCentre" #-} createAndUnpackTSOAndSTACKClosure + assertEqual (getClosureType tso) TSO + assertEqual (what_next tso) ThreadRunGHC + assertEqual (why_blocked tso) NotBlocked + assertEqual (saved_errno tso) 0 + forM_ (flags tso) $ \flag -> case flag of + TsoFlagsUnknownValue _ -> error $ "Unknown flag: " ++ show flag + _ | flag `elem` + [ TsoLocked + , TsoBlockx + , TsoStoppedOnBreakpoint + , TsoSqueezed + ] -> error $ "Unexpected flag: " ++ show flag + _ -> return () + + assertEqual (getClosureType stack) STACK + +#if defined(PROFILING) + let costCentre = ccs_cc <$> (cccs =<< prof tso) + case costCentre of + Nothing -> error $ "No CostCentre found in TSO: " ++ show tso + Just _ -> case findMyCostCentre (linkedCostCentres costCentre) of + Just myCostCentre -> do + assertEqual (cc_label myCostCentre) "MyCostCentre" + assertEqual (cc_module myCostCentre) "Main" + assertEqual (cc_srcloc myCostCentre) (Just "tso_and_stack_closures.hs:23:48-80") + assertEqual (cc_is_caf myCostCentre) False + Nothing -> error $ "MyCostCentre not found in:\n" ++ unlines (cc_label <$> linkedCostCentres costCentre) +#endif + +linkedCostCentres :: Maybe CostCentre -> [CostCentre] +linkedCostCentres Nothing = [] +linkedCostCentres (Just cc) = cc : linkedCostCentres (cc_link cc) + +findMyCostCentre:: [CostCentre] -> Maybe CostCentre +findMyCostCentre ccs = find (\cc -> cc_label cc == "MyCostCentre") ccs + +getClosureType :: GenClosure b -> ClosureType +getClosureType = tipe . info + +type StgTso = Any +type StgStack = Any +data MBA a = MBA (MutableByteArray# a) +data BA = BA ByteArray# + +foreign import ccall safe "create_tso.h create_and_unpack_tso_and_stack" + c_create_and_unpack_tso_and_stack + :: Ptr (Ptr StgTso) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> Ptr (Ptr StgStack) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> IO () + +createAndUnpackTSOAndSTACKClosure + :: IO ( GenClosure (Ptr Any) + , GenClosure (Ptr Any) + ) +createAndUnpackTSOAndSTACKClosure = do + + alloca $ \ptrPtrTso -> do + alloca $ \ptrPtrTsoInfoTable -> do + alloca $ \ptrTsoHeapRepSize -> do + alloca $ \ptrPtrTsoHeapRep -> do + alloca $ \ptrTsoPointersSize -> do + alloca $ \ptrPtrPtrTsoPointers -> do + + alloca $ \ptrPtrStack -> do + alloca $ \ptrPtrStackInfoTable -> do + alloca $ \ptrStackHeapRepSize -> do + alloca $ \ptrPtrStackHeapRep -> do + alloca $ \ptrStackPointersSize -> do + alloca $ \ptrPtrPtrStackPointers -> do + + c_create_and_unpack_tso_and_stack + + ptrPtrTso + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + ptrPtrStack + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + let fromHeapRep + ptrPtrClosureInfoTable + ptrClosureHeapRepSize + ptrPtrClosureHeapRep + ptrClosurePointersSize + ptrPtrPtrClosurePointers = do + ptrInfoTable :: Ptr StgInfoTable <- peek ptrPtrClosureInfoTable + + heapRepSize :: Int <- fromIntegral <$> peek ptrClosureHeapRepSize + let I# heapRepSize# = heapRepSize + ptrHeapRep :: Ptr Word8 <- peek ptrPtrClosureHeapRep + MBA mutHeapRepBA <- IO $ \s -> let + (# s', mba# #) = newByteArray# heapRepSize# s + in (# s', MBA mba# #) + forM_ [0..heapRepSize-1] $ \i@(I# i#) -> do + W8# w <- peekElemOff ptrHeapRep i + IO (\s -> (# writeWord8Array# mutHeapRepBA i# (extendWord8# w) s, () #)) + BA heapRep <- IO $ \s -> let + (# s', ba# #) = unsafeFreezeByteArray# mutHeapRepBA s + in (# s', BA ba# #) + + pointersSize :: Int <- fromIntegral <$> peek ptrClosurePointersSize + ptrPtrPointers :: Ptr (Ptr Any) <- peek ptrPtrPtrClosurePointers + ptrPtrPointers :: [Ptr Any] <- sequence + [ peekElemOff ptrPtrPointers i + | i <- [0..pointersSize-1] + ] + + getClosureDataFromHeapRep + heapRep + ptrInfoTable + ptrPtrPointers + + tso <- fromHeapRep + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + stack <- fromHeapRep + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + return (tso, stack) ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables, - GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards #-} + GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards, + CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-} -- | @@ -29,7 +30,7 @@ import GHCi.TH.Binary () -- For Binary instances import GHCi.BreakArray import GHC.LanguageExtensions -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.ForeignSrcLang import GHC.Fingerprint import Control.Concurrent @@ -110,7 +111,7 @@ data Message a where -> Int -- constr tag -> Int -- pointer tag -> ByteString -- constructor desccription - -> Message (RemotePtr StgInfoTable) + -> Message (RemotePtr Heap.StgInfoTable) -- | Evaluate a statement EvalStmt @@ -211,7 +212,7 @@ data Message a where -- type reconstruction. GetClosure :: HValueRef - -> Message (GenClosure HValueRef) + -> Message (Heap.GenClosure HValueRef) -- | Evaluate something. This is used to support :force in GHCi. Seq @@ -449,10 +450,20 @@ instance Binary (FunPtr a) where get = castPtrToFunPtr <$> get -- Binary instances to support the GetClosure message -instance Binary StgInfoTable -instance Binary ClosureType -instance Binary PrimType -instance Binary a => Binary (GenClosure a) +#if MIN_VERSION_ghc_heap(8,11,0) +instance Binary Heap.StgTSOProfInfo +instance Binary Heap.CostCentreStack +instance Binary Heap.CostCentre +instance Binary Heap.IndexTable +instance Binary Heap.WhatNext +instance Binary Heap.WhyBlocked +instance Binary Heap.TsoFlags +#endif + +instance Binary Heap.StgInfoTable +instance Binary Heap.ClosureType +instance Binary Heap.PrimType +instance Binary a => Binary (Heap.GenClosure a) data Msg = forall a . (Binary a, Show a) => Msg (Message a) ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -32,7 +32,7 @@ import Data.Binary.Get import Data.ByteString (ByteString) import qualified Data.ByteString.Unsafe as B import GHC.Exts -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack import Foreign hiding (void) import Foreign.C @@ -93,8 +93,8 @@ run m = case m of toRemotePtr <$> mkConInfoTable tc ptrs nptrs tag ptrtag desc StartTH -> startTH GetClosure ref -> do - clos <- getClosureData =<< localRef ref - mapM (\(Box x) -> mkRemoteRef (HValue x)) clos + clos <- Heap.getClosureData =<< localRef ref + mapM (\(Heap.Box x) -> mkRemoteRef (HValue x)) clos Seq ref -> doSeq ref ResumeSeq ref -> resumeSeq ref _other -> error "GHCi.Run.run" ===================================== rts/Heap.c ===================================== @@ -203,7 +203,26 @@ StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[siz ptrs[nptrs++] = (StgClosure *)((StgMVar *)closure)->tail; ptrs[nptrs++] = ((StgMVar *)closure)->value; break; + case TSO: + ASSERT((StgClosure *)((StgTSO *)closure)->_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->_link; + ASSERT((StgClosure *)((StgTSO *)closure)->global_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->global_link; + + ASSERT((StgClosure *)((StgTSO *)closure)->stackobj != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->stackobj; + + ASSERT((StgClosure *)((StgTSO *)closure)->trec != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->trec; + + ASSERT((StgClosure *)((StgTSO *)closure)->blocked_exceptions != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->blocked_exceptions; + + ASSERT((StgClosure *)((StgTSO *)closure)->bq != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->bq; + + break; case WEAK: ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->cfinalizers; ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->key; ===================================== rts/PrimOps.cmm ===================================== @@ -2371,11 +2371,11 @@ stg_unpackClosurezh ( P_ closure ) clos = UNTAG(closure); W_ len; - // The array returned is the raw data for the entire closure. + // The array returned, dat_arr, is the raw data for the entire closure. // The length is variable based upon the closure type, ptrs, and non-ptrs (len) = foreign "C" heap_view_closureSize(clos "ptr"); - W_ ptrs_arr_sz, ptrs_arr_cards, dat_arr_sz; + W_ dat_arr_sz; dat_arr_sz = SIZEOF_StgArrBytes + WDS(len); ("ptr" dat_arr) = ccall allocateMightFail(MyCapability() "ptr", BYTES_TO_WDS(dat_arr_sz)); @@ -2396,7 +2396,7 @@ for: W_ ptrArray; - // Follow the pointers + // Collect pointers. ("ptr" ptrArray) = foreign "C" heap_view_closurePtrs(MyCapability() "ptr", clos "ptr"); return (info, dat_arr, ptrArray); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb4fc4d48b81897e153e9e9fd5ab7aa1cb86527a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb4fc4d48b81897e153e9e9fd5ab7aa1cb86527a 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 Nov 26 17:47:44 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Thu, 26 Nov 2020 12:47:44 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 4 commits: Move core flattening algorithm to Core.Unify Message-ID: <5fbfea40973dd_86c1573a414410273@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: d43eeeac by Richard Eisenberg at 2020-11-26T12:45:11-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into GHC.Core.Map.Type and GHC.Core.Map.Expr, in order to avoid module import cycles with GHC.Core. - - - - - cdeabd19 by Richard Eisenberg at 2020-11-26T12:45:12-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - 22bdbb4a by Richard Eisenberg at 2020-11-26T12:46:35-05:00 Remove flattening variables This patch redesigns the flattener to simplify type family applications directly instead of using flattening meta-variables and skolems. The key new innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS is either a type variable or exactly-saturated type family application; either can now be rewritten using a CEqCan constraint in the inert set. Because the flattener no longer reduces all type family applications to variables, there was some performance degradation if a lengthy type family application is now flattened over and over (not making progress). To compensate, this patch contains some extra optimizations in the flattener, leading to a number of performance improvements. Close #18875. Close #18910. There are many extra parts of the compiler that had to be affected in writing this patch: * The family-application cache (formerly the flat-cache) sometimes stores coercions built from Given inerts. When these inerts get kicked out, we must kick out from the cache as well. (This was, I believe, true previously, but somehow never caused trouble.) Kicking out from the cache requires adding a filterTM function to TrieMap. * This patch obviates the need to distinguish "blocking" coercion holes from non-blocking ones (which, previously, arose from CFunEqCans). There is thus some simplification around coercion holes. * Extra commentary throughout parts of the code I read through, to preserve the knowledge I gained while working. * A change in the pure unifier around unifying skolems with other types. Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented in Note [Binding when looking up instances] in GHC.Core.InstEnv. * Some more use of MCoercion where appropriate. * Previously, class-instance lookup automatically noticed that e.g. C Int was a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to a variable. Now, a little more care must be taken around checking for unifying instances. * Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly, because (=>) is not a tycon in Haskell. Fixed now, but there are some knock-on changes in e.g. TrieMap code and in the canonicaliser. * New function anyFreeVarsOf{Type,Co} to check whether a free variable satisfies a certain predicate. * Type synonyms now remember whether or not they are "forgetful"; a forgetful synonym drops at least one argument. This is useful when flattening; see flattenView. * The pattern-match completeness checker invokes the solver. This invocation might need to look through newtypes when checking representational equality. Thus, the desugarer needs to keep track of the in-scope variables to know what newtype constructors are in scope. I bet this bug was around before but never noticed. * Extra-constraints wildcards are no longer simplified before printing. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. * Whether or not there are Given equalities has become slightly subtler. See the new HasGivenEqs datatype. * Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical explains a significant new wrinkle in the new approach. * See Note [What might match later?] in GHC.Tc.Solver.Interact, which explains the fix to #18910. Though I (Richard) did the implementation, Simon PJ was very involved in design and review. This updates the Haddock submodule to avoid #18932 by adding a type signature. ------------------------- Metric Decrease: T12227 T5030 T9872a T9872b T9872c Metric Increase: T9872d ------------------------- - - - - - cbdf6734 by Richard Eisenberg at 2020-11-26T12:47:30-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - 30 changed files: - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - + compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map.hs → compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Ext/Utils.hs - compiler/GHC/Stg/CSE.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Gen/Bind.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/faad5f02b2728c022c69d930679cee16707956ad...cbdf67348305ec61714e974a1e8980a2be0947af -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/faad5f02b2728c022c69d930679cee16707956ad...cbdf67348305ec61714e974a1e8980a2be0947af 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 Nov 26 17:58:52 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Thu, 26 Nov 2020 12:58:52 -0500 Subject: [Git][ghc/ghc][wip/T17656] 319 commits: Add test for T18574 Message-ID: <5fbfecdc47a7c_86c3fc6ab4f115c4180f7@gitlab.mail> Simon Peyton Jones pushed to branch wip/T17656 at Glasgow Haskell Compiler / GHC Commits: 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - d43eeeac by Richard Eisenberg at 2020-11-26T12:45:11-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into GHC.Core.Map.Type and GHC.Core.Map.Expr, in order to avoid module import cycles with GHC.Core. - - - - - cdeabd19 by Richard Eisenberg at 2020-11-26T12:45:12-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - 22bdbb4a by Richard Eisenberg at 2020-11-26T12:46:35-05:00 Remove flattening variables This patch redesigns the flattener to simplify type family applications directly instead of using flattening meta-variables and skolems. The key new innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS is either a type variable or exactly-saturated type family application; either can now be rewritten using a CEqCan constraint in the inert set. Because the flattener no longer reduces all type family applications to variables, there was some performance degradation if a lengthy type family application is now flattened over and over (not making progress). To compensate, this patch contains some extra optimizations in the flattener, leading to a number of performance improvements. Close #18875. Close #18910. There are many extra parts of the compiler that had to be affected in writing this patch: * The family-application cache (formerly the flat-cache) sometimes stores coercions built from Given inerts. When these inerts get kicked out, we must kick out from the cache as well. (This was, I believe, true previously, but somehow never caused trouble.) Kicking out from the cache requires adding a filterTM function to TrieMap. * This patch obviates the need to distinguish "blocking" coercion holes from non-blocking ones (which, previously, arose from CFunEqCans). There is thus some simplification around coercion holes. * Extra commentary throughout parts of the code I read through, to preserve the knowledge I gained while working. * A change in the pure unifier around unifying skolems with other types. Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented in Note [Binding when looking up instances] in GHC.Core.InstEnv. * Some more use of MCoercion where appropriate. * Previously, class-instance lookup automatically noticed that e.g. C Int was a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to a variable. Now, a little more care must be taken around checking for unifying instances. * Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly, because (=>) is not a tycon in Haskell. Fixed now, but there are some knock-on changes in e.g. TrieMap code and in the canonicaliser. * New function anyFreeVarsOf{Type,Co} to check whether a free variable satisfies a certain predicate. * Type synonyms now remember whether or not they are "forgetful"; a forgetful synonym drops at least one argument. This is useful when flattening; see flattenView. * The pattern-match completeness checker invokes the solver. This invocation might need to look through newtypes when checking representational equality. Thus, the desugarer needs to keep track of the in-scope variables to know what newtype constructors are in scope. I bet this bug was around before but never noticed. * Extra-constraints wildcards are no longer simplified before printing. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. * Whether or not there are Given equalities has become slightly subtler. See the new HasGivenEqs datatype. * Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical explains a significant new wrinkle in the new approach. * See Note [What might match later?] in GHC.Tc.Solver.Interact, which explains the fix to #18910. Though I (Richard) did the implementation, Simon PJ was very involved in design and review. This updates the Haddock submodule to avoid #18932 by adding a type signature. ------------------------- Metric Decrease: T12227 T5030 T9872a T9872b T9872c Metric Increase: T9872d ------------------------- - - - - - cbdf6734 by Richard Eisenberg at 2020-11-26T12:47:30-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - dc29ee24 by Simon Peyton Jones at 2020-11-26T17:55:39+00:00 Kill floatEqualities This WIP patch over-delivers on #17656. I say "over-delivers" because instead of improving floatEqualities, it kills it off entirely. Instead we use level numbers. There is plenty of dead code to delete, and Notes to write, but for now this a proof of concept, to enable code review. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lexer.x The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a00b2fdd651151ad6e90d374de3b27d5e44e62c...dc29ee245d5a52dc785e9e3ad5d5728d0b79061a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2a00b2fdd651151ad6e90d374de3b27d5e44e62c...dc29ee245d5a52dc785e9e3ad5d5728d0b79061a 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 Nov 26 21:00:43 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 26 Nov 2020 16:00:43 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc0177bbf3b8_86c111d4a004433f6@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62b56d3358bf12cf364474aa4b5dc27cc973a01f...3e3555cc9c2a9f5246895f151259fd2a81621f38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62b56d3358bf12cf364474aa4b5dc27cc973a01f...3e3555cc9c2a9f5246895f151259fd2a81621f38 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 Nov 26 21:01:20 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 16:01:20 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/hugepages Message-ID: <5fc017a027387_86c11450e28452135@gitlab.mail> Ben Gamari pushed new branch wip/hugepages at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/hugepages 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 Nov 26 21:10:50 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 16:10:50 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/nonmoving-fixes Message-ID: <5fc019dac2bb2_86c879fa9c460029@gitlab.mail> Ben Gamari pushed new branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/nonmoving-fixes 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 Nov 26 21:12:56 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 16:12:56 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 40 commits: Add Addr# atomic primops (#17751) Message-ID: <5fc01a585431_86c111d4a00460241@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 91f4b8c6 by GHC GitLab CI at 2020-11-26T16:12:18-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - b62f3a1a by GHC GitLab CI at 2020-11-26T16:12:18-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 037db8f4 by GHC GitLab CI at 2020-11-26T16:12:18-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 44b1967b by GHC GitLab CI at 2020-11-26T16:12:18-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 0ec5a2b0 by GHC GitLab CI at 2020-11-26T16:12:19-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 93dab503 by GHC GitLab CI at 2020-11-26T16:12:19-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - e8c0248a by GHC GitLab CI at 2020-11-26T16:12:19-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 7396146e by GHC GitLab CI at 2020-11-26T16:12:19-05:00 nonmoving: Ensure that evacuated large objects are marked When evacuating a large objects we n - - - - - 4e41516e by Ben Gamari at 2020-11-26T16:12:19-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64258061375715ab8ddad879871b133317130608...4e41516e3a9d89ac3e7e40cbaa0d82cdcd4deaf3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64258061375715ab8ddad879871b133317130608...4e41516e3a9d89ac3e7e40cbaa0d82cdcd4deaf3 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 Nov 26 21:29:36 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 16:29:36 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 9 commits: ThreadPaused: Don't zero slop until free vars are pushed Message-ID: <5fc01e404d805_86c879fa9c46347e@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: feaadbf8 by Ben Gamari at 2020-11-26T16:28:50-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - fb124a30 by Ben Gamari at 2020-11-26T16:28:55-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 076f8045 by Ben Gamari at 2020-11-26T16:28:59-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 5196edf8 by Ben Gamari at 2020-11-26T16:29:02-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - cd3c98b8 by Ben Gamari at 2020-11-26T16:29:05-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 32483eb7 by Ben Gamari at 2020-11-26T16:29:08-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - becf7013 by Ben Gamari at 2020-11-26T16:29:12-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - cc002412 by Ben Gamari at 2020-11-26T16:29:17-05:00 nonmoving: Ensure that evacuated large objects are marked When evacuating a large objects we n - - - - - e151c961 by Ben Gamari at 2020-11-26T16:29:20-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 11 changed files: - includes/rts/storage/ClosureMacros.h - rts/Messages.c - rts/Messages.h - rts/PrimOps.cmm - rts/RaiseAsync.c - rts/ThreadPaused.c - rts/Updates.h - rts/posix/OSThreads.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/NonMoving.c Changes: ===================================== includes/rts/storage/ClosureMacros.h ===================================== @@ -520,11 +520,15 @@ INLINE_HEADER StgWord8 *mutArrPtrsCard (StgMutArrPtrs *a, W_ n) #if defined(PROFILING) || defined(DEBUG) #define OVERWRITING_CLOSURE(c) \ overwritingClosure(c) +#define OVERWRITING_CLOSURE_SIZE(c, size) \ + overwritingClosureSize(c, size) #define OVERWRITING_CLOSURE_MUTABLE(c, off) \ overwritingMutableClosureOfs(c, off) #else #define OVERWRITING_CLOSURE(c) \ do { (void) sizeof(c); } while(0) +#define OVERWRITING_CLOSURE_SIZE(c, size) \ + do { (void) sizeof(c); (void) sizeof(size); } while(0) #define OVERWRITING_CLOSURE_MUTABLE(c, off) \ do { (void) sizeof(c); (void) sizeof(off); } while(0) #endif ===================================== rts/Messages.c ===================================== @@ -97,7 +97,7 @@ loop: case THROWTO_SUCCESS: { // this message is done StgTSO *source = t->source; - doneWithMsgThrowTo(t); + doneWithMsgThrowTo(cap, t); tryWakeupThread(cap, source); break; } ===================================== rts/Messages.h ===================================== @@ -23,8 +23,15 @@ void sendMessage (Capability *from_cap, Capability *to_cap, Message *msg); #include "SMPClosureOps.h" INLINE_HEADER void -doneWithMsgThrowTo (MessageThrowTo *m) +doneWithMsgThrowTo (Capability *cap, MessageThrowTo *m) { + ASSERT(m->header.info == &stg_MSG_THROWTO_info); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + updateRemembSetPushClosure(cap, (StgClosure *) m->link); + updateRemembSetPushClosure(cap, (StgClosure *) m->source); + updateRemembSetPushClosure(cap, (StgClosure *) m->target); + updateRemembSetPushClosure(cap, (StgClosure *) m->exception); + } OVERWRITING_CLOSURE((StgClosure*)m); unlockClosure((StgClosure*)m, &stg_MSG_NULL_info); LDV_RECORD_CREATE(m); ===================================== rts/PrimOps.cmm ===================================== @@ -227,6 +227,21 @@ stg_shrinkSmallMutableArrayzh ( gcptr mba, W_ new_size ) { ASSERT(new_size <= StgSmallMutArrPtrs_ptrs(mba)); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + // Ensure that the elements we are about to shrink out of existence + // remain visible to the non-moving collector. + W_ p, end; + p = mba + SIZEOF_StgSmallMutArrPtrs + WDS(new_size); + end = mba + SIZEOF_StgSmallMutArrPtrs + WDS(StgSmallMutArrPtrs_ptrs(mba)); +again: + ccall updateRemembSetPushClosure_(BaseReg "ptr", + W_[p] "ptr"); + if (p < end) { + p = p + SIZEOF_W; + goto again; + } + } + OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) + new_size)); StgSmallMutArrPtrs_ptrs(mba) = new_size; ===================================== rts/RaiseAsync.c ===================================== @@ -336,7 +336,7 @@ check_target: } // nobody else can wake up this TSO after we claim the message - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); raiseAsync(cap, target, msg->exception, false, NULL); return THROWTO_SUCCESS; @@ -580,7 +580,7 @@ maybePerformBlockedException (Capability *cap, StgTSO *tso) throwToSingleThreaded(cap, msg->target, msg->exception); source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); return 1; } @@ -602,7 +602,7 @@ awakenBlockedExceptionQueue (Capability *cap, StgTSO *tso) i = lockClosure((StgClosure *)msg); if (i != &stg_MSG_NULL_info) { source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); } else { unlockClosure((StgClosure *)msg,i); @@ -700,7 +700,7 @@ removeFromQueues(Capability *cap, StgTSO *tso) // ASSERT(m->header.info == &stg_WHITEHOLE_info); // unlock and revoke it at the same time - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); break; } ===================================== rts/ThreadPaused.c ===================================== @@ -314,10 +314,6 @@ threadPaused(Capability *cap, StgTSO *tso) continue; } - // zero out the slop so that the sanity checker can tell - // where the next closure is. - OVERWRITING_CLOSURE(bh); - // an EAGER_BLACKHOLE or CAF_BLACKHOLE gets turned into a // BLACKHOLE here. #if defined(THREADED_RTS) @@ -345,11 +341,16 @@ threadPaused(Capability *cap, StgTSO *tso) // overwrite to the update remembered set. // N.B. We caught the WHITEHOLE case above. updateRemembSetPushThunkEager(cap, - THUNK_INFO_PTR_TO_STRUCT(bh_info), - (StgThunk *) bh); + THUNK_INFO_PTR_TO_STRUCT(bh_info), + (StgThunk *) bh); } } + // zero out the slop so that the sanity checker can tell + // where the next closure is. N.B. We mustn't do this until we have + // pushed the free variables to the update remembered set above. + OVERWRITING_CLOSURE_SIZE(bh, closure_sizeW_(bh, INFO_PTR_TO_STRUCT(bh_info))); + // The payload of the BLACKHOLE points to the TSO RELAXED_STORE(&((StgInd *)bh)->indirectee, (StgClosure *)tso); SET_INFO_RELEASE(bh,&stg_BLACKHOLE_info); ===================================== rts/Updates.h ===================================== @@ -49,7 +49,6 @@ W_ bd; \ \ prim_write_barrier; \ - OVERWRITING_CLOSURE(p1); \ bd = Bdescr(p1); \ if (bdescr_gen_no(bd) != 0 :: bits16) { \ IF_NONMOVING_WRITE_BARRIER_ENABLED { \ @@ -60,6 +59,7 @@ } else { \ TICK_UPD_NEW_IND(); \ } \ + OVERWRITING_CLOSURE(p1); \ StgInd_indirectee(p1) = p2; \ prim_write_barrier; \ SET_INFO(p1, stg_BLACKHOLE_info); \ ===================================== rts/posix/OSThreads.c ===================================== @@ -401,8 +401,9 @@ interruptOSThread (OSThreadId id) void joinOSThread (OSThreadId id) { - if (pthread_join(id, NULL) != 0) { - sysErrorBelch("joinOSThread: error %d", errno); + int ret = pthread_join(id, NULL); + if (ret != 0) { + sysErrorBelch("joinOSThread: error %d", ret); } } ===================================== rts/sm/Evac.c ===================================== @@ -505,6 +505,7 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -694,7 +695,9 @@ loop: // We may have evacuated the block to the nonmoving generation. If so // we need to make sure it is added to the mark queue since the only // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { + // + // N.B. evaculate_large might have set BF_NONMOVING. + if (major_gc && bd->flags & BF_NONMOVING && !deadlock_detect_gc) { markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); } return; @@ -1014,6 +1017,10 @@ evacuate_BLACKHOLE(StgClosure **p) // See #14497. if (flags & BF_LARGE) { evacuate_large((P_)q); + // N.B. evacuate_large might have evacuated to the non-moving + // generation. + if (bd->flags & BF_NONMOVING) + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); return; } if (flags & BF_EVACUATED) { ===================================== rts/sm/GC.c ===================================== @@ -1701,13 +1701,8 @@ collect_gct_blocks (void) static void collect_pinned_object_blocks (void) { - generation *gen; const bool use_nonmoving = RtsFlags.GcFlags.useNonmoving; - if (use_nonmoving && major_gc) { - gen = oldest_gen; - } else { - gen = g0; - } + generation *const gen = (use_nonmoving && major_gc) ? oldest_gen : g0; for (uint32_t n = 0; n < n_capabilities; n++) { bdescr *last = NULL; @@ -1732,7 +1727,7 @@ collect_pinned_object_blocks (void) if (gen->large_objects != NULL) { gen->large_objects->u.back = last; } - g0->large_objects = RELAXED_LOAD(&capabilities[n]->pinned_object_blocks); + gen->large_objects = RELAXED_LOAD(&capabilities[n]->pinned_object_blocks); RELAXED_STORE(&capabilities[n]->pinned_object_blocks, NULL); } } ===================================== rts/sm/NonMoving.c ===================================== @@ -191,8 +191,8 @@ Mutex concurrent_coll_finished_lock; * === Other references === * * Apart from the design document in docs/storage/nonmoving-gc and the Ueno - * 2016 paper (TODO citation) from which it drew inspiration, there are a - * variety of other relevant Notes scattered throughout the tree: + * 2016 paper [ueno 2016] from which it drew inspiration, there are a variety + * of other relevant Notes scattered throughout the tree: * * - Note [Concurrent non-moving collection] (NonMoving.c) describes * concurrency control of the nonmoving collector @@ -232,6 +232,11 @@ Mutex concurrent_coll_finished_lock; * how we use the DIRTY flags associated with MUT_VARs and TVARs to improve * barrier efficiency. * + * [ueno 2016]: + * Katsuhiro Ueno and Atsushi Ohori. 2016. A fully concurrent garbage + * collector for functional programs on multicore processors. SIGPLAN Not. 51, + * 9 (September 2016), 421–433. DOI:https://doi.org/10.1145/3022670.2951944 + * * * Note [Concurrent non-moving collection] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -726,7 +731,6 @@ void nonmovingStop(void) "waiting for nonmoving collector thread to terminate"); ACQUIRE_LOCK(&concurrent_coll_finished_lock); waitCondition(&concurrent_coll_finished, &concurrent_coll_finished_lock); - joinOSThread(mark_thread); } #endif } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e41516e3a9d89ac3e7e40cbaa0d82cdcd4deaf3...e151c961266e3b4fdc966918f2cbde9aa657436a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e41516e3a9d89ac3e7e40cbaa0d82cdcd4deaf3...e151c961266e3b4fdc966918f2cbde9aa657436a 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 Nov 26 23:16:18 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 18:16:18 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 19 commits: Fix haddock parse error Message-ID: <5fc0374227b90_86cfd752bc4676a4@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: faa95a99 by Matthew Pickering at 2020-11-18T13:42:30+00:00 Fix haddock parse error - - - - - 4addeede by Matthew Pickering at 2020-11-18T16:24:25+00:00 Revert "Remove GHC.Types.Unique.Map module" This reverts commit 1c7c6f1afc8e7f7ba5d256780bc9d5bb5f3e7601. - - - - - ff1846e0 by Matthew Pickering at 2020-11-23T10:42:39+00:00 Profiling by info table mode (-hi) This profiling mode creates bands by the address of the info table for each closure. This provides a much more fine-grained profiling output than any of the other profiling modes. The `-hi` profiling mode does not require a profiling build. - - - - - 4e2fe44f by Matthew Pickering at 2020-11-23T11:18:16+00:00 Add -finfo-table-map which maps info tables to source positions This new flag embeds a lookup table from the address of an info table to information about that info table. The main interface for consulting the map is the `lookupIPE` C function > InfoProvEnt * lookupIPE(StgInfoTable *info) The `InfoProvEnt` has the following structure: > typedef struct InfoProv_{ > char * table_name; > char * closure_desc; > char * ty_desc; > char * label; > char * module; > char * srcloc; > } InfoProv; > > typedef struct InfoProvEnt_ { > StgInfoTable * info; > InfoProv prov; > struct InfoProvEnt_ *link; > } InfoProvEnt; The source positions are approximated in a similar way to the source positions for DWARF debugging information. They are only approximate but in our experience provide a good enough hint about where the problem might be. It is therefore recommended to use this flag in conjunction with `-g<n>` for more accurate locations. The lookup table is also emitted into the eventlog when it is available as it is intended to be used with the `-hi` profiling mode. Using this flag will significantly increase the size of the resulting object file but only by a factor of 2-3x in our experience. - - - - - 960108eb by Matthew Pickering at 2020-11-23T11:18:42+00:00 Add option to give each usage of a data constructor its own info table The `-fdistinct-constructor-tables` flag will generate a fresh info table for the usage of any data constructor. This is useful for debugging as now by inspecting the info table, you can determine which usage of a constructor caused that allocation rather than the old situation where the info table always mapped to the definition site of the data constructor which is useless. In conjunction with `-hi` and `-finfo-table-map` this gives a more fine grained understanding of where constructor allocations arise from in a program. - - - - - e1270f24 by Matthew Pickering at 2020-11-23T11:18:44+00:00 Add whereFrom and whereFrom# primop The `whereFrom` function provides a Haskell interface for using the information created by `-finfo-table-map`. Given a Haskell value, the info table address will be passed to the `lookupIPE` function in order to attempt to find the source location information for that particular closure. At the moment it's not possible to distinguish the absense of the map and a failed lookup. - - - - - e1fb2d2b by Matthew Pickering at 2020-11-23T11:18:44+00:00 Add test for whereFrom# - - - - - 364ceb53 by Matthew Pickering at 2020-11-23T11:18:44+00:00 Add release notes for -hi, -finfo-table-map and -fdistinct-constructor-tables - - - - - 570ea663 by David Eichmann at 2020-11-23T11:27:07+00:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - a45694db by Matthew Pickering at 2020-11-23T11:27:07+00:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 It now points to the wrong place, and should be dealt with in client code. - - - - - 2b9dfd09 by Matthew Pickering at 2020-11-23T11:33:17+00:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 293cf770 by GHC GitLab CI at 2020-11-25T23:09:19+00:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - 5b73212e by GHC GitLab CI at 2020-11-25T23:09:35+00:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 3d6d269b by GHC GitLab CI at 2020-11-26T00:10:26+00:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 5aabe473 by GHC GitLab CI at 2020-11-26T00:11:41+00:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - ab1e1929 by GHC GitLab CI at 2020-11-26T01:01:18+00:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 51ad8e05 by GHC GitLab CI at 2020-11-26T01:06:32+00:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - dce82a43 by GHC GitLab CI at 2020-11-26T01:07:24+00:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 576f4d94 by GHC GitLab CI at 2020-11-26T23:15:11+00:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Hooks.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Stg/CSE.hs - + compiler/GHC/Stg/Debug.hs - compiler/GHC/Stg/DepAnal.hs - compiler/GHC/Stg/FVs.hs - compiler/GHC/Stg/Lift.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/Stg/Lift/Monad.hs - compiler/GHC/Stg/Lint.hs - compiler/GHC/Stg/Stats.hs - compiler/GHC/Stg/Syntax.hs - compiler/GHC/Stg/Unarise.hs - compiler/GHC/StgToCmm.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Closure.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Expr.hs - compiler/GHC/StgToCmm/Monad.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Prof.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e151c961266e3b4fdc966918f2cbde9aa657436a...576f4d948127bf7edbb3055793d6400be22aa233 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e151c961266e3b4fdc966918f2cbde9aa657436a...576f4d948127bf7edbb3055793d6400be22aa233 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 Nov 26 23:16:49 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Thu, 26 Nov 2020 18:16:49 -0500 Subject: [Git][ghc/ghc][wip/amg/fieldselectors] 3 commits: Simplify IncorrectParent Message-ID: <5fc037617f3e4_86c111d4a004683ec@gitlab.mail> Adam Gundry pushed to branch wip/amg/fieldselectors at Glasgow Haskell Compiler / GHC Commits: 3d84bba9 by Adam Gundry at 2020-11-25T21:48:47+00:00 Simplify IncorrectParent - - - - - 01e161e0 by Adam Gundry at 2020-11-26T22:35:11+00:00 Correct NoFieldSelectors tests in the light of #18999 - - - - - 78970cde by Adam Gundry at 2020-11-26T23:16:21+00:00 WIP: refactor and clean up GHC.Rename.Env - - - - - 13 changed files: - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Unbound.hs - compiler/GHC/Tc/Gen/Export.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Types/Name/Reader.hs - testsuite/tests/rename/should_compile/NFSDRF.hs - testsuite/tests/rename/should_compile/NoFieldSelectors.hs - testsuite/tests/rename/should_fail/NoFieldSelectorsFail.hs - testsuite/tests/rename/should_fail/NoFieldSelectorsFail.stderr Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -17,9 +17,9 @@ module GHC.Rename.Env ( lookupLocalOccThLvl_maybe, lookupLocalOccRn, lookupTypeOccRn, lookupGlobalOccRn, lookupGlobalOccRn_maybe, - LookupOccRnOverloadedResult(..), - lookupGlobalOccRn_overloaded_sel, - lookupOccRn_overloaded_expr, + LookupOccResult(..), + lookupOccRn_overloaded_maybe, + lookupGlobalOccRn_overloaded, ChildLookupResult(..), lookupSubBndrOcc_helper, @@ -507,12 +507,14 @@ lookupRecFieldOcc mb_con rdr_name ; case mb_field of Just (fl, gre) -> do { addUsedGRE True gre ; return (flSelector fl) } - Nothing -> lookupGlobalOccRn rdr_name } + Nothing -> lookupGlobalOccRn' fos rdr_name } -- See Note [Fall back on lookupGlobalOccRn in lookupRecFieldOcc] | otherwise -- This use of Global is right as we are looking up a selector which -- can only be defined at the top level. - = lookupGlobalOccRn rdr_name + = lookupGlobalOccRn' fos rdr_name + where + fos = IncludeFieldsWithoutSelectors {- Note [DisambiguateRecordFields] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -648,14 +650,13 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent - (gre_name g) (ppr $ gre_name g) + (gre_child g) [p | Just p <- [getParent g]] gss@(g:gss'@(_:_)) -> if all isRecFldGRE gss && overload_ok then return $ IncorrectParent parent - (gre_name g) - (ppr $ expectJust "noMatchingParentErr" (greLabel g)) + (gre_child g) [p | x <- gss, Just p <- [getParent x]] else mkNameClashErr $ g NE.:| gss' @@ -735,8 +736,7 @@ instance Monoid DisambigInfo where data ChildLookupResult = NameNotFound -- We couldn't find a suitable name | IncorrectParent Name -- Parent - Name -- Name of thing we were looking for - SDoc -- How to print the name + Child -- Child we were looking for [Name] -- List of possible parents | FoundChild Parent Child -- We resolved to a child @@ -752,8 +752,8 @@ combineChildLookupResult (x:xs) = do instance Outputable ChildLookupResult where ppr NameNotFound = text "NameNotFound" ppr (FoundChild p n) = text "Found:" <+> ppr p <+> ppr n - ppr (IncorrectParent p n td ns) = text "IncorrectParent" - <+> hsep [ppr p, ppr n, td, ppr ns] + ppr (IncorrectParent p n ns) = text "IncorrectParent" + <+> hsep [ppr p, ppr n, ppr ns] lookupSubBndrOcc :: Bool -> Name -- Parent @@ -1065,71 +1065,83 @@ when the user writes the following declaration x = id Int -} --- | Look up a global variable, local variable or one or more record selector functions. --- It does NOT find a record selector created under NoFieldSelectors. --- See Note [NoFieldSelectors] -lookupOccRn_overloaded_expr :: DuplicateRecordFields -> RdrName -> RnM (Maybe LookupOccRnOverloadedResult) -lookupOccRn_overloaded_expr overload_ok rdr_name - = do { mb_name <- lookupOccRnX_maybe global_lookup LookupOccRnUnique rdr_name - ; case mb_name of - Nothing -> fmap @Maybe LookupOccRnUnique <$> lookup_promoted rdr_name - -- See Note [Promotion]. - -- We try looking up the name as a - -- type constructor or type variable, if - -- we failed to look up the name at the term level. - p -> return p } - where - global_lookup :: RdrName -> RnM (Maybe LookupOccRnOverloadedResult) - global_lookup n = - runMaybeT . msum . map MaybeT $ - [ lookupGlobalOccRn_overloaded_expr overload_ok n - , listToMaybe <$> lookupQualifiedNameGHCi n ] - -lookupOccRnX_maybe :: (RdrName -> RnM (Maybe r)) -> (Name -> r) -> RdrName - -> RnM (Maybe r) -lookupOccRnX_maybe globalLookup wrapper rdr_name - = runMaybeT . msum . map MaybeT $ - [ fmap wrapper <$> lookupLocalOccRn_maybe rdr_name - , globalLookup rdr_name ] +-- | Result of looking up an occurrence that might be an ambiguous field. +data LookupOccResult + = LookupOccName Name + -- ^ Occurrence picked out a non-field Name (potentially unbound). + | LookupOccFields (NE.NonEmpty FieldLabel) + -- ^ Occurrence picked out one or more fields. If ambiguous fields were not + -- allowed during lookup, this list will be a singleton. + +-- | Get the Name of the result. This assumes ambiguous fields were not allowed +-- (otherwise it simply returns the first field, without any disambiguation). +-- Also note that, for fields, this discards the field label and returns the +-- underlying selector function, which may have a mangled Name (see Note +-- [FieldLabel] in GHC.Types.FieldLabel). +nameFromLookupOccResult :: LookupOccResult -> Name +nameFromLookupOccResult (LookupOccName x) = x +nameFromLookupOccResult (LookupOccFields xs) = flSelector (NE.head xs) + + +-- | Look up a global variable, local variable or one or more record selector +-- functions. The 'FieldsOrSelectors' argument controls whether it will include +-- record fields created under NoFieldSelectors. See Note [NoFieldSelectors]. +-- The 'DuplicateRecordFields' argument controls whether ambiguous fields may be +-- returned. +-- +-- This is used for looking up variables in expressions during renaming. +lookupOccRn_overloaded_maybe + :: Bool-> FieldsOrSelectors -> DuplicateRecordFields -> RdrName + -> RnM (Maybe LookupOccResult) +lookupOccRn_overloaded_maybe try_promotion fos overload_ok rdr_name = + runMaybeT . msum . map MaybeT $ + [ fmap LookupOccName <$> lookupLocalOccRn_maybe rdr_name + , lookupGlobalOccRn_overloaded_maybe fos overload_ok rdr_name + , promoted_lookup + ] + where + -- See Note [Promotion]. We try looking up the name as a type + -- constructor or type variable, if we failed to look up the name at the + -- term level. + promoted_lookup :: RnM (Maybe LookupOccResult) + promoted_lookup + | try_promotion = fmap LookupOccName <$> lookup_promoted rdr_name + | otherwise = pure Nothing + +-- Used outside this module only by TH name reification (lookupName, lookupThName_maybe) lookupOccRn_maybe :: RdrName -> RnM (Maybe Name) -lookupOccRn_maybe = lookupOccRnX_maybe lookupGlobalOccRn_maybe id +lookupOccRn_maybe rdr_name = + fmap nameFromLookupOccResult <$> + lookupOccRn_overloaded_maybe False ExcludeFieldsWithoutSelectors NoDuplicateRecordFields rdr_name -lookupGlobalOccRn_maybe :: RdrName -> RnM (Maybe Name) -- Looks up a RdrName occurrence in the top-level -- environment, including using lookupQualifiedNameGHCi -- for the GHCi case, but first tries to find an Exact or Orig name. -- No filter function; does not report an error on failure -- See Note [Errors in lookup functions] -- Uses addUsedRdrName to record use and deprecations +-- +-- Used directly only by getLocalNonValBinders (new_assoc). +lookupGlobalOccRn_maybe :: RdrName -> RnM (Maybe Name) lookupGlobalOccRn_maybe rdr_name = - lookupExactOrOrig_maybe rdr_name id (lookupGlobalOccRn_base rdr_name) + fmap nameFromLookupOccResult <$> + lookupGlobalOccRn_overloaded_maybe ExcludeFieldsWithoutSelectors + NoDuplicateRecordFields + rdr_name +-- Used by exports_from_avail lookupGlobalOccRn :: RdrName -> RnM Name +lookupGlobalOccRn = lookupGlobalOccRn' ExcludeFieldsWithoutSelectors + +lookupGlobalOccRn' :: FieldsOrSelectors -> RdrName -> RnM Name -- lookupGlobalOccRn is like lookupOccRn, except that it looks in the global -- environment. Adds an error message if the RdrName is not in scope. -- You usually want to use "lookupOccRn" which also looks in the local -- environment. -lookupGlobalOccRn rdr_name = - lookupExactOrOrig rdr_name id $ do - mn <- lookupGlobalOccRn_base rdr_name - case mn of - Just n -> return n - Nothing -> do { traceRn "lookupGlobalOccRn" (ppr rdr_name) - ; unboundName WL_Global rdr_name } - --- Looks up a RdrName occurence in the GlobalRdrEnv and with --- lookupQualifiedNameGHCi. Does not try to find an Exact or Orig name first. --- lookupQualifiedNameGHCi here is used when we're in GHCi and a name like --- 'Data.Map.elems' is typed, even if you didn't import Data.Map -lookupGlobalOccRn_base :: RdrName -> RnM (Maybe Name) -lookupGlobalOccRn_base rdr_name = - runMaybeT . msum . map MaybeT $ - [ fmap gre_name <$> lookupGreRn_maybe rdr_name - , listToMaybe . concatMap nameFromLookupOccRnOverloadedResult - <$> lookupQualifiedNameGHCi rdr_name ] - -- This test is not expensive, - -- and only happens for failed lookups +lookupGlobalOccRn' fos rdr_name = + nameFromLookupOccResult <$> + lookupGlobalOccRn_overloaded fos NoDuplicateRecordFields rdr_name lookupInfoOccRn :: RdrName -> RnM [Name] -- lookupInfoOccRn is intended for use in GHCi's ":info" command @@ -1142,68 +1154,86 @@ lookupInfoOccRn :: RdrName -> RnM [Name] lookupInfoOccRn rdr_name = lookupExactOrOrig rdr_name (:[]) $ do { rdr_env <- getGlobalRdrEnv - ; let ns = map gre_name (lookupGRE_RdrName rdr_name rdr_env) - ; qual_ns <- concatMap nameFromLookupOccRnOverloadedResult - <$> lookupQualifiedNameGHCi rdr_name + ; let ns = map gre_name (lookupGRE_RdrName' fos rdr_name rdr_env) + ; qual_ns <- map childName <$> lookupQualifiedNameGHCi fos rdr_name ; return (ns ++ (qual_ns `minusList` ns)) } + where + fos = IncludeFieldsWithoutSelectors --- | A datatype to distinguish record selector functions from regular symbols. -data LookupOccRnOverloadedResult - = LookupOccRnUnique Name - -- ^ non-selector name uniquely refers to x - -- or there is a name clash - | LookupOccRnSelectors (NE.NonEmpty FieldLabel) - -- ^ name refers to one or more record selectors; - -- If DuplicateRecordFields is disabled, this list will be - -- a singleton. - -nameFromLookupOccRnOverloadedResult :: LookupOccRnOverloadedResult -> [Name] -nameFromLookupOccRnOverloadedResult (LookupOccRnUnique x) = [x] -nameFromLookupOccRnOverloadedResult (LookupOccRnSelectors xs) = map flSelector $ NE.toList xs - -instance Outputable LookupOccRnOverloadedResult where - ppr (LookupOccRnUnique x) = text "LookupOccRnUnique " <> ppr x - ppr (LookupOccRnSelectors xs) = text "LoookupOccRnSelectors " <> ppr xs -- | Process a list of 'GlobalRdrElt's in 'GreLookupResult' matching the given 'RdrName' -- and check if it is a unique 'Name' or a set of record selector functions. -- See Note [NoFieldSelectors] + +-- Look up the RdrName in the GlobalRdrEnv +-- Exactly one binding: records it as "used", return (Just gre) +-- No bindings: return Nothing +-- Many bindings: report "ambiguous", return an arbitrary (Just gre) +-- Uses addUsedRdrName to record use and deprecations + lookupGlobalOccRn_resolve :: DuplicateRecordFields -> RdrName -> GreLookupResult - -> RnM (Maybe LookupOccRnOverloadedResult) + -> RnM (Maybe LookupOccResult) lookupGlobalOccRn_resolve overload_ok rdr_name res = case res of GreNotFound -> return Nothing OneNameMatch gre -> return $ Just $ case gre_child gre of - ChildName name -> LookupOccRnUnique name - ChildField fl -> LookupOccRnSelectors $ pure fl - MultipleNames gres - | fld : flds <- mapMaybe greFieldLabel $ NE.toList gres - , overload_ok == DuplicateRecordFields || null flds -> - -- Don't record usage for ambiguous selectors - -- until we know which is meant - return $ Just $ LookupOccRnSelectors $ fld NE.:| flds + ChildName name -> LookupOccName name + ChildField fl -> LookupOccFields $ pure fl + MultipleNames (gre NE.:| gres) + -- Make sure *all* the names are fields before returning a non-clash result; + -- mixing fields and non-fields is not allowed. + | overload_ok == DuplicateRecordFields || null gres + , Just fld <- greFieldLabel gre + , Just flds <- mapM greFieldLabel gres + -> return $ Just $ LookupOccFields $ fld NE.:| flds MultipleNames gres -> do addNameClashErrRn rdr_name gres - return $ Just $ LookupOccRnUnique $ gre_name (NE.head gres) + return $ Just $ LookupOccName $ gre_name (NE.head gres) --- | Look up a variable or record selector functions. -lookupGlobalOccRn_overloaded_expr :: DuplicateRecordFields +-- | Used when looking up fields in record updates. +lookupGlobalOccRn_overloaded + :: FieldsOrSelectors + -> DuplicateRecordFields + -> RdrName + -> RnM LookupOccResult +lookupGlobalOccRn_overloaded fos overload_ok rdr_name = do + mb <- lookupGlobalOccRn_overloaded_maybe fos overload_ok rdr_name + case mb of + Just r -> return r + Nothing -> do { traceRn "lookupGlobalOccRn_overloaded unbound" (ppr rdr_name) + ; LookupOccName <$> unboundName WL_Global rdr_name } + + +-- | Look up a variable or record selector functions. Looks up a RdrName +-- occurence in the GlobalRdrEnv and with 'lookupQualifiedNameGHCi'. +-- 'lookupQualifiedNameGHCi' here is used when we're in GHCi and a name like +-- 'Data.Map.elems' is typed, even if you didn't import "Data.Map". +lookupGlobalOccRn_overloaded_maybe + :: FieldsOrSelectors + -> DuplicateRecordFields -> RdrName - -> RnM (Maybe LookupOccRnOverloadedResult) -lookupGlobalOccRn_overloaded_expr overload_ok rdr_name = - lookupExactOrOrig_maybe rdr_name (fmap LookupOccRnUnique) $ - do { env <- getGlobalRdrEnv - ; res <- case filter (not . isNoFieldSelectorGRE) - -- filter out invisible selector functions - $ lookupGRE_RdrName rdr_name env of - [] -> return GreNotFound - [gre] -> do { addUsedGRE True gre - ; return (OneNameMatch gre) } - gre : gres -> return $ MultipleNames $ gre NE.:| gres - ; lookupGlobalOccRn_resolve overload_ok rdr_name res - } + -> RnM (Maybe LookupOccResult) +lookupGlobalOccRn_overloaded_maybe fos overload_ok rdr_name = + lookupExactOrOrig_maybe rdr_name (fmap LookupOccName) $ + runMaybeT . msum . map MaybeT $ + [ do res <- lookupGreRn_helper fos rdr_name + lookupGlobalOccRn_resolve overload_ok rdr_name res + , children_to_lookup_result <$> lookupQualifiedNameGHCi fos rdr_name ] + where + children_to_lookup_result :: [Child] -> Maybe LookupOccResult + children_to_lookup_result [ChildName name] = Just $ LookupOccName name + children_to_lookup_result [ChildField fl] = Just $ LookupOccFields (fl NE.:| []) + children_to_lookup_result children + | overload_ok == DuplicateRecordFields + = do (fl:fls) <- mapM to_field children + Just $ LookupOccFields (fl NE.:| fls) + | otherwise = Nothing + + to_field (ChildField fl) = Just fl + to_field (ChildName _) = Nothing + {- Note [NoFieldSelectors] @@ -1226,20 +1256,6 @@ In order to avoid name clashes, selector names are mangled in the same way as Du generates @$sel:foo:MkT at . -} --- | Look up a variable or record selectors. --- It MAY find a selector function with NoFieldSelectors. --- See Note [NoFieldSelectors] -lookupGlobalOccRn_overloaded_sel :: DuplicateRecordFields - -> RdrName - -> RnM (Maybe LookupOccRnOverloadedResult) -lookupGlobalOccRn_overloaded_sel overload_ok rdr_name = - lookupExactOrOrig_maybe rdr_name (fmap LookupOccRnUnique) $ runMaybeT $ msum - [ MaybeT $ do - { res <- lookupGreRn_helper rdr_name - ; lookupGlobalOccRn_resolve overload_ok rdr_name res } - , MaybeT (listToMaybe <$> lookupQualifiedNameGHCi rdr_name) - ] - -------------------------------------------------- -- Lookup in the Global RdrEnv of the module @@ -1249,22 +1265,6 @@ data GreLookupResult = GreNotFound | OneNameMatch GlobalRdrElt | MultipleNames (NE.NonEmpty GlobalRdrElt) -lookupGreRn_maybe :: RdrName -> RnM (Maybe GlobalRdrElt) --- Look up the RdrName in the GlobalRdrEnv --- Exactly one binding: records it as "used", return (Just gre) --- No bindings: return Nothing --- Many bindings: report "ambiguous", return an arbitrary (Just gre) --- Uses addUsedRdrName to record use and deprecations -lookupGreRn_maybe rdr_name - = do - res <- lookupGreRn_helper rdr_name - case res of - OneNameMatch gre -> return $ Just gre - MultipleNames gres -> do - traceRn "lookupGreRn_maybe:NameClash" (ppr gres) - addNameClashErrRn rdr_name gres - return $ Just (NE.head gres) - GreNotFound -> return Nothing {- @@ -1295,13 +1295,15 @@ is enabled then we defer the selection until the typechecker. -- Internal Function -lookupGreRn_helper :: RdrName -> RnM GreLookupResult -lookupGreRn_helper rdr_name +lookupGreRn_helper :: FieldsOrSelectors -> RdrName -> RnM GreLookupResult +lookupGreRn_helper fos rdr_name = do { env <- getGlobalRdrEnv - ; case lookupGRE_RdrName rdr_name env of + ; case lookupGRE_RdrName' fos rdr_name env of [] -> return GreNotFound [gre] -> do { addUsedGRE True gre ; return (OneNameMatch gre) } + -- Don't record usage for ambiguous names + -- until we know which is meant gre : gres -> return (MultipleNames $ gre NE.:| gres) } lookupGreAvailRn :: RdrName -> RnM (Name, AvailInfo) @@ -1310,7 +1312,7 @@ lookupGreAvailRn :: RdrName -> RnM (Name, AvailInfo) -- Uses addUsedRdrName to record use and deprecations lookupGreAvailRn rdr_name = do - mb_gre <- lookupGreRn_helper rdr_name + mb_gre <- lookupGreRn_helper IncludeFieldsWithoutSelectors rdr_name case mb_gre of GreNotFound -> do @@ -1472,8 +1474,8 @@ this requires some refactoring so leave as a TODO -lookupQualifiedNameGHCi :: RdrName -> RnM [LookupOccRnOverloadedResult] -lookupQualifiedNameGHCi rdr_name +lookupQualifiedNameGHCi :: FieldsOrSelectors -> RdrName -> RnM [Child] +lookupQualifiedNameGHCi fos rdr_name = -- We want to behave as we would for a source file import here, -- and respect hiddenness of modules/packages, hence loadSrcInterface. do { dflags <- getDynFlags @@ -1481,16 +1483,6 @@ lookupQualifiedNameGHCi rdr_name ; go_for_it dflags is_ghci } where - -- TODO: this could be done more sensibly - convert :: [Child] -> [LookupOccRnOverloadedResult] - convert [ChildName n] = [LookupOccRnUnique n] - convert children = case mapM to_field children of - Just (fl:fls) -> [LookupOccRnSelectors (fl NE.:| fls)] - _ -> [] - - to_field (ChildField fl) = Just fl - to_field (ChildName _) = Nothing - go_for_it dflags is_ghci | Just (mod,occ) <- isQual_maybe rdr_name , is_ghci @@ -1499,10 +1491,12 @@ lookupQualifiedNameGHCi rdr_name = do { res <- loadSrcInterface_maybe doc mod NotBoot Nothing ; case res of Succeeded iface - -> return $ convert [ child + -> return [ child | avail <- mi_exports iface , child <- availChildren avail - , occName child == occ ] + , occName child == occ + , allow_child child + ] _ -> -- Either we couldn't load the interface, or -- we could but we didn't find the name in it @@ -1515,6 +1509,10 @@ lookupQualifiedNameGHCi rdr_name doc = text "Need to find" <+> ppr rdr_name + allow_child (ChildField fl) = (flHasFieldSelector fl == FieldSelectors) + || (fos == IncludeFieldsWithoutSelectors) + allow_child (ChildName _) = True + {- Note [Looking up signature names] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -123,11 +123,11 @@ rnUnboundVar v = rnExpr (HsVar _ (L l v)) = do { dflags <- getDynFlags ; let overload_ok = xopt_DuplicateRecordFields dflags - ; mb_name <- lookupOccRn_overloaded_expr overload_ok v + ; mb_name <- lookupOccRn_overloaded_maybe True ExcludeFieldsWithoutSelectors overload_ok v ; case mb_name of { Nothing -> rnUnboundVar v ; - Just (LookupOccRnUnique name) + Just (LookupOccName name) | name == nilDataConName -- Treat [] as an ExplicitList, so that -- OverloadedLists works correctly -- Note [Empty lists] in GHC.Hs.Expr @@ -136,9 +136,9 @@ rnExpr (HsVar _ (L l v)) | otherwise -> finishHsVar (L l name) ; - Just (LookupOccRnSelectors (s NE.:| [])) -> -- AMG TODO review this + Just (LookupOccFields (s NE.:| [])) -> -- AMG TODO review this return ( HsRecFld noExtField (Unambiguous (flSelector s) (L l v) ), unitFV (flSelector s)) ; - Just (LookupOccRnSelectors fs@(_ NE.:| _:_)) -> + Just (LookupOccFields fs@(_ NE.:| _:_)) -> return ( HsRecFld noExtField (Ambiguous noExtField (L l v)) , mkFVs $ NE.toList $ fmap flSelector fs); } } ===================================== compiler/GHC/Rename/Pat.hs ===================================== @@ -58,8 +58,7 @@ import GHC.Rename.Fixity import GHC.Rename.Utils ( HsDocContext(..), newLocalBndrRn, bindLocalNames , warnUnusedMatches, newLocalBndrRn , checkUnusedRecordWildcard - , checkDupNames, checkDupAndShadowedNames - , unknownSubordinateErr ) + , checkDupNames, checkDupAndShadowedNames ) import GHC.Rename.HsType import GHC.Builtin.Names import GHC.Types.Name @@ -740,8 +739,6 @@ rnHsRecUpdFields flds ; return (flds1, plusFVs fvss) } where - doc = text "constructor field name" - rn_fld :: Bool -> DuplicateRecordFields -> LHsRecUpdField GhcPs -> RnM (LHsRecUpdField GhcRn, FreeVars) rn_fld pun_ok overload_ok (L l (HsRecField { hsRecFieldLbl = L loc f @@ -751,16 +748,7 @@ rnHsRecUpdFields flds ; sel <- setSrcSpan loc $ -- Defer renaming of overloaded fields to the typechecker -- See Note [Disambiguating record fields] in GHC.Tc.Gen.Head - -- AMG TODO: not clear why we need this test, but T11941 fails if we don't - if overload_ok == DuplicateRecordFields - then do { mb <- lookupGlobalOccRn_overloaded_sel overload_ok lbl - ; case mb of - Nothing -> - do { addErr - (unknownSubordinateErr doc lbl) - ; return Nothing } - Just r -> return $ Just r } - else fmap (Just . LookupOccRnUnique) $ lookupGlobalOccRn lbl + lookupGlobalOccRn_overloaded IncludeFieldsWithoutSelectors overload_ok lbl ; arg' <- if pun then do { checkErr pun_ok (badPun (L loc lbl)) -- Discard any module qualifier (#11662) @@ -770,13 +758,13 @@ rnHsRecUpdFields flds ; (arg'', fvs) <- rnLExpr arg' ; let fvs' = case sel of -- AMG TODO review this - Just (LookupOccRnUnique sel_name) -> fvs `addOneFV` sel_name - Just (LookupOccRnSelectors (fld NE.:| [])) -> fvs `addOneFV` flSelector fld + LookupOccName sel_name -> fvs `addOneFV` sel_name + LookupOccFields (fld NE.:| []) -> fvs `addOneFV` flSelector fld _ -> fvs lbl' = case sel of - Just (LookupOccRnUnique sel_name) -> + LookupOccName sel_name -> L loc (Unambiguous sel_name (L loc lbl)) - Just (LookupOccRnSelectors (fld NE.:| [])) -> + LookupOccFields (fld NE.:| []) -> L loc (Unambiguous (flSelector fld) (L loc lbl)) _ -> L loc (Ambiguous noExtField (L loc lbl)) ===================================== compiler/GHC/Rename/Unbound.hs ===================================== @@ -121,7 +121,7 @@ unknownNameSuggestions_ where_look dflags hpt curr_mod global_env local_env fieldSelectorSuggestions :: GlobalRdrEnv -> RdrName -> SDoc fieldSelectorSuggestions global_env tried_rdr_name - = case filter isNoFieldSelectorGRE $ lookupGRE_RdrName tried_rdr_name global_env of + = case filter isNoFieldSelectorGRE $ lookupGRE_RdrName' IncludeFieldsWithoutSelectors tried_rdr_name global_env of gre : _ -> text "NB:" <+> ppr tried_rdr_name <+> whose gre ===================================== compiler/GHC/Tc/Gen/Export.hs ===================================== @@ -529,7 +529,7 @@ lookupChildrenExport spec_parent rdr_items = ChildField fl -> Right (L (getLoc n) fl) ChildName name -> Left (replaceLWrappedName n name) } - IncorrectParent p g td gs -> failWithDcErr p g td gs + IncorrectParent p c gs -> failWithDcErr p c gs -- Note: [Typing Pattern Synonym Exports] @@ -617,7 +617,7 @@ checkPatSynParent parent NoParent child AConLike (PatSynCon p) -> handle_pat_syn (psErr p) parent_ty_con p - _ -> failWithDcErr parent mpat_syn (ppr child) [] } + _ -> failWithDcErr parent child [] } where psErr = exportErrCtxt "pattern synonym" selErr = exportErrCtxt "pattern synonym record selector" @@ -809,11 +809,11 @@ dcErrMsg ty_con what_is thing parents = [_] -> text "Parent:" _ -> text "Parents:") <+> fsep (punctuate comma parents) -failWithDcErr :: Name -> Name -> SDoc -> [Name] -> TcM a -failWithDcErr parent thing thing_doc parents = do - ty_thing <- tcLookupGlobal thing +failWithDcErr :: Name -> Child -> [Name] -> TcM a +failWithDcErr parent child parents = do + ty_thing <- tcLookupGlobal (childName child) failWithTc $ dcErrMsg parent (tyThingCategory' ty_thing) - thing_doc (map ppr parents) + (ppr child) (map ppr parents) where tyThingCategory' :: TyThing -> String tyThingCategory' (AnId i) ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -1310,7 +1310,7 @@ disambiguateRecordBinds record_expr record_rho rbnds res_ty , [(RecSelParent, GlobalRdrElt)])] getUpdFieldsParents = fmap (zip rbnds) $ mapM - (lookupParents . unLoc . hsRecUpdFieldRdr . unLoc) + (lookupParents IncludeFieldsWithoutSelectors . unLoc . hsRecUpdFieldRdr . unLoc) rbnds -- Given a the lists of possible parents for each field, ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -539,7 +539,7 @@ finish_ambiguous_selector lr@(L _ rdr) parent_type Nothing -> ambiguousSelector lr ; Just p -> - do { xs <- lookupParents rdr + do { xs <- lookupParents ExcludeFieldsWithoutSelectors rdr ; let parent = RecSelData p ; case lookup parent xs of { Nothing -> failWithTc (fieldNotInType parent rdr) ; @@ -592,13 +592,13 @@ tyConOfET fam_inst_envs ty0 = tyConOf fam_inst_envs =<< checkingExpType_maybe ty -- For an ambiguous record field, find all the candidate record -- selectors (as GlobalRdrElts) and their parents. -lookupParents :: RdrName -> RnM [(RecSelParent, GlobalRdrElt)] -lookupParents rdr +lookupParents :: FieldsOrSelectors -> RdrName -> RnM [(RecSelParent, GlobalRdrElt)] +lookupParents fos rdr = do { env <- getGlobalRdrEnv -- filter by isRecFldGRE because otherwise a non-selector variable with an overlapping name can get through -- when NoFieldSelector is enabled - -- AMG TODO really need a function to do this consistently! - ; let gres = filter isRecFldGRE $ lookupGRE_RdrName rdr env + -- AMG TODO check this, seems implausible + ; let gres = filter isRecFldGRE $ lookupGRE_RdrName' fos rdr env ; mapM lookupParent gres } where lookupParent :: GlobalRdrElt -> RnM (RecSelParent, GlobalRdrElt) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1499,11 +1499,8 @@ lookupName :: Bool -- True <=> type namespace -- False <=> value namespace -> String -> TcM (Maybe TH.Name) lookupName is_type_name s - = do { lcl_env <- getLocalRdrEnv - ; case lookupLocalRdrEnv lcl_env rdr_name of - Just n -> return (Just (reifyName n)) - Nothing -> do { mb_nm <- lookupGlobalOccRn_maybe rdr_name - ; return (fmap reifyName mb_nm) } } + = do { mb_nm <- lookupOccRn_maybe rdr_name + ; return (fmap reifyName mb_nm) } where th_name = TH.mkName s -- Parses M.x into a base of 'x' and a module of 'M' @@ -1552,18 +1549,10 @@ lookupThName th_name = do lookupThName_maybe :: TH.Name -> TcM (Maybe Name) lookupThName_maybe th_name - = do { names <- mapMaybeM lookup (thRdrNameGuesses th_name) + = do { names <- mapMaybeM lookupOccRn_maybe (thRdrNameGuesses th_name) -- Pick the first that works -- E.g. reify (mkName "A") will pick the class A in preference to the data constructor A ; return (listToMaybe names) } - where - lookup rdr_name - = do { -- Repeat much of lookupOccRn, because we want - -- to report errors in a TH-relevant way - ; rdr_env <- getLocalRdrEnv - ; case lookupLocalRdrEnv rdr_env rdr_name of - Just name -> return (Just name) - Nothing -> lookupGlobalOccRn_maybe rdr_name } tcLookupTh :: Name -> TcM TcTyThing -- This is a specialised version of GHC.Tc.Utils.Env.tcLookup; specialised mainly in that ===================================== compiler/GHC/Types/Name/Reader.hs ===================================== @@ -46,7 +46,7 @@ module GHC.Types.Name.Reader ( GlobalRdrEnv, emptyGlobalRdrEnv, mkGlobalRdrEnv, plusGlobalRdrEnv, lookupGlobalRdrEnv, extendGlobalRdrEnv, greOccName, shadowNames, pprGlobalRdrEnv, globalRdrEnvElts, - lookupGRE_RdrName, lookupGRE_Name, + lookupGRE_RdrName, lookupGRE_RdrName', lookupGRE_Name, lookupGRE_Child, lookupGRE_FieldLabel, lookupGRE_Name_OccName, getGRE_NameQualifier_maybes, @@ -74,6 +74,7 @@ module GHC.Types.Name.Reader ( -- * Utils opIsAt, + FieldsOrSelectors(..), ) where #include "HsVersions.h" @@ -815,11 +816,26 @@ greOccName :: GlobalRdrElt -> OccName greOccName GRE{gre_child = ChildName n} = nameOccName n greOccName GRE{gre_child = ChildField fl} = mkVarOccFS (flLabel fl) + +-- | When looking up GREs, we may or may not want to include fields that were +-- defined in modules with @NoFieldSelectors@ enabled. +data FieldsOrSelectors + = IncludeFieldsWithoutSelectors -- ^ Include fields in @NoFieldSelectors@ modules + | ExcludeFieldsWithoutSelectors -- ^ Ignore such fields during lookup + deriving Eq + +filterFieldGREs :: FieldsOrSelectors -> [GlobalRdrElt] -> [GlobalRdrElt] +filterFieldGREs IncludeFieldsWithoutSelectors = id +filterFieldGREs ExcludeFieldsWithoutSelectors = filter (not . isNoFieldSelectorGRE) + lookupGRE_RdrName :: RdrName -> GlobalRdrEnv -> [GlobalRdrElt] -lookupGRE_RdrName rdr_name env +lookupGRE_RdrName = lookupGRE_RdrName' ExcludeFieldsWithoutSelectors + +lookupGRE_RdrName' :: FieldsOrSelectors -> RdrName -> GlobalRdrEnv -> [GlobalRdrElt] +lookupGRE_RdrName' fos rdr_name env = case lookupOccEnv env (rdrNameOcc rdr_name) of Nothing -> [] - Just gres -> pickGREs rdr_name gres + Just gres -> filterFieldGREs fos (pickGREs rdr_name gres) lookupGRE_Name :: GlobalRdrEnv -> Name -> Maybe GlobalRdrElt -- ^ Look for precisely this 'Name' in the environment. This tests ===================================== testsuite/tests/rename/should_compile/NFSDRF.hs ===================================== @@ -25,12 +25,12 @@ foo1 = Foo 3 "bar" foo2 = Foo { foo = 3, bar = "bar" } -- disambiguate foo -foo3 :: Foo -foo3 = foo1 { foo = 4 } -- update +-- foo3 :: Foo +-- foo3 = foo1 { foo = 4 } -- currently rejected, see #18999 -foo4 = foo1 { bar = "baz" } -- bar is unambiguous +foo4 = foo1 { bar = "baz" } -- unambiguous bar0 = Bar { foo = 0, bar' = "bar'" } -bar1 :: Bar -bar1 = bar0 { foo = 1 } +-- bar1 :: Bar +-- bar1 = bar0 { foo = 1 } -- currently rejected, see #18999 ===================================== testsuite/tests/rename/should_compile/NoFieldSelectors.hs ===================================== @@ -10,6 +10,7 @@ import Prelude data Foo = Foo { foo :: Int, bar :: String } +{-# ANN foo () #-} foo = 3 -- should not conflict fooX = foo + 1 @@ -24,6 +25,6 @@ foo1 = Foo 3 "bar" foo2 = Foo { foo = 3, bar = "bar" } -- disambiguate foo -foo3 = foo1 { foo = 4 } -- bar is unambiguous +-- foo3 = foo1 { foo = 4 } -- currently rejected, see #18999 foo4 = foo1 { bar = "baz" } -- bar is unambiguous ===================================== testsuite/tests/rename/should_fail/NoFieldSelectorsFail.hs ===================================== @@ -18,3 +18,7 @@ foo3 :: Foo foo3 = foo1 { foo = 4 } -- update bar1 = bar0 { foo = 1 } + +bar = undefined + +foo4 = foo1 { bar = "" } -- currently rejected, see #18999 ===================================== testsuite/tests/rename/should_fail/NoFieldSelectorsFail.stderr ===================================== @@ -1,18 +1,25 @@ -NoFieldSelectorsFail.hs:15:14: +NoFieldSelectorsFail.hs:15:14: error: Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’, defined at NoFieldSelectorsFail.hs:10:18 or the field ‘foo’, defined at NoFieldSelectorsFail.hs:9:18 -NoFieldSelectorsFail.hs:18:15: +NoFieldSelectorsFail.hs:18:15: error: Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’, defined at NoFieldSelectorsFail.hs:10:18 or the field ‘foo’, defined at NoFieldSelectorsFail.hs:9:18 -NoFieldSelectorsFail.hs:20:15: +NoFieldSelectorsFail.hs:20:15: error: Ambiguous occurrence ‘foo’ It could refer to either the field ‘foo’, defined at NoFieldSelectorsFail.hs:10:18 - or the field ‘foo’, defined at NoFieldSelectorsFail.hs:9:18 \ No newline at end of file + or the field ‘foo’, defined at NoFieldSelectorsFail.hs:9:18 + +NoFieldSelectorsFail.hs:24:15: error: + Ambiguous occurrence ‘bar’ + It could refer to + either the field ‘bar’, defined at NoFieldSelectorsFail.hs:9:30 + or ‘NoFieldSelectorsFail.bar’, + defined at NoFieldSelectorsFail.hs:22:1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/461c9ba829fd4090d7aa11366cc908f1b6a42cb3...78970cde8c63f6243130971fe94181338a63cbc3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/461c9ba829fd4090d7aa11366cc908f1b6a42cb3...78970cde8c63f6243130971fe94181338a63cbc3 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 Nov 26 23:16:58 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 18:16:58 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 40 commits: Add Addr# atomic primops (#17751) Message-ID: <5fc0376a56030_86c113a5b2c4685f0@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 6a83041d by GHC GitLab CI at 2020-11-26T18:16:37-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - 3f6bcef7 by GHC GitLab CI at 2020-11-26T18:16:37-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 4ad3417c by GHC GitLab CI at 2020-11-26T18:16:37-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 3a293093 by GHC GitLab CI at 2020-11-26T18:16:37-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - b2c173b1 by GHC GitLab CI at 2020-11-26T18:16:37-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 5c1c42cc by GHC GitLab CI at 2020-11-26T18:16:37-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - df5abf98 by GHC GitLab CI at 2020-11-26T18:16:37-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 3d4942de by GHC GitLab CI at 2020-11-26T18:16:38-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 4545ccb9 by Ben Gamari at 2020-11-26T18:16:44-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/576f4d948127bf7edbb3055793d6400be22aa233...4545ccb9ce3ff95af8805c2eb397522cc2c6f932 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/576f4d948127bf7edbb3055793d6400be22aa233...4545ccb9ce3ff95af8805c2eb397522cc2c6f932 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 Nov 26 23:23:27 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 18:23:27 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 2 commits: nonmoving: Add reference to Ueno 2016 Message-ID: <5fc038ef725d8_86c111d4a0047056e@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: fe07a6bd by Ben Gamari at 2020-11-26T18:23:21-05:00 nonmoving: Add reference to Ueno 2016 - - - - - eba4c278 by GHC GitLab CI at 2020-11-26T18:23:21-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 2 changed files: - rts/sm/Evac.c - rts/sm/NonMoving.c Changes: ===================================== rts/sm/Evac.c ===================================== @@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) // // However, if we are in a deadlock detection GC then we disable aging // so there is no need. + // + // See Note [Non-moving GC: Marking evacuated objects]. if (major_gc && !deadlock_detect_gc) markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to); return to; @@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ +/* + * Note [Non-moving GC: Marking evacuated objects] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * When the non-moving collector is in use we must be careful to ensure that any + * references to objects in the non-moving generation from younger generations + * are pushed to the mark queue. + * + * In particular we need to ensure that we handle newly-promoted objects are + * correctly marked. For instance, consider this case: + * + * generation 0 generation 1 + * ────────────── ────────────── + * + * ┌───────┐ + * ┌───────┐ │ A │ + * │ B │ ◁────────────────────────── │ │ + * │ │ ──┬─────────────────┐ └───────┘ + * └───────┘ ┆ after GC │ + * ┆ │ + * ┌───────┐ ┆ before GC │ ┌───────┐ + * │ C │ ◁┄┘ └─────▷ │ C' │ + * │ │ │ │ + * └───────┘ └───────┘ + * + * + * In this case object C started off in generation 0 and was evacuated into + * generation 1 during the preparatory GC. However, the only reference to C' + * is from B, which lives in the generation 0 (via aging); this reference will + * not be visible to the concurrent non-moving collector (which can only + * traverse the generation 1 heap). Consequently, upon evacuating C we need to + * ensure that C' is added to the update remembered set as we know that it will + * continue to be reachable via B (which is assumed to be reachable as it lives + * in a younger generation). + * + * Where this happens depends upon the type of the object (e.g. C'): + * + * - In the case of "normal" small heap-allocated objects this happens in + * alloc_for_copy. + * - In the case of compact region this happens in evacuate_compact. + * - In the case of large objects this happens in evacuate_large. + * + * See also Note [Aging under the non-moving collector] in NonMoving.c. + * + */ + /* size is in words */ STATIC_INLINE GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, @@ -351,6 +399,9 @@ evacuate_large(StgPtr p) __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL); if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, p); } initBdescr(bd, new_gen, new_gen->to); @@ -505,6 +556,9 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -690,13 +744,6 @@ loop: */ if (flags & BF_LARGE) { evacuate_large((P_)q); - - // We may have evacuated the block to the nonmoving generation. If so - // we need to make sure it is added to the mark queue since the only - // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { - markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); - } return; } ===================================== rts/sm/NonMoving.c ===================================== @@ -191,8 +191,8 @@ Mutex concurrent_coll_finished_lock; * === Other references === * * Apart from the design document in docs/storage/nonmoving-gc and the Ueno - * 2016 paper (TODO citation) from which it drew inspiration, there are a - * variety of other relevant Notes scattered throughout the tree: + * 2016 paper [ueno 2016] from which it drew inspiration, there are a variety + * of other relevant Notes scattered throughout the tree: * * - Note [Concurrent non-moving collection] (NonMoving.c) describes * concurrency control of the nonmoving collector @@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock; * - Note [Aging under the non-moving collector] (NonMoving.c) describes how * we accommodate aging * + * - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how + * non-moving objects reached by evacuate() are marked, which is necessary + * due to aging. + * * - Note [Large objects in the non-moving collector] (NonMovingMark.c) * describes how we track large objects. * @@ -232,6 +236,11 @@ Mutex concurrent_coll_finished_lock; * how we use the DIRTY flags associated with MUT_VARs and TVARs to improve * barrier efficiency. * + * [ueno 2016]: + * Katsuhiro Ueno and Atsushi Ohori. 2016. A fully concurrent garbage + * collector for functional programs on multicore processors. SIGPLAN Not. 51, + * 9 (September 2016), 421–433. DOI:https://doi.org/10.1145/3022670.2951944 + * * * Note [Concurrent non-moving collection] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -312,6 +321,8 @@ Mutex concurrent_coll_finished_lock; * * The non-moving collector will come to C in the mark queue and mark it. * + * The implementation details of this are described in Note [Non-moving GC: + * Marking evacuated objects] in Evac.c. * * Note [Deadlock detection under the non-moving collector] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4545ccb9ce3ff95af8805c2eb397522cc2c6f932...eba4c278f55a348c8f8123c616fc9704eefb4618 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4545ccb9ce3ff95af8805c2eb397522cc2c6f932...eba4c278f55a348c8f8123c616fc9704eefb4618 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 Nov 26 23:44:56 2020 From: gitlab at gitlab.haskell.org (Simon Peyton Jones) Date: Thu, 26 Nov 2020 18:44:56 -0500 Subject: [Git][ghc/ghc][wip/T17656] Wibbles Message-ID: <5fc03df8569ba_86c3fc6ab4f115c47638d@gitlab.mail> Simon Peyton Jones pushed to branch wip/T17656 at Glasgow Haskell Compiler / GHC Commits: 061eee91 by Simon Peyton Jones at 2020-11-26T23:44:19+00:00 Wibbles - - - - - 5 changed files: - compiler/GHC/Tc/Solver/Canonical.hs - testsuite/tests/ghci.debugger/scripts/break012.stdout - testsuite/tests/partial-sigs/should_fail/ScopedNamedWildcardsBad.stderr - testsuite/tests/typecheck/should_fail/ExpandSynsFail2.stderr - testsuite/tests/typecheck/should_fail/T7453.stderr Changes: ===================================== compiler/GHC/Tc/Solver/Canonical.hs ===================================== @@ -2269,7 +2269,7 @@ canEqCanLHS2 ev eq_rel swapped lhs1 ps_xi1 lhs2 ps_xi2 mco -- This function handles the case where one side is a tyvar and the other is -- a type family application. Which to put on the left? --- If we can unify the variable, put it on the left, as this may be our only +-- If the tyvar is a meta-tyvar, put it on the left, as this may be our only -- shot to unify. -- Otherwise, put the function on the left, because it's generally better to -- rewrite away function calls. This makes types smaller. And it seems necessary: @@ -2288,17 +2288,16 @@ canEqTyVarFunEq :: CtEvidence -- :: lhs ~ (rhs |> mco) -> MCoercion -- :: kind(rhs) ~N kind(lhs) -> TcS (StopOrContinue Ct) canEqTyVarFunEq ev eq_rel swapped tv1 ps_xi1 fun_tc2 fun_args2 ps_xi2 mco - = do { tclvl <- getTcLevel - ; dflags <- getDynFlags - ; if | isTouchableMetaTyVar tclvl tv1 - , MTVU_OK _ <- checkTyVarEq dflags YesTypeFamilies tv1 (ps_xi2 `mkCastTyMCo` mco) - -> canEqCanLHSFinish ev eq_rel swapped (TyVarLHS tv1) - (ps_xi2 `mkCastTyMCo` mco) + = do { -- tclvl <- getTcLevel + -- dflags <- getDynFlags + ; if | isMetaTyVar tv1 + -> canEqCanLHSFinish ev eq_rel swapped (TyVarLHS tv1) + (ps_xi2 `mkCastTyMCo` mco) | otherwise - -> do { new_ev <- rewriteCastedEquality ev eq_rel swapped + -> do { new_ev <- rewriteCastedEquality ev eq_rel swapped (mkTyVarTy tv1) (mkTyConApp fun_tc2 fun_args2) mco - ; canEqCanLHSFinish new_ev eq_rel IsSwapped + ; canEqCanLHSFinish new_ev eq_rel IsSwapped (TyFamLHS fun_tc2 fun_args2) (ps_xi1 `mkCastTyMCo` sym_mco) } } where ===================================== testsuite/tests/ghci.debugger/scripts/break012.stdout ===================================== @@ -1,14 +1,14 @@ Stopped in Main.g, break012.hs:5:10-18 -_result :: (p, a1 -> a1, (), a -> a -> a) = _ -a :: p = _ -b :: a2 -> a2 = _ +_result :: (a1, a2 -> a2, (), a -> a -> a) = _ +a :: a1 = _ +b :: a3 -> a3 = _ c :: () = _ d :: a -> a -> a = _ -a :: p -b :: a2 -> a2 +a :: a1 +b :: a3 -> a3 c :: () d :: a -> a -> a -a = (_t1::p) -b = (_t2::a2 -> a2) +a = (_t1::a1) +b = (_t2::a3 -> a3) c = (_t3::()) d = (_t4::a -> a -> a) ===================================== testsuite/tests/partial-sigs/should_fail/ScopedNamedWildcardsBad.stderr ===================================== @@ -1,6 +1,11 @@ -ScopedNamedWildcardsBad.hs:8:21: error: +ScopedNamedWildcardsBad.hs:11:15: error: • Couldn't match expected type ‘Bool’ with actual type ‘Char’ - • In the first argument of ‘not’, namely ‘x’ - In the expression: not x - In an equation for ‘v’: v = not x + • In the first argument of ‘g’, namely ‘'x'’ + In the expression: g 'x' + In the expression: + let + v = not x + g :: _a -> _a + g x = x + in (g 'x') ===================================== testsuite/tests/typecheck/should_fail/ExpandSynsFail2.stderr ===================================== @@ -1,6 +1,6 @@ ExpandSynsFail2.hs:19:37: error: - • Couldn't match type ‘Int’ with ‘Bool’ + • Couldn't match type ‘Bool’ with ‘Int’ Expected: ST s Foo Actual: MyBarST s Type synonyms expanded: ===================================== testsuite/tests/typecheck/should_fail/T7453.stderr ===================================== @@ -1,6 +1,8 @@ -T7453.hs:10:30: error: - • Couldn't match expected type ‘t’ with actual type ‘p’ +T7453.hs:9:15: error: + • Couldn't match type ‘t’ with ‘p’ + Expected: Id t + Actual: Id p ‘t’ is a rigid type variable bound by the type signature for: z :: forall t. Id t @@ -8,17 +10,29 @@ T7453.hs:10:30: error: ‘p’ is a rigid type variable bound by the inferred type of cast1 :: p -> a at T7453.hs:(7,1)-(10,30) - • In the first argument of ‘Id’, namely ‘v’ - In the expression: Id v - In an equation for ‘aux’: aux = Id v + • In the expression: aux + In an equation for ‘z’: + z = aux + where + aux = Id v + In an equation for ‘cast1’: + cast1 v + = runId z + where + z :: Id t + z = aux + where + aux = Id v • Relevant bindings include - aux :: Id t (bound at T7453.hs:10:21) + aux :: Id p (bound at T7453.hs:10:21) z :: Id t (bound at T7453.hs:9:11) v :: p (bound at T7453.hs:7:7) cast1 :: p -> a (bound at T7453.hs:7:1) -T7453.hs:16:33: error: - • Couldn't match expected type ‘t1’ with actual type ‘p’ +T7453.hs:15:15: error: + • Couldn't match type ‘t1’ with ‘p’ + Expected: () -> t1 + Actual: () -> p ‘t1’ is a rigid type variable bound by the type signature for: z :: forall t1. () -> t1 @@ -26,11 +40,21 @@ T7453.hs:16:33: error: ‘p’ is a rigid type variable bound by the inferred type of cast2 :: p -> t at T7453.hs:(13,1)-(16,33) - • In the first argument of ‘const’, namely ‘v’ - In the expression: const v - In an equation for ‘aux’: aux = const v + • In the expression: aux + In an equation for ‘z’: + z = aux + where + aux = const v + In an equation for ‘cast2’: + cast2 v + = z () + where + z :: () -> t + z = aux + where + aux = const v • Relevant bindings include - aux :: b -> t1 (bound at T7453.hs:16:21) + aux :: forall {b}. b -> p (bound at T7453.hs:16:21) z :: () -> t1 (bound at T7453.hs:15:11) v :: p (bound at T7453.hs:13:7) cast2 :: p -> t (bound at T7453.hs:13:1) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/061eee913a913b934845549ba90a4e8381454b1d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/061eee913a913b934845549ba90a4e8381454b1d 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 Fri Nov 27 01:50:53 2020 From: gitlab at gitlab.haskell.org (Moritz Angermann) Date: Thu, 26 Nov 2020 20:50:53 -0500 Subject: [Git][ghc/ghc][wip/angerman/aarch64-ncg] fix up rebase Message-ID: <5fc05b7d19841_86ce89fc5c47809c@gitlab.mail> Moritz Angermann pushed to branch wip/angerman/aarch64-ncg at Glasgow Haskell Compiler / GHC Commits: 0e7d6211 by Moritz Angermann at 2020-11-27T09:46:58+08:00 fix up rebase - - - - - 9 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Type.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/Platform.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -285,7 +285,10 @@ data CLabel deriving Eq instance Show CLabel where - show = showPprUnsafe . ppr + show = showPprUnsafe . pprDebugCLabel genericPlatform + +instance Outputable CLabel where + ppr = text . show isIdLabel :: CLabel -> Bool isIdLabel IdLabel{} = True @@ -411,7 +414,6 @@ data ForeignLabelSource deriving (Eq, Ord) - -- | For debugging problems with the CLabel representation. -- We can't make a Show instance for CLabel because lots of its components don't have instances. -- The regular Outputable instance only shows the label name, and not its other info. @@ -1484,7 +1486,7 @@ pprDynamicLinkerAsmLabel platform dllInfo ppLbl = _ -> panic "pprDynamicLinkerAsmLabel" | platformArch platform == ArchAArch64 - = ppr lbl + = ppLbl | platformArch platform == ArchX86_64 ===================================== compiler/GHC/Cmm/Type.hs ===================================== @@ -18,7 +18,6 @@ module GHC.Cmm.Type , rEP_StgEntCounter_allocd , ForeignHint(..) - , hintToWidth , Length , vec, vec2, vec4, vec8, vec16 @@ -322,10 +321,6 @@ data ForeignHint -- Used to give extra per-argument or per-result -- information needed by foreign calling conventions -hintToWidth :: ForeignHint -> Width -hintToWidth (NoHint w) = w -hintToWidth AddrHint = W64 -- XXX: this should be ptr size. -hintToWidth (SignedHint w) = w ------------------------------------------------------------------------- -- These don't really belong here, but I don't know where is best to ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -129,7 +129,7 @@ basicBlockCodeGen , [NatCmmDecl RawCmmStatics Instr]) basicBlockCodeGen block = do - -- config <- getConfig + config <- getConfig -- do -- traceM $ "-- --------------------------- basicBlockCodeGen --------------------------- --\n" -- ++ showSDocUnsafe (ppr block) @@ -139,7 +139,7 @@ basicBlockCodeGen block = do header_comment_instr = unitOL $ MULTILINE_COMMENT ( text "-- --------------------------- basicBlockCodeGen --------------------------- --\n" - $+$ ppr block + $+$ pdoc (ncgPlatform config) block ) -- Generate location directive dbg <- getDebugBlock (entryLabel block) @@ -279,7 +279,7 @@ stmtToInstrs bid stmt = do CmmUnwind _regs -> return nilOL - _ -> pprPanic "stmtToInstrs: statement should have been cps'd away" (ppr stmt) + _ -> pprPanic "stmtToInstrs: statement should have been cps'd away" (pdoc platform stmt) jumpRegs :: Platform -> [GlobalReg] -> [Reg] jumpRegs = undefined @@ -374,7 +374,9 @@ getFloatReg expr = do Any II64 code -> do tmp <- getNewRegNat FF64 return (tmp, FF64, code tmp) - Any _w _code -> pprPanic "can't do getFloatReg on" (ppr expr) + Any _w _code -> do + config <- getConfig + pprPanic "can't do getFloatReg on" (pdoc (ncgPlatform config) expr) -- can't do much for fixed. Fixed rep reg code -> return (reg, rep, code) @@ -479,8 +481,8 @@ getRegister' config plat expr (op, imm_code) <- litToImm' lit return (Any (floatFormat w) (\dst -> imm_code `snocOL` ANN (text $ show expr) (MOV (OpReg w dst) op))) - CmmFloat _f W8 -> pprPanic "getRegister' (CmmLit:CmmFloat), no support for bytes" (ppr expr) - CmmFloat _f W16 -> pprPanic "getRegister' (CmmLit:CmmFloat), no support for halfs" (ppr expr) + CmmFloat _f W8 -> pprPanic "getRegister' (CmmLit:CmmFloat), no support for bytes" (pdoc plat expr) + CmmFloat _f W16 -> pprPanic "getRegister' (CmmLit:CmmFloat), no support for halfs" (pdoc plat expr) CmmFloat f W32 -> do let word = castFloatToWord32 (fromRational f) :: Word32 half0 = fromIntegral (fromIntegral word :: Word16) @@ -505,8 +507,8 @@ getRegister' config plat expr , MOVK (OpReg W64 tmp) (OpImmShift (ImmInt half3) SLSL 48) , MOV (OpReg W64 dst) (OpReg W64 tmp) ])) - CmmFloat _f _w -> pprPanic "getRegister' (CmmLit:CmmFloat), unsupported float lit" (ppr expr) - CmmVec _ -> pprPanic "getRegister' (CmmLit:CmmVec): " (ppr expr) + CmmFloat _f _w -> pprPanic "getRegister' (CmmLit:CmmFloat), unsupported float lit" (pdoc plat expr) + CmmVec _ -> pprPanic "getRegister' (CmmLit:CmmVec): " (pdoc plat expr) CmmLabel _lbl -> do (op, imm_code) <- litToImm' lit let rep = cmmLitType plat lit @@ -528,15 +530,15 @@ getRegister' config plat expr (off_r, _off_format, off_code) <- getSomeReg $ CmmLit (CmmInt (fromIntegral off) width) return (Any format (\dst -> imm_code `appOL` off_code `snocOL` LDR format (OpReg (formatToWidth format) dst) op `snocOL` ADD (OpReg width dst) (OpReg width dst) (OpReg width off_r))) - CmmLabelDiffOff _ _ _ _ -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (ppr expr) - CmmBlock _ -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (ppr expr) - CmmHighStackMark -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (ppr expr) + CmmLabelDiffOff _ _ _ _ -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (pdoc plat expr) + CmmBlock _ -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (pdoc plat expr) + CmmHighStackMark -> pprPanic "getRegister' (CmmLit:CmmLabelOff): " (pdoc plat expr) CmmLoad mem rep -> do Amode addr addr_code <- getAmode plat mem let format = cmmTypeFormat rep return (Any format (\dst -> addr_code `snocOL` LDR format (OpReg (formatToWidth format) dst) (OpAddr addr))) CmmStackSlot _ _ - -> pprPanic "getRegister' (CmmStackSlot): " (ppr expr) + -> pprPanic "getRegister' (CmmStackSlot): " (pdoc plat expr) CmmReg reg -> return (Fixed (cmmTypeFormat (cmmRegType plat reg)) (getRegisterReg plat reg) @@ -577,7 +579,7 @@ getRegister' config plat expr -- Conversions MO_XX_Conv _from to -> swizzleRegisterRep (intFormat to) <$> getRegister e - _ -> pprPanic "getRegister' (monadic CmmMachOp):" (ppr expr) + _ -> pprPanic "getRegister' (monadic CmmMachOp):" (pdoc plat expr) where toImm W8 = (OpImm (ImmInt 7)) toImm W16 = (OpImm (ImmInt 15)) toImm W32 = (OpImm (ImmInt 31)) @@ -725,7 +727,7 @@ getRegister' config plat expr intOp w (\d x y -> toOL [ SDIV t x y, MSUB d t y x ]) -- Unsigned multiply/divide - MO_U_MulMayOflo _w -> unsupported expr + MO_U_MulMayOflo _w -> unsupportedP plat expr MO_U_Quot w -> intOp w (\d x y -> unitOL $ UDIV d x y) MO_U_Rem w -> withTempIntReg w $ \t -> intOp w (\d x y -> toOL [ UDIV t x y, MSUB d t y x ]) @@ -773,14 +775,17 @@ getRegister' config plat expr -- XXX - op -> pprPanic "getRegister' (unhandled dyadic CmmMachOp): " $ (pprMachOp op) <+> text "in" <+> (ppr expr) + op -> pprPanic "getRegister' (unhandled dyadic CmmMachOp): " $ (pprMachOp op) <+> text "in" <+> (pdoc plat expr) CmmMachOp _op _xs - -> pprPanic "getRegister' (variadic CmmMachOp): " (ppr expr) + -> pprPanic "getRegister' (variadic CmmMachOp): " (pdoc plat expr) where unsupported :: Outputable a => a -> b unsupported op = pprPanic "Unsupported op:" (ppr op) + unsupportedP :: OutputableP env a => env -> a -> b + unsupportedP platform op = pprPanic "Unsupported op:" (pdoc platform op) + is12bit :: Integer -> Bool is12bit i = (-1 `shiftL` 11) <= i && i < (1 `shiftL` 11) is16bit :: Integer -> Bool @@ -1307,7 +1312,6 @@ genCCall target dest_regs arg_regs bid = do -- No mor regs left to pass. Must pass on stack. passArguments pack [] [] ((r, format, hint, code_r):args) stackSpace accumRegs accumCode = do let w = formatToWidth format - -- w = hintToWidth hint bytes = widthInBits w `div` 8 space = if pack then bytes else 8 stackCode = code_r `snocOL` (ANN (text $ "Pass argument (size " ++ show w ++ ") on the stack: " ++ show r) $ STR format (OpReg w r) (OpAddr (AddrRegImm (regSingle 31) (ImmInt stackSpace)))) @@ -1316,7 +1320,6 @@ genCCall target dest_regs arg_regs bid = do -- Still have fpRegs left, but want to pass a GP argument. Must be passed on the stack then. passArguments pack [] fpRegs ((r, format, hint, code_r):args) stackSpace accumRegs accumCode | isIntFormat format = do let w = formatToWidth format - -- w = hintToWidth hint bytes = widthInBits w `div` 8 space = if pack then bytes else 8 stackCode = code_r `snocOL` (ANN (text $ "Pass argument (size " ++ show w ++ ") on the stack: " ++ show r) $ STR format (OpReg w r) (OpAddr (AddrRegImm (regSingle 31) (ImmInt stackSpace)))) @@ -1325,7 +1328,6 @@ genCCall target dest_regs arg_regs bid = do -- Still have gpRegs left, but want to pass a FP argument. Must be passed on the stack then. passArguments pack gpRegs [] ((r, format, hint, code_r):args) stackSpace accumRegs accumCode | isFloatFormat format = do let w = formatToWidth format - -- w = hintToWidth hint bytes = widthInBits w `div` 8 space = if pack then bytes else 8 stackCode = code_r `snocOL` (ANN (text $ "Pass argument (size " ++ show w ++ ") on the stack: " ++ show r) $ STR format (OpReg w r) (OpAddr (AddrRegImm (regSingle 31) (ImmInt stackSpace)))) @@ -1335,8 +1337,12 @@ genCCall target dest_regs arg_regs bid = do readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM ([Reg], InstrBlock) readResults _ _ [] accumRegs accumCode = return (accumRegs, accumCode) - readResults [] _ _ _ _ = pprPanic "genCCall, out of gp registers when reading results" (ppr target) - readResults _ [] _ _ _ = pprPanic "genCCall, out of fp registers when reading results" (ppr target) + readResults [] _ _ _ _ = do + platform <- getPlatform + pprPanic "genCCall, out of gp registers when reading results" (pdoc platform target) + readResults _ [] _ _ _ = do + platform <- getPlatform + pprPanic "genCCall, out of fp registers when reading results" (pdoc platform target) readResults (gpReg:gpRegs) (fpReg:fpRegs) (dst:dsts) accumRegs accumCode = do -- gp/fp reg -> dst platform <- getPlatform ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -81,9 +81,9 @@ pprNatCmmDecl config proc@(CmmProc top_info lbl _ (ListGraph blocks)) = pprLabel :: Platform -> CLabel -> SDoc pprLabel platform lbl = - pprGloblDecl lbl + pprGloblDecl platform lbl $$ pprTypeDecl platform lbl - $$ (ppr lbl <> char ':') + $$ (pdoc platform lbl <> char ':') pprAlign :: Platform -> Alignment -> SDoc pprAlign _platform alignment @@ -96,8 +96,7 @@ pprAlignForSection _platform _seg = text "\t.balign 8" -- always 8 instance Outputable Instr where - ppr instr = sdocWithDynFlags $ \dflags -> - pprInstr (targetPlatform dflags) instr + ppr = pprInstr genericPlatform -- | Print section header and appropriate alignment for that section. -- @@ -117,7 +116,7 @@ pprSectionAlign config sec@(Section seg _) = pprSizeDecl :: Platform -> CLabel -> SDoc pprSizeDecl platform lbl = if osElfTarget (platformOS platform) - then text "\t.size" <+> ppr lbl <> ptext (sLit ", .-") <> ppr lbl + then text "\t.size" <+> pdoc platform lbl <> ptext (sLit ", .-") <> pdoc platform lbl else empty pprBasicBlock :: NCGConfig -> LabelMap RawCmmStatics -> NatBasicBlock Instr @@ -186,15 +185,15 @@ pprBasicBlock config info_env (BasicBlock blockid instrs) pprDatas :: NCGConfig -> RawCmmStatics -> SDoc -- See note [emit-time elimination of static indirections] in "GHC.Cmm.CLabel". -pprDatas _config (CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) +pprDatas config (CmmStaticsRaw alias [CmmStaticLit (CmmLabel lbl), CmmStaticLit ind, _, _]) | lbl == mkIndStaticInfoLabel , let labelInd (CmmLabelOff l _) = Just l labelInd (CmmLabel l) = Just l labelInd _ = Nothing , Just ind' <- labelInd ind , alias `mayRedirectTo` ind' - = pprGloblDecl alias - $$ text ".equiv" <+> ppr alias <> comma <> ppr (CmmLabel ind') + = pprGloblDecl (ncgPlatform config) alias + $$ text ".equiv" <+> pdoc (ncgPlatform config) alias <> comma <> pdoc (ncgPlatform config) (CmmLabel ind') pprDatas config (CmmStaticsRaw lbl dats) = vcat (pprLabel platform lbl : map (pprData config) dats) @@ -213,10 +212,10 @@ pprData config (CmmUninitialised bytes) pprData config (CmmStaticLit lit) = pprDataItem config lit -pprGloblDecl :: CLabel -> SDoc -pprGloblDecl lbl +pprGloblDecl :: Platform -> CLabel -> SDoc +pprGloblDecl platform lbl | not (externallyVisibleCLabel lbl) = empty - | otherwise = text "\t.globl " <> ppr lbl + | otherwise = text "\t.globl " <> pdoc platform lbl -- See discussion in X86.Ppr -- for why this is necessary. Essentially we need to ensure that we never @@ -237,7 +236,7 @@ pprLabelType' platform lbl = pprTypeDecl :: Platform -> CLabel -> SDoc pprTypeDecl platform lbl = if osElfTarget (platformOS platform) && externallyVisibleCLabel lbl - then text ".type " <> ppr lbl <> ptext (sLit ", ") <> pprLabelType' platform lbl + then text ".type " <> pdoc platform lbl <> ptext (sLit ", ") <> pprLabelType' platform lbl else empty pprDataItem :: NCGConfig -> CmmLit -> SDoc @@ -248,18 +247,18 @@ pprDataItem config lit imm = litToImm lit - ppr_item II8 _ = [text "\t.byte\t" <> pprImm imm] - ppr_item II16 _ = [text "\t.short\t" <> pprImm imm] - ppr_item II32 _ = [text "\t.long\t" <> pprImm imm] - ppr_item II64 _ = [text "\t.quad\t" <> pprImm imm] + ppr_item II8 _ = [text "\t.byte\t" <> pprImm platform imm] + ppr_item II16 _ = [text "\t.short\t" <> pprImm platform imm] + ppr_item II32 _ = [text "\t.long\t" <> pprImm platform imm] + ppr_item II64 _ = [text "\t.quad\t" <> pprImm platform imm] ppr_item FF32 (CmmFloat r _) = let bs = floatToBytes (fromRational r) - in map (\b -> text "\t.byte\t" <> pprImm (ImmInt b)) bs + in map (\b -> text "\t.byte\t" <> pprImm platform (ImmInt b)) bs ppr_item FF64 (CmmFloat r _) = let bs = doubleToBytes (fromRational r) - in map (\b -> text "\t.byte\t" <> pprImm (ImmInt b)) bs + in map (\b -> text "\t.byte\t" <> pprImm platform (ImmInt b)) bs ppr_item _ _ = pprPanic "pprDataItem:ppr_item" (text $ show lit) @@ -279,24 +278,24 @@ floatToBytes f castFloatToWord8Array :: STUArray s Int Float -> ST s (STUArray s Int Word8) castFloatToWord8Array = U.castSTUArray -pprImm :: Imm -> SDoc -pprImm (ImmInt i) = int i -pprImm (ImmInteger i) = integer i -pprImm (ImmCLbl l) = ppr l -pprImm (ImmIndex l i) = ppr l <> char '+' <> int i -pprImm (ImmLit s) = s +pprImm :: Platform -> Imm -> SDoc +pprImm _ (ImmInt i) = int i +pprImm _ (ImmInteger i) = integer i +pprImm p (ImmCLbl l) = pdoc p l +pprImm p (ImmIndex l i) = pdoc p l <> char '+' <> int i +pprImm _ (ImmLit s) = s -- XXX: See pprIm below for why this is a bad idea! -pprImm (ImmFloat f) +pprImm _ (ImmFloat f) | f == 0 = text "wzr" | otherwise = float (fromRational f) -pprImm (ImmDouble d) +pprImm _ (ImmDouble d) | d == 0 = text "xzr" | otherwise = double (fromRational d) -pprImm (ImmConstantSum a b) = pprImm a <> char '+' <> pprImm b -pprImm (ImmConstantDiff a b) = pprImm a <> char '-' - <> lparen <> pprImm b <> rparen +pprImm p (ImmConstantSum a b) = pprImm p a <> char '+' <> pprImm p b +pprImm p (ImmConstantDiff a b) = pprImm p a <> char '-' + <> lparen <> pprImm p b <> rparen -- aarch64 GNU as uses // for comments. @@ -309,8 +308,8 @@ asmDoubleslashComment c = whenPprDebug $ text "//" <+> c asmMultilineComment :: SDoc -> SDoc asmMultilineComment c = whenPprDebug $ text "/*" $+$ c $+$ text "*/" -pprIm :: Imm -> SDoc -pprIm im = case im of +pprIm :: Platform -> Imm -> SDoc +pprIm platform im = case im of ImmInt i -> char '#' <> int i ImmInteger i -> char '#' <> integer i @@ -331,8 +330,8 @@ pprIm im = case im of ImmDouble d | d == 0 -> text "xzr" ImmDouble d -> char '#' <> double (fromRational d) -- = pseudo instruction! - ImmCLbl l -> char '=' <> ppr l - ImmIndex l o -> text "[=" <> ppr l <> comma <+> char '#' <> int o <> char ']' + ImmCLbl l -> char '=' <> pdoc platform l + ImmIndex l o -> text "[=" <> pdoc platform l <> comma <+> char '#' <> int o <> char ']' _ -> panic "AArch64.pprIm" pprExt :: ExtMode -> SDoc @@ -351,17 +350,17 @@ pprShift SLSR = text "lsr" pprShift SASR = text "asr" pprShift SROR = text "ror" -pprOp :: Operand -> SDoc -pprOp op = case op of +pprOp :: Platform -> Operand -> SDoc +pprOp plat op = case op of OpReg w r -> pprReg w r OpRegExt w r x 0 -> pprReg w r <> comma <+> pprExt x OpRegExt w r x i -> pprReg w r <> comma <+> pprExt x <> comma <+> char '#' <> int i OpRegShift w r s i -> pprReg w r <> comma <+> pprShift s <> comma <+> char '#' <> int i - OpImm im -> pprIm im - OpImmShift im s i -> pprIm im <> comma <+> pprShift s <+> char '#' <> int i + OpImm im -> pprIm plat im + OpImmShift im s i -> pprIm plat im <> comma <+> pprShift s <+> char '#' <> int i -- XXX: Address compuation always use registers as 64bit -- is this correct? OpAddr (AddrRegReg r1 r2) -> char '[' <+> pprReg W64 r1 <> comma <+> pprReg W64 r2 <+> char ']' - OpAddr (AddrRegImm r1 im) -> char '[' <+> pprReg W64 r1 <> comma <+> pprImm im <+> char ']' + OpAddr (AddrRegImm r1 im) -> char '[' <+> pprReg W64 r1 <> comma <+> pprImm plat im <+> char ']' OpAddr (AddrReg r1) -> char '[' <+> pprReg W64 r1 <+> char ']' pprReg :: Width -> Reg -> SDoc @@ -426,75 +425,75 @@ pprInstr platform instr = case instr of -- AArch64 Instruction Set -- 1. Arithmetic Instructions ------------------------------------------------ ADD o1 o2 o3 - | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> text "\tfadd" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - | otherwise -> text "\tadd" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - CMN o1 o2 -> text "\tcmn" <+> pprOp o1 <> comma <+> pprOp o2 + | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> text "\tfadd" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + | otherwise -> text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + CMN o1 o2 -> text "\tcmn" <+> pprOp platform o1 <> comma <+> pprOp platform o2 CMP o1 o2 - | isFloatOp o1 && isFloatOp o2 -> text "\tfcmp" <+> pprOp o1 <> comma <+> pprOp o2 - | otherwise -> text "\tcmp" <+> pprOp o1 <> comma <+> pprOp o2 - MSUB o1 o2 o3 o4 -> text "\tmsub" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 <> comma <+> pprOp o4 + | isFloatOp o1 && isFloatOp o2 -> text "\tfcmp" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + | otherwise -> text "\tcmp" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + MSUB o1 o2 o3 o4 -> text "\tmsub" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 <> comma <+> pprOp platform o4 MUL o1 o2 o3 - | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> text "\tfmul" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - | otherwise -> text "\tmul" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 + | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> text "\tfmul" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + | otherwise -> text "\tmul" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 NEG o1 o2 - | isFloatOp o1 && isFloatOp o2 -> text "\tfneg" <+> pprOp o1 <> comma <+> pprOp o2 - | otherwise -> text "\tneg" <+> pprOp o1 <> comma <+> pprOp o2 + | isFloatOp o1 && isFloatOp o2 -> text "\tfneg" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + | otherwise -> text "\tneg" <+> pprOp platform o1 <> comma <+> pprOp platform o2 SDIV o1 o2 o3 | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 - -> text "\tfdiv" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - SDIV o1 o2 o3 -> text "\tsdiv" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 + -> text "\tfdiv" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + SDIV o1 o2 o3 -> text "\tsdiv" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 SUB o1 o2 o3 - | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> text "\tfsub" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - | otherwise -> text "\tsub" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - UDIV o1 o2 o3 -> text "\tudiv" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 + | isFloatOp o1 && isFloatOp o2 && isFloatOp o3 -> text "\tfsub" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + | otherwise -> text "\tsub" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + UDIV o1 o2 o3 -> text "\tudiv" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 -- 2. Bit Manipulation Instructions ------------------------------------------ - SBFM o1 o2 o3 o4 -> text "\tsbfm" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 <> comma <+> pprOp o4 - UBFM o1 o2 o3 o4 -> text "\tubfm" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 <> comma <+> pprOp o4 + SBFM o1 o2 o3 o4 -> text "\tsbfm" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 <> comma <+> pprOp platform o4 + UBFM o1 o2 o3 o4 -> text "\tubfm" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 <> comma <+> pprOp platform o4 -- 3. Logical and Move Instructions ------------------------------------------ - AND o1 o2 o3 -> text "\tand" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - ANDS o1 o2 o3 -> text "\tands" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - ASR o1 o2 o3 -> text "\tasr" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - BIC o1 o2 o3 -> text "\tbic" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - BICS o1 o2 o3 -> text "\tbics" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - EON o1 o2 o3 -> text "\teon" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - EOR o1 o2 o3 -> text "\teor" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - LSL o1 o2 o3 -> text "\tlsl" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - LSR o1 o2 o3 -> text "\tlsr" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 + AND o1 o2 o3 -> text "\tand" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + ANDS o1 o2 o3 -> text "\tands" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + ASR o1 o2 o3 -> text "\tasr" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + BIC o1 o2 o3 -> text "\tbic" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + BICS o1 o2 o3 -> text "\tbics" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + EON o1 o2 o3 -> text "\teon" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + EOR o1 o2 o3 -> text "\teor" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + LSL o1 o2 o3 -> text "\tlsl" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + LSR o1 o2 o3 -> text "\tlsr" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 MOV o1 o2 - | isFloatOp o1 || isFloatOp o2 -> text "\tfmov" <+> pprOp o1 <> comma <+> pprOp o2 - | otherwise -> text "\tmov" <+> pprOp o1 <> comma <+> pprOp o2 - MOVK o1 o2 -> text "\tmovk" <+> pprOp o1 <> comma <+> pprOp o2 - MVN o1 o2 -> text "\tmvn" <+> pprOp o1 <> comma <+> pprOp o2 - ORN o1 o2 o3 -> text "\torn" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - ORR o1 o2 o3 -> text "\torr" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - ROR o1 o2 o3 -> text "\tror" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - TST o1 o2 -> text "\ttst" <+> pprOp o1 <> comma <+> pprOp o2 + | isFloatOp o1 || isFloatOp o2 -> text "\tfmov" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + | otherwise -> text "\tmov" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + MOVK o1 o2 -> text "\tmovk" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + MVN o1 o2 -> text "\tmvn" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + ORN o1 o2 o3 -> text "\torn" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + ORR o1 o2 o3 -> text "\torr" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + ROR o1 o2 o3 -> text "\tror" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + TST o1 o2 -> text "\ttst" <+> pprOp platform o1 <> comma <+> pprOp platform o2 -- 4. Branch Instructions ---------------------------------------------------- J t -> pprInstr platform (B t) - B (TBlock bid) -> text "\tb" <+> ppr (mkLocalBlockLabel (getUnique bid)) - B (TLabel lbl) -> text "\tb" <+> ppr lbl + B (TBlock bid) -> text "\tb" <+> pdoc platform (mkLocalBlockLabel (getUnique bid)) + B (TLabel lbl) -> text "\tb" <+> pdoc platform lbl B (TReg r) -> text "\tbr" <+> pprReg W64 r - BL (TBlock bid) _ _ -> text "\tbl" <+> ppr (mkLocalBlockLabel (getUnique bid)) - BL (TLabel lbl) _ _ -> text "\tbl" <+> ppr lbl + BL (TBlock bid) _ _ -> text "\tbl" <+> pdoc platform (mkLocalBlockLabel (getUnique bid)) + BL (TLabel lbl) _ _ -> text "\tbl" <+> pdoc platform lbl BL (TReg r) _ _ -> text "\tblr" <+> pprReg W64 r - BCOND c (TBlock bid) -> text "\t" <> pprBcond c <+> ppr (mkLocalBlockLabel (getUnique bid)) - BCOND c (TLabel lbl) -> text "\t" <> pprBcond c <+> ppr lbl + BCOND c (TBlock bid) -> text "\t" <> pprBcond c <+> pdoc platform (mkLocalBlockLabel (getUnique bid)) + BCOND c (TLabel lbl) -> text "\t" <> pprBcond c <+> pdoc platform lbl BCOND _ (TReg _) -> panic "AArch64.ppr: No conditional branching to registers!" -- 5. Atomic Instructions ---------------------------------------------------- -- 6. Conditional Instructions ----------------------------------------------- - CSET o c -> text "\tcset" <+> pprOp o <> comma <+> pprCond c + CSET o c -> text "\tcset" <+> pprOp platform o <> comma <+> pprCond c - CBZ o (TBlock bid) -> text "\tcbz" <+> pprOp o <> comma <+> ppr (mkLocalBlockLabel (getUnique bid)) - CBZ o (TLabel lbl) -> text "\tcbz" <+> pprOp o <> comma <+> ppr lbl + CBZ o (TBlock bid) -> text "\tcbz" <+> pprOp platform o <> comma <+> pdoc platform (mkLocalBlockLabel (getUnique bid)) + CBZ o (TLabel lbl) -> text "\tcbz" <+> pprOp platform o <> comma <+> pdoc platform lbl CBZ _ (TReg _) -> panic "AArch64.ppr: No conditional (cbz) branching to registers!" - CBNZ o (TBlock bid) -> text "\tcbnz" <+> pprOp o <> comma <+> ppr (mkLocalBlockLabel (getUnique bid)) - CBNZ o (TLabel lbl) -> text "\tcbnz" <+> pprOp o <> comma <+> ppr lbl + CBNZ o (TBlock bid) -> text "\tcbnz" <+> pprOp platform o <> comma <+> pdoc platform (mkLocalBlockLabel (getUnique bid)) + CBNZ o (TLabel lbl) -> text "\tcbnz" <+> pprOp platform o <> comma <+> pdoc platform lbl CBNZ _ (TReg _) -> panic "AArch64.ppr: No conditional (cbnz) branching to registers!" -- 7. Load and Store Instructions -------------------------------------------- @@ -502,82 +501,82 @@ pprInstr platform instr = case instr of -- address. Not observing the correct size when loading will lead -- inevitably to crashes. STR _f o1@(OpReg W8 (RegReal (RealRegSingle i))) o2 | i < 32 -> - text "\tstrb" <+> pprOp o1 <> comma <+> pprOp o2 + text "\tstrb" <+> pprOp platform o1 <> comma <+> pprOp platform o2 STR _f o1@(OpReg W16 (RegReal (RealRegSingle i))) o2 | i < 32 -> - text "\tstrh" <+> pprOp o1 <> comma <+> pprOp o2 - STR _f o1 o2 -> text "\tstr" <+> pprOp o1 <> comma <+> pprOp o2 + text "\tstrh" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + STR _f o1 o2 -> text "\tstr" <+> pprOp platform o1 <> comma <+> pprOp platform o2 #if defined(darwin_HOST_OS) LDR _f o1 (OpImm (ImmIndex lbl' off)) | Just (_info, lbl) <- dynamicLinkerLabelInfo lbl' -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl <> text "@gotpage" $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> ppr lbl <> text "@gotpageoff" <> text "]" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpage" $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpageoff" <> text "]" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. LDR _f o1 (OpImm (ImmIndex lbl off)) | isForeignLabel lbl -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl <> text "@gotpage" $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> ppr lbl <> text "@gotpageoff" <> text "]" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpage" $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpageoff" <> text "]" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. LDR _f o1 (OpImm (ImmIndex lbl off)) -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl <> text "@page" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> ppr lbl <> text "@pageoff" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@page" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@pageoff" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. LDR _f o1 (OpImm (ImmCLbl lbl')) | Just (_info, lbl) <- dynamicLinkerLabelInfo lbl' -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl <> text "@gotpage" $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> ppr lbl <> text "@gotpageoff" <> text "]" + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpage" $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpageoff" <> text "]" LDR _f o1 (OpImm (ImmCLbl lbl)) | isForeignLabel lbl -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl <> text "@gotpage" $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> ppr lbl <> text "@gotpageoff" <> text "]" + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpage" $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@gotpageoff" <> text "]" LDR _f o1 (OpImm (ImmCLbl lbl)) -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl <> text "@page" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> ppr lbl <> text "@pageoff" + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@page" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> pdoc platform lbl <> text "@pageoff" #else LDR _f o1 (OpImm (ImmIndex lbl' off)) | Just (_info, lbl) <- dynamicLinkerLabelInfo lbl' -> - text "\tadrp" <+> pprOp o1 <> comma <+> text ":got:" <> ppr lbl $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> text ":got_lo12:" <> ppr lbl <> text "]" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. + text "\tadrp" <+> pprOp platform o1 <> comma <+> text ":got:" <> pdoc platform lbl $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> text ":got_lo12:" <> pdoc platform lbl <> text "]" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. LDR _f o1 (OpImm (ImmIndex lbl off)) | isForeignLabel lbl -> - text "\tadrp" <+> pprOp o1 <> comma <+> text ":got:" <> ppr lbl $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> text ":got_lo12:" <> ppr lbl <> text "]" $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. + text "\tadrp" <+> pprOp platform o1 <> comma <+> text ":got:" <> pdoc platform lbl $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> text ":got_lo12:" <> pdoc platform lbl <> text "]" $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. LDR _f o1 (OpImm (ImmIndex lbl off)) -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> text ":lo12:" <> ppr lbl $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> text ":lo12:" <> pdoc platform lbl $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> char '#' <> int off -- XXX: check that off is in 12bits. LDR _f o1 (OpImm (ImmCLbl lbl')) | Just (_info, lbl) <- dynamicLinkerLabelInfo lbl' -> - text "\tadrp" <+> pprOp o1 <> comma <+> text ":got:" <> ppr lbl $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> text ":got_lo12:" <> ppr lbl <> text "]" + text "\tadrp" <+> pprOp platform o1 <> comma <+> text ":got:" <> pdoc platform lbl $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> text ":got_lo12:" <> pdoc platform lbl <> text "]" LDR _f o1 (OpImm (ImmCLbl lbl)) | isForeignLabel lbl -> - text "\tadrp" <+> pprOp o1 <> comma <+> text ":got:" <> ppr lbl $$ - text "\tldr" <+> pprOp o1 <> comma <+> text "[" <> pprOp o1 <> comma <+> text ":got_lo12:" <> ppr lbl <> text "]" + text "\tadrp" <+> pprOp platform o1 <> comma <+> text ":got:" <> pdoc platform lbl $$ + text "\tldr" <+> pprOp platform o1 <> comma <+> text "[" <> pprOp platform o1 <> comma <+> text ":got_lo12:" <> pdoc platform lbl <> text "]" LDR _f o1 (OpImm (ImmCLbl lbl)) -> - text "\tadrp" <+> pprOp o1 <> comma <+> ppr lbl $$ - text "\tadd" <+> pprOp o1 <> comma <+> pprOp o1 <> comma <+> text ":lo12:" <> ppr lbl + text "\tadrp" <+> pprOp platform o1 <> comma <+> pdoc platform lbl $$ + text "\tadd" <+> pprOp platform o1 <> comma <+> pprOp platform o1 <> comma <+> text ":lo12:" <> pdoc platform lbl #endif LDR _f o1@(OpReg W8 (RegReal (RealRegSingle i))) o2 | i < 32 -> - text "\tldrsb" <+> pprOp o1 <> comma <+> pprOp o2 + text "\tldrsb" <+> pprOp platform o1 <> comma <+> pprOp platform o2 LDR _f o1@(OpReg W16 (RegReal (RealRegSingle i))) o2 | i < 32 -> - text "\tldrsh" <+> pprOp o1 <> comma <+> pprOp o2 - LDR _f o1 o2 -> text "\tldr" <+> pprOp o1 <> comma <+> pprOp o2 + text "\tldrsh" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + LDR _f o1 o2 -> text "\tldr" <+> pprOp platform o1 <> comma <+> pprOp platform o2 - STP _f o1 o2 o3 -> text "\tstp" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 - LDP _f o1 o2 o3 -> text "\tldp" <+> pprOp o1 <> comma <+> pprOp o2 <> comma <+> pprOp o3 + STP _f o1 o2 o3 -> text "\tstp" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + LDP _f o1 o2 o3 -> text "\tldp" <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 -- 8. Synchronization Instructions ------------------------------------------- DMBSY -> text "\tdmb sy" -- 8. Synchronization Instructions ------------------------------------------- - FCVT o1 o2 -> text "\tfcvt" <+> pprOp o1 <> comma <+> pprOp o2 - SCVTF o1 o2 -> text "\tscvtf" <+> pprOp o1 <> comma <+> pprOp o2 - FCVTZS o1 o2 -> text "\tfcvtzs" <+> pprOp o1 <> comma <+> pprOp o2 + FCVT o1 o2 -> text "\tfcvt" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + SCVTF o1 o2 -> text "\tscvtf" <+> pprOp platform o1 <> comma <+> pprOp platform o2 + FCVTZS o1 o2 -> text "\tfcvtzs" <+> pprOp platform o1 <> comma <+> pprOp platform o2 pprBcond :: Cond -> SDoc pprBcond c = text "b." <> pprCond c ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -257,11 +257,11 @@ howToAccessLabel config _arch OSMinGW32 _kind lbl -- is enough for ~64MB of range. Anything else will need to go through a veneer, -- which is the job of the linker to build. We might only want to lookup -- Data References through the GOT. -howToAccessLabel config ArchAArch64 _os this_mod _kind lbl +howToAccessLabel config ArchAArch64 _os _kind lbl | not (ncgExternalDynamicRefs config) = AccessDirectly - | labelDynamic config this_mod lbl + | labelDynamic config lbl = AccessViaSymbolPtr | otherwise ===================================== compiler/GHC/Linker/Static.hs ===================================== @@ -224,7 +224,7 @@ linkBinary' staticLink dflags o_files dep_units = do not staticLink && (platformOS platform == OSDarwin) && case platformArch platform of - ArchX86 -> True + ArchX86 -> True ArchX86_64 -> True ArchARM {} -> True ArchAArch64 -> True ===================================== compiler/GHC/Platform.hs ===================================== @@ -35,6 +35,7 @@ module GHC.Platform , platformSOName , platformHsSOName , platformSOExt + , genericPlatform ) where @@ -66,11 +67,26 @@ data Platform = Platform -- ^ Determines whether we will be compiling info tables that reside just -- before the entry code, or with an indirection to the entry code. See -- TABLES_NEXT_TO_CODE in includes/rts/storage/InfoTables.h. - , platformConstants :: !PlatformConstants + , platformConstants :: PlatformConstants -- ^ Constants such as structure offsets, type sizes, etc. } deriving (Read, Show, Eq) +genericPlatform :: Platform +genericPlatform = Platform + { platformArchOS = ArchOS ArchX86_64 OSLinux + , platformWordSize = PW8 + , platformByteOrder = LittleEndian + , platformUnregisterised = False + , platformHasGnuNonexecStack = False + , platformHasIdentDirective = False + , platformHasSubsectionsViaSymbols= False + , platformIsCrossCompiling = False + , platformLeadingUnderscore = False + , platformTablesNextToCode = True + , platformConstants = error "No PlatformConstants" + } + data PlatformWordSize = PW4 -- ^ A 32-bit platform | PW8 -- ^ A 64-bit platform ===================================== compiler/GHC/StgToCmm/Foreign.hs ===================================== @@ -108,7 +108,7 @@ cgForeignCall (CCall (CCallSpec target cconv safety)) typ stg_args res_ty [] -> panic "cgForeignCall []" fc = ForeignConvention cconv arg_hints res_hints CmmMayReturn call_target = ForeignTarget cmm_target fc - + {- ; forM cmm_args $ \arg -> case arg of (CmmLit _, AddrHint) -> pure () (CmmReg _, AddrHint) -> pure () @@ -121,7 +121,7 @@ cgForeignCall (CCall (CCallSpec target cconv safety)) typ stg_args res_ty (CmmReg (CmmLocal (LocalReg _ ty)), SignedHint w) | isBitsType ty && typeWidth ty == w -> pure () (CmmReg (CmmLocal (LocalReg _ ty)), NoHint w) | isBitsType ty && typeWidth ty == w -> pure () arg -> traceM $ show cmm_args ++ "\n\t" ++ show arg ++ "; sized don't match! in" ++ "\n\t" ++ showPprUnsafe (ppr cmm_target) - + -} -- we want to emit code for the call, and then emitReturn. -- However, if the sequel is AssignTo, we shortcut a little -- and generate a foreign call that assigns the results ===================================== compiler/ghc.cabal.in ===================================== @@ -206,6 +206,13 @@ Library GHC.Cmm.Switch GHC.Cmm.Switch.Implement GHC.CmmToAsm + GHC.CmmToAsm.AArch64 + GHC.CmmToAsm.AArch64.CodeGen + GHC.CmmToAsm.AArch64.Cond + GHC.CmmToAsm.AArch64.Instr + GHC.CmmToAsm.AArch64.Ppr + GHC.CmmToAsm.AArch64.RegInfo + GHC.CmmToAsm.AArch64.Regs GHC.CmmToAsm.BlockLayout GHC.CmmToAsm.CFG GHC.CmmToAsm.CFG.Dominators @@ -237,6 +244,7 @@ Library GHC.CmmToAsm.Reg.Graph.TrivColorable GHC.CmmToAsm.Reg.Graph.X86 GHC.CmmToAsm.Reg.Linear + GHC.CmmToAsm.Reg.Linear.AArch64 GHC.CmmToAsm.Reg.Linear.Base GHC.CmmToAsm.Reg.Linear.FreeRegs GHC.CmmToAsm.Reg.Linear.JoinToTargets View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e7d62114131b8eef8cbc5bd9477f81672e72e9d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e7d62114131b8eef8cbc5bd9477f81672e72e9d 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 Fri Nov 27 03:16:27 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 22:16:27 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/quick-windows-ci Message-ID: <5fc06f8b6e29f_86c3fc6a6528e7c492854@gitlab.mail> Ben Gamari pushed new branch wip/quick-windows-ci at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/quick-windows-ci 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 Fri Nov 27 03:19:49 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 22:19:49 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/quick-windows-ci Message-ID: <5fc07055c1100_86c111d4a004930dd@gitlab.mail> Ben Gamari deleted branch wip/quick-windows-ci at Glasgow Haskell Compiler / GHC -- 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 Fri Nov 27 03:21:15 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 26 Nov 2020 22:21:15 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: Move core flattening algorithm to Core.Unify Message-ID: <5fc070aba78eb_86c113a5b2c4971ed@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: d43eeeac by Richard Eisenberg at 2020-11-26T12:45:11-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into GHC.Core.Map.Type and GHC.Core.Map.Expr, in order to avoid module import cycles with GHC.Core. - - - - - cdeabd19 by Richard Eisenberg at 2020-11-26T12:45:12-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - 22bdbb4a by Richard Eisenberg at 2020-11-26T12:46:35-05:00 Remove flattening variables This patch redesigns the flattener to simplify type family applications directly instead of using flattening meta-variables and skolems. The key new innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS is either a type variable or exactly-saturated type family application; either can now be rewritten using a CEqCan constraint in the inert set. Because the flattener no longer reduces all type family applications to variables, there was some performance degradation if a lengthy type family application is now flattened over and over (not making progress). To compensate, this patch contains some extra optimizations in the flattener, leading to a number of performance improvements. Close #18875. Close #18910. There are many extra parts of the compiler that had to be affected in writing this patch: * The family-application cache (formerly the flat-cache) sometimes stores coercions built from Given inerts. When these inerts get kicked out, we must kick out from the cache as well. (This was, I believe, true previously, but somehow never caused trouble.) Kicking out from the cache requires adding a filterTM function to TrieMap. * This patch obviates the need to distinguish "blocking" coercion holes from non-blocking ones (which, previously, arose from CFunEqCans). There is thus some simplification around coercion holes. * Extra commentary throughout parts of the code I read through, to preserve the knowledge I gained while working. * A change in the pure unifier around unifying skolems with other types. Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented in Note [Binding when looking up instances] in GHC.Core.InstEnv. * Some more use of MCoercion where appropriate. * Previously, class-instance lookup automatically noticed that e.g. C Int was a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to a variable. Now, a little more care must be taken around checking for unifying instances. * Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly, because (=>) is not a tycon in Haskell. Fixed now, but there are some knock-on changes in e.g. TrieMap code and in the canonicaliser. * New function anyFreeVarsOf{Type,Co} to check whether a free variable satisfies a certain predicate. * Type synonyms now remember whether or not they are "forgetful"; a forgetful synonym drops at least one argument. This is useful when flattening; see flattenView. * The pattern-match completeness checker invokes the solver. This invocation might need to look through newtypes when checking representational equality. Thus, the desugarer needs to keep track of the in-scope variables to know what newtype constructors are in scope. I bet this bug was around before but never noticed. * Extra-constraints wildcards are no longer simplified before printing. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. * Whether or not there are Given equalities has become slightly subtler. See the new HasGivenEqs datatype. * Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical explains a significant new wrinkle in the new approach. * See Note [What might match later?] in GHC.Tc.Solver.Interact, which explains the fix to #18910. Though I (Richard) did the implementation, Simon PJ was very involved in design and review. This updates the Haddock submodule to avoid #18932 by adding a type signature. ------------------------- Metric Decrease: T12227 T5030 T9872a T9872b T9872c Metric Increase: T9872d ------------------------- - - - - - cbdf6734 by Richard Eisenberg at 2020-11-26T12:47:30-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - dfd4b65d by Andreas Klebinger at 2020-11-26T22:21:03-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - 544b8f3e by Sylvain Henry at 2020-11-26T22:21:04-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - 13866c4f by Tim Barnes at 2020-11-26T22:21:05-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 42cc1a47 by Ben Gamari at 2020-11-26T22:21:05-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - db285f59 by Matthew Pickering at 2020-11-26T22:21:06-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - 4d7260cf by Matthew Pickering at 2020-11-26T22:21:06-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 2548c2c0 by Ben Gamari at 2020-11-26T22:21:06-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 7ac3b271 by Andreas Klebinger at 2020-11-26T22:21:07-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - 30 changed files: - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - + compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map.hs → compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/TyCon/Env.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/Data/Bag.hs - compiler/GHC/Data/Maybe.hs - compiler/GHC/Data/TrieMap.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore/Monad.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Types.hs - compiler/GHC/Iface/Ext/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e3555cc9c2a9f5246895f151259fd2a81621f38...7ac3b27159e7c47b924d20418ee5c2c9f4fdce7f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e3555cc9c2a9f5246895f151259fd2a81621f38...7ac3b27159e7c47b924d20418ee5c2c9f4fdce7f 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 Fri Nov 27 03:21:28 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 22:21:28 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] nonmoving: Ensure that evacuated large objects are marked Message-ID: <5fc070b834c8a_86c11450e285051d0@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: d13e4c8f by GHC GitLab CI at 2020-11-26T22:19:55-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 2 changed files: - rts/sm/Evac.c - rts/sm/NonMoving.c Changes: ===================================== rts/sm/Evac.c ===================================== @@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) // // However, if we are in a deadlock detection GC then we disable aging // so there is no need. + // + // See Note [Non-moving GC: Marking evacuated objects]. if (major_gc && !deadlock_detect_gc) markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to); return to; @@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ +/* + * Note [Non-moving GC: Marking evacuated objects] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * When the non-moving collector is in use we must be careful to ensure that any + * references to objects in the non-moving generation from younger generations + * are pushed to the mark queue. + * + * In particular we need to ensure that we handle newly-promoted objects are + * correctly marked. For instance, consider this case: + * + * generation 0 generation 1 + * ────────────── ────────────── + * + * ┌───────┐ + * ┌───────┐ │ A │ + * │ B │ ◁────────────────────────── │ │ + * │ │ ──┬─────────────────┐ └───────┘ + * └───────┘ ┆ after GC │ + * ┆ │ + * ┌───────┐ ┆ before GC │ ┌───────┐ + * │ C │ ◁┄┘ └─────▷ │ C' │ + * │ │ │ │ + * └───────┘ └───────┘ + * + * + * In this case object C started off in generation 0 and was evacuated into + * generation 1 during the preparatory GC. However, the only reference to C' + * is from B, which lives in the generation 0 (via aging); this reference will + * not be visible to the concurrent non-moving collector (which can only + * traverse the generation 1 heap). Consequently, upon evacuating C we need to + * ensure that C' is added to the update remembered set as we know that it will + * continue to be reachable via B (which is assumed to be reachable as it lives + * in a younger generation). + * + * Where this happens depends upon the type of the object (e.g. C'): + * + * - In the case of "normal" small heap-allocated objects this happens in + * alloc_for_copy. + * - In the case of compact region this happens in evacuate_compact. + * - In the case of large objects this happens in evacuate_large. + * + * See also Note [Aging under the non-moving collector] in NonMoving.c. + * + */ + /* size is in words */ STATIC_INLINE GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, @@ -351,6 +399,9 @@ evacuate_large(StgPtr p) __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL); if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, p); } initBdescr(bd, new_gen, new_gen->to); @@ -505,6 +556,9 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -690,13 +744,6 @@ loop: */ if (flags & BF_LARGE) { evacuate_large((P_)q); - - // We may have evacuated the block to the nonmoving generation. If so - // we need to make sure it is added to the mark queue since the only - // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { - markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); - } return; } ===================================== rts/sm/NonMoving.c ===================================== @@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock; * - Note [Aging under the non-moving collector] (NonMoving.c) describes how * we accommodate aging * + * - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how + * non-moving objects reached by evacuate() are marked, which is necessary + * due to aging. + * * - Note [Large objects in the non-moving collector] (NonMovingMark.c) * describes how we track large objects. * @@ -317,6 +321,8 @@ Mutex concurrent_coll_finished_lock; * * The non-moving collector will come to C in the mark queue and mark it. * + * The implementation details of this are described in Note [Non-moving GC: + * Marking evacuated objects] in Evac.c. * * Note [Deadlock detection under the non-moving collector] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d13e4c8f335ab8cac8b68790686f79f1c9c2b5b0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d13e4c8f335ab8cac8b68790686f79f1c9c2b5b0 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 Fri Nov 27 03:26:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 22:26:44 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 7 commits: rts/Messages: Add missing write barrier in THROWTO message update Message-ID: <5fc071f427da0_86ce89fc5c508427@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: ced673a4 by GHC GitLab CI at 2020-11-27T03:26:18+00:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - cf1792ec by GHC GitLab CI at 2020-11-27T03:26:18+00:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 142e8844 by GHC GitLab CI at 2020-11-27T03:26:18+00:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - ec086bfa by GHC GitLab CI at 2020-11-27T03:26:18+00:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - b62bd8f8 by GHC GitLab CI at 2020-11-27T03:26:18+00:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 75578ed3 by Ben Gamari at 2020-11-27T03:26:18+00:00 nonmoving: Add reference to Ueno 2016 - - - - - 4f77bcc8 by GHC GitLab CI at 2020-11-27T03:26:18+00:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 8 changed files: - rts/Messages.c - rts/Messages.h - rts/PrimOps.cmm - rts/RaiseAsync.c - rts/Updates.h - rts/posix/OSThreads.c - rts/sm/Evac.c - rts/sm/NonMoving.c Changes: ===================================== rts/Messages.c ===================================== @@ -97,7 +97,7 @@ loop: case THROWTO_SUCCESS: { // this message is done StgTSO *source = t->source; - doneWithMsgThrowTo(t); + doneWithMsgThrowTo(cap, t); tryWakeupThread(cap, source); break; } ===================================== rts/Messages.h ===================================== @@ -23,8 +23,16 @@ void sendMessage (Capability *from_cap, Capability *to_cap, Message *msg); #include "SMPClosureOps.h" INLINE_HEADER void -doneWithMsgThrowTo (MessageThrowTo *m) +doneWithMsgThrowTo (Capability *cap, MessageThrowTo *m) { + // The message better be locked + ASSERT(m->header.info == &stg_WHITEHOLE_info); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + updateRemembSetPushClosure(cap, (StgClosure *) m->link); + updateRemembSetPushClosure(cap, (StgClosure *) m->source); + updateRemembSetPushClosure(cap, (StgClosure *) m->target); + updateRemembSetPushClosure(cap, (StgClosure *) m->exception); + } OVERWRITING_CLOSURE((StgClosure*)m); unlockClosure((StgClosure*)m, &stg_MSG_NULL_info); LDV_RECORD_CREATE(m); ===================================== rts/PrimOps.cmm ===================================== @@ -227,6 +227,21 @@ stg_shrinkSmallMutableArrayzh ( gcptr mba, W_ new_size ) { ASSERT(new_size <= StgSmallMutArrPtrs_ptrs(mba)); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + // Ensure that the elements we are about to shrink out of existence + // remain visible to the non-moving collector. + W_ p, end; + p = mba + SIZEOF_StgSmallMutArrPtrs + WDS(new_size); + end = mba + SIZEOF_StgSmallMutArrPtrs + WDS(StgSmallMutArrPtrs_ptrs(mba)); +again: + ccall updateRemembSetPushClosure_(BaseReg "ptr", + W_[p] "ptr"); + if (p < end) { + p = p + SIZEOF_W; + goto again; + } + } + OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) + new_size)); StgSmallMutArrPtrs_ptrs(mba) = new_size; ===================================== rts/RaiseAsync.c ===================================== @@ -336,7 +336,7 @@ check_target: } // nobody else can wake up this TSO after we claim the message - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); raiseAsync(cap, target, msg->exception, false, NULL); return THROWTO_SUCCESS; @@ -580,7 +580,7 @@ maybePerformBlockedException (Capability *cap, StgTSO *tso) throwToSingleThreaded(cap, msg->target, msg->exception); source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); return 1; } @@ -602,7 +602,7 @@ awakenBlockedExceptionQueue (Capability *cap, StgTSO *tso) i = lockClosure((StgClosure *)msg); if (i != &stg_MSG_NULL_info) { source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); } else { unlockClosure((StgClosure *)msg,i); @@ -700,7 +700,7 @@ removeFromQueues(Capability *cap, StgTSO *tso) // ASSERT(m->header.info == &stg_WHITEHOLE_info); // unlock and revoke it at the same time - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); break; } ===================================== rts/Updates.h ===================================== @@ -49,7 +49,6 @@ W_ bd; \ \ prim_write_barrier; \ - OVERWRITING_CLOSURE(p1); \ bd = Bdescr(p1); \ if (bdescr_gen_no(bd) != 0 :: bits16) { \ IF_NONMOVING_WRITE_BARRIER_ENABLED { \ @@ -60,6 +59,7 @@ } else { \ TICK_UPD_NEW_IND(); \ } \ + OVERWRITING_CLOSURE(p1); \ StgInd_indirectee(p1) = p2; \ prim_write_barrier; \ SET_INFO(p1, stg_BLACKHOLE_info); \ ===================================== rts/posix/OSThreads.c ===================================== @@ -401,8 +401,9 @@ interruptOSThread (OSThreadId id) void joinOSThread (OSThreadId id) { - if (pthread_join(id, NULL) != 0) { - sysErrorBelch("joinOSThread: error %d", errno); + int ret = pthread_join(id, NULL); + if (ret != 0) { + sysErrorBelch("joinOSThread: error %d", ret); } } ===================================== rts/sm/Evac.c ===================================== @@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) // // However, if we are in a deadlock detection GC then we disable aging // so there is no need. + // + // See Note [Non-moving GC: Marking evacuated objects]. if (major_gc && !deadlock_detect_gc) markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to); return to; @@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ +/* + * Note [Non-moving GC: Marking evacuated objects] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * When the non-moving collector is in use we must be careful to ensure that any + * references to objects in the non-moving generation from younger generations + * are pushed to the mark queue. + * + * In particular we need to ensure that we handle newly-promoted objects are + * correctly marked. For instance, consider this case: + * + * generation 0 generation 1 + * ────────────── ────────────── + * + * ┌───────┐ + * ┌───────┐ │ A │ + * │ B │ ◁────────────────────────── │ │ + * │ │ ──┬─────────────────┐ └───────┘ + * └───────┘ ┆ after GC │ + * ┆ │ + * ┌───────┐ ┆ before GC │ ┌───────┐ + * │ C │ ◁┄┘ └─────▷ │ C' │ + * │ │ │ │ + * └───────┘ └───────┘ + * + * + * In this case object C started off in generation 0 and was evacuated into + * generation 1 during the preparatory GC. However, the only reference to C' + * is from B, which lives in the generation 0 (via aging); this reference will + * not be visible to the concurrent non-moving collector (which can only + * traverse the generation 1 heap). Consequently, upon evacuating C we need to + * ensure that C' is added to the update remembered set as we know that it will + * continue to be reachable via B (which is assumed to be reachable as it lives + * in a younger generation). + * + * Where this happens depends upon the type of the object (e.g. C'): + * + * - In the case of "normal" small heap-allocated objects this happens in + * alloc_for_copy. + * - In the case of compact region this happens in evacuate_compact. + * - In the case of large objects this happens in evacuate_large. + * + * See also Note [Aging under the non-moving collector] in NonMoving.c. + * + */ + /* size is in words */ STATIC_INLINE GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, @@ -351,6 +399,9 @@ evacuate_large(StgPtr p) __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL); if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, p); } initBdescr(bd, new_gen, new_gen->to); @@ -505,6 +556,9 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -690,13 +744,6 @@ loop: */ if (flags & BF_LARGE) { evacuate_large((P_)q); - - // We may have evacuated the block to the nonmoving generation. If so - // we need to make sure it is added to the mark queue since the only - // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { - markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); - } return; } ===================================== rts/sm/NonMoving.c ===================================== @@ -191,8 +191,8 @@ Mutex concurrent_coll_finished_lock; * === Other references === * * Apart from the design document in docs/storage/nonmoving-gc and the Ueno - * 2016 paper (TODO citation) from which it drew inspiration, there are a - * variety of other relevant Notes scattered throughout the tree: + * 2016 paper [ueno 2016] from which it drew inspiration, there are a variety + * of other relevant Notes scattered throughout the tree: * * - Note [Concurrent non-moving collection] (NonMoving.c) describes * concurrency control of the nonmoving collector @@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock; * - Note [Aging under the non-moving collector] (NonMoving.c) describes how * we accommodate aging * + * - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how + * non-moving objects reached by evacuate() are marked, which is necessary + * due to aging. + * * - Note [Large objects in the non-moving collector] (NonMovingMark.c) * describes how we track large objects. * @@ -232,6 +236,11 @@ Mutex concurrent_coll_finished_lock; * how we use the DIRTY flags associated with MUT_VARs and TVARs to improve * barrier efficiency. * + * [ueno 2016]: + * Katsuhiro Ueno and Atsushi Ohori. 2016. A fully concurrent garbage + * collector for functional programs on multicore processors. SIGPLAN Not. 51, + * 9 (September 2016), 421–433. DOI:https://doi.org/10.1145/3022670.2951944 + * * * Note [Concurrent non-moving collection] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -312,6 +321,8 @@ Mutex concurrent_coll_finished_lock; * * The non-moving collector will come to C in the mark queue and mark it. * + * The implementation details of this are described in Note [Non-moving GC: + * Marking evacuated objects] in Evac.c. * * Note [Deadlock detection under the non-moving collector] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -726,7 +737,6 @@ void nonmovingStop(void) "waiting for nonmoving collector thread to terminate"); ACQUIRE_LOCK(&concurrent_coll_finished_lock); waitCondition(&concurrent_coll_finished, &concurrent_coll_finished_lock); - joinOSThread(mark_thread); } #endif } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d13e4c8f335ab8cac8b68790686f79f1c9c2b5b0...4f77bcc8276f9b81698aa7da3b2ae681ba76d800 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d13e4c8f335ab8cac8b68790686f79f1c9c2b5b0...4f77bcc8276f9b81698aa7da3b2ae681ba76d800 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 Fri Nov 27 04:05:11 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Thu, 26 Nov 2020 23:05:11 -0500 Subject: [Git][ghc/ghc][master] 8 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc07af7cb86a_86c111d4a0051358b@gitlab.mail> Ben Gamari pushed to branch master at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2ed3e6c0f179c06828712832d1176519cdfa82a6...3e3555cc9c2a9f5246895f151259fd2a81621f38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2ed3e6c0f179c06828712832d1176519cdfa82a6...3e3555cc9c2a9f5246895f151259fd2a81621f38 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 Fri Nov 27 04:07:02 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Thu, 26 Nov 2020 23:07:02 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc07b6691807_86c3fc6a6528e7c51832e@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - cec7848b by Ben Gamari at 2020-11-26T23:06:53-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ac3b27159e7c47b924d20418ee5c2c9f4fdce7f...cec7848bcb28623daceeb2ee5caa32f1d911710c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7ac3b27159e7c47b924d20418ee5c2c9f4fdce7f...cec7848bcb28623daceeb2ee5caa32f1d911710c 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 Fri Nov 27 10:40:21 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Fri, 27 Nov 2020 05:40:21 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 2 commits: Rts/elf-linker: Upcast to 64bit to satisfy format string. Message-ID: <5fc0d7954c091_86cf5745685461c3@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: 006ac733 by Andreas Klebinger at 2020-11-27T11:39:52+01:00 Rts/elf-linker: Upcast to 64bit to satisfy format string. The elf size is 32bit on 32bit builds and 64 otherwise. We just upcast to 64bits before printing now. - - - - - 878f4abd by Andreas Klebinger at 2020-11-27T11:39:53+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 T5642 WWRec ------------------------- - - - - - 2 changed files: - .gitlab-ci.yml - rts/linker/Elf.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | ===================================== rts/linker/Elf.c ===================================== @@ -904,8 +904,8 @@ ocGetNames_ELF ( ObjectCode* oc ) ASSERT(common_used <= common_size); IF_DEBUG(linker, - debugBelch("COMMON symbol, size %lu name %s allocated at %p\n", - symbol->elf_sym->st_size, nm, symbol->addr)); + debugBelch("COMMON symbol, size %llu name %s allocated at %p\n", + (uint64_t) symbol->elf_sym->st_size, nm, symbol->addr)); /* Pointless to do addProddableBlock() for this area, since the linker should never poke around in it. */ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e818856f88097a9d58a4997bf6947a16651e2bfb...878f4abdbae9a6e8936aa006940df42def3b148d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e818856f88097a9d58a4997bf6947a16651e2bfb...878f4abdbae9a6e8936aa006940df42def3b148d 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 Fri Nov 27 10:48:49 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Fri, 27 Nov 2020 05:48:49 -0500 Subject: [Git][ghc/ghc][wip/andreask/ci_validate] 5 commits: OSMem.c: Use proper type for mbinds mask argument. Message-ID: <5fc0d9918c8d3_86c879fa9c5526fd@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/ci_validate at Glasgow Haskell Compiler / GHC Commits: afcd1727 by Andreas Klebinger at 2020-11-27T11:47:02+01:00 OSMem.c: Use proper type for mbinds mask argument. StgWord has different widths on 32/64bit. So use the proper type instead. - - - - - 49dcad94 by Andreas Klebinger at 2020-11-27T11:47:02+01:00 Linker.c: Only define freeNativeCode_ELF when using elf format. - - - - - 399d306e by Andreas Klebinger at 2020-11-27T11:47:02+01:00 rts: EventLog.c: Properly cast (potential) 32bit pointers to uint64_t - - - - - 9fc22a20 by Andreas Klebinger at 2020-11-27T11:47:44+01:00 Rts/elf-linker: Upcast to 64bit to satisfy format string. The elf size is 32bit on 32bit builds and 64 otherwise. We just upcast to 64bits before printing now. - - - - - b02863bc by Andreas Klebinger at 2020-11-27T11:48:29+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 T5642 WWRec ------------------------- - - - - - 5 changed files: - .gitlab-ci.yml - rts/Linker.c - rts/eventlog/EventLog.c - rts/linker/Elf.c - rts/posix/OSMem.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | ===================================== rts/Linker.c ===================================== @@ -171,7 +171,9 @@ Mutex linker_mutex; /* Generic wrapper function to try and Resolve and RunInit oc files */ int ocTryLoad( ObjectCode* oc ); +#if defined(OBJFORMAT_ELF) static void freeNativeCode_ELF (ObjectCode *nc); +#endif /* Link objects into the lower 2Gb on x86_64 and AArch64. GHC assumes the * small memory model on this architecture (see gcc docs, ===================================== rts/eventlog/EventLog.c ===================================== @@ -1489,7 +1489,8 @@ static void postTickyCounterDef(EventsBuf *eb, StgEntCounter *p) ensureRoomForVariableEvent(eb, len); postEventHeader(eb, EVENT_TICKY_COUNTER_DEF); postPayloadSize(eb, len); - postWord64(eb, (uint64_t) p); + + postWord64(eb, (uint64_t)((uintptr_t) p)); postWord16(eb, (uint16_t) p->arity); postString(eb, p->arg_kinds); postString(eb, p->str); @@ -1513,7 +1514,7 @@ static void postTickyCounterSample(EventsBuf *eb, StgEntCounter *p) ensureRoomForEvent(eb, EVENT_TICKY_COUNTER_SAMPLE); postEventHeader(eb, EVENT_TICKY_COUNTER_SAMPLE); - postWord64(eb, (uint64_t) p); + postWord64(eb, (uint64_t)((uintptr_t) p)); postWord64(eb, p->entry_count); postWord64(eb, p->allocs); postWord64(eb, p->allocd); ===================================== rts/linker/Elf.c ===================================== @@ -904,8 +904,8 @@ ocGetNames_ELF ( ObjectCode* oc ) ASSERT(common_used <= common_size); IF_DEBUG(linker, - debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", - symbol->elf_sym->st_size, nm, symbol->addr)); + debugBelch("COMMON symbol, size %llu name %s allocated at %p\n", + (uint64_t) symbol->elf_sym->st_size, nm, symbol->addr)); /* Pointless to do addProddableBlock() for this area, since the linker should never poke around in it. */ ===================================== rts/posix/OSMem.c ===================================== @@ -364,7 +364,7 @@ void osBindMBlocksToNode( { #if HAVE_LIBNUMA int ret; - StgWord mask = 0; + unsigned long mask = 0; mask |= 1 << node; if (RtsFlags.GcFlags.numa) { ret = mbind(addr, (unsigned long)size, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/878f4abdbae9a6e8936aa006940df42def3b148d...b02863bc0a299f67bafbfcba0db2c46fee228ad4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/878f4abdbae9a6e8936aa006940df42def3b148d...b02863bc0a299f67bafbfcba0db2c46fee228ad4 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 Fri Nov 27 10:49:17 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Fri, 27 Nov 2020 05:49:17 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/fix_rts_warnings Message-ID: <5fc0d9ad2e361_86c111d4a005533cb@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/fix_rts_warnings at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/fix_rts_warnings 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 Fri Nov 27 10:49:56 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Fri, 27 Nov 2020 05:49:56 -0500 Subject: [Git][ghc/ghc][wip/andreask/fix_rts_warnings] Deleted 1 commit: Use validate flavour for all CI builds. Message-ID: <5fc0d9d456147_86c11450e28553579@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/fix_rts_warnings at Glasgow Haskell Compiler / GHC WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below. Deleted commits: b02863bc by Andreas Klebinger at 2020-11-27T11:48:29+01:00 Use validate flavour for all CI builds. This also means we compile GHC with -O1 instead of -O2 for some platforms for CI. As a result a lot of test metrics got worse which we now have to accept. ------------------------- Metric Increase: ManyAlternatives ManyConstructors MultiLayerModules Naperian T10421 T12150 T12227 T12234 T12425 T12545 T12707 T13035 T13253 T13253-spj T13379 T13719 T14697 T18282 T18698a T18698b T1969 T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9020 T9203 T9233 T9872a T9872b T9872c T9872d T9961 haddock.Cabal haddock.base parsing001 T5642 WWRec ------------------------- - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -442,7 +442,7 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: "--with-intree-gmp" TEST_ENV: "x86_64-darwin" - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -493,7 +493,7 @@ validate-x86_64-darwin: tags: - x86_64-linux variables: - BUILD_FLAVOUR: "perf" + BUILD_FLAVOUR: "validate" before_script: # Build hyperlinked sources for documentation when building releases - | View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b02863bc0a299f67bafbfcba0db2c46fee228ad4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b02863bc0a299f67bafbfcba0db2c46fee228ad4 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 Fri Nov 27 11:20:48 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 27 Nov 2020 06:20:48 -0500 Subject: [Git][ghc/ghc][master] rts: Allocate MBlocks with MAP_TOP_DOWN on Windows Message-ID: <5fc0e110231b6_86c879fa9c5798e9@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 1 changed file: - rts/win32/OSMem.c Changes: ===================================== rts/win32/OSMem.c ===================================== @@ -50,8 +50,11 @@ allocNew(uint32_t n) { alloc_rec* rec; rec = (alloc_rec*)stgMallocBytes(sizeof(alloc_rec),"getMBlocks: allocNew"); rec->size = ((W_)n+1)*MBLOCK_SIZE; + // N.B. We use MEM_TOP_DOWN here to ensure that we leave the bottom of the + // address space available for the linker and libraries, which in general + // want to live in low memory. See #18991. rec->base = - VirtualAlloc(NULL, rec->size, MEM_RESERVE, PAGE_READWRITE); + VirtualAlloc(NULL, rec->size, MEM_RESERVE | MEM_TOP_DOWN, PAGE_READWRITE); if(rec->base==0) { stgFree((void*)rec); rec=0; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1a75aa9be2c133dd1372a08eeb6a92c31688df7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1a75aa9be2c133dd1372a08eeb6a92c31688df7 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 Fri Nov 27 12:13:53 2020 From: gitlab at gitlab.haskell.org (Sebastian Graf) Date: Fri, 27 Nov 2020 07:13:53 -0500 Subject: [Git][ghc/ghc][wip/T18894] 2 commits: DmdAnal: Annotate top-level function bindings with demands (#18894) Message-ID: <5fc0ed8160447_86cf574568588010@gitlab.mail> Sebastian Graf pushed to branch wip/T18894 at Glasgow Haskell Compiler / GHC Commits: b853798a by Sebastian Graf at 2020-11-27T11:41:35+01:00 DmdAnal: Annotate top-level function bindings with demands (#18894) It's useful to annotate a non-exported top-level function like `g` in ```hs module Lib (h) where g :: Int -> Int -> (Int,Int) g m 1 = (m, 0) g m n = (2 * m, 2 `div` n) {-# NOINLINE g #-} h :: Int -> Int h 1 = 0 h m | odd m = snd (g m 2) | otherwise = uncurry (+) (g 2 m) ``` with its demand `UCU(CS(P(1P(U),SP(U))`, which tells us that whenever `g` was called, the second component of the returned pair was evaluated strictly. Since #18903 we do so for local functions, where we can see all calls. For top-level functions, we can assume that all *exported* functions are demanded according to `topDmd` and thus get sound demands for non-exported top-level functions. The demand on `g` is crucial information for Nested CPR, which may the go on and unbox `g` for the second pair component. That is true even if that pair component may diverge, as is the case for the call site `g 13 0`, which throws a div-by-zero exception. We only track bindings of function type in order not to risk huge compile-time regressions, see `isInterestingTopLevelFn`. Fixes #18894. - - - - - 3a7344fb by Sebastian Graf at 2020-11-27T13:03:07+01:00 Demand: Simplify `CU(U)` to `U` (#19005) Both sub-demands encode the same information. This is a trivial change and already affects a few regression tests (e.g. `T5075`), so no separate regression test is necessary. - - - - - 13 changed files: - compiler/GHC/Core/FVs.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/Tidy.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Id/Info.hs - testsuite/tests/arityanal/should_compile/Arity11.stderr - testsuite/tests/arityanal/should_compile/Arity16.stderr - + testsuite/tests/stranal/should_compile/T18894.hs - + testsuite/tests/stranal/should_compile/T18894.stderr - testsuite/tests/stranal/should_compile/all.T - testsuite/tests/stranal/sigs/T5075.stderr Changes: ===================================== compiler/GHC/Core/FVs.hs ===================================== @@ -525,12 +525,11 @@ ruleLhsFVIds (Rule { ru_bndrs = bndrs, ru_args = args }) = filterFV isLocalId $ addBndrs bndrs (exprs_fvs args) ruleRhsFreeIds :: CoreRule -> VarSet --- ^ This finds all locally-defined free Ids on the left hand side of a rule +-- ^ This finds all locally-defined free Ids on the right hand side of a rule -- and returns them as a non-deterministic set ruleRhsFreeIds (BuiltinRule {}) = emptyVarSet -ruleRhsFreeIds (Rule { ru_bndrs = bndrs, ru_args = args }) - = fvVarSet $ filterFV isLocalId $ - addBndrs bndrs $ exprs_fvs args +ruleRhsFreeIds (Rule { ru_bndrs = bndrs, ru_rhs = rhs }) + = fvVarSet $ filterFV isLocalId $ addBndrs bndrs $ expr_fvs rhs {- Note [Rule free var hack] (Not a hack any more) ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -37,6 +37,7 @@ import GHC.Core.Type import GHC.Core.FVs ( exprFreeIds, ruleRhsFreeIds ) import GHC.Core.Coercion ( Coercion, coVarsOfCo ) import GHC.Core.FamInstEnv +import GHC.Core.Opt.Arity ( typeArity ) import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Data.Maybe ( isJust ) @@ -59,33 +60,62 @@ data DmdAnalOpts = DmdAnalOpts { dmd_strict_dicts :: !Bool -- ^ Use strict dictionaries } +-- | Whether we want to store demands on a top-level Id or just default +-- to 'topDmd'. +-- +-- Basically, we want to now how top-level *functions* are *used* +-- (e.g. called), but aren't interested in whether they were called strictly +-- or not. Other top-level bindings are boring. +isInterestingTopLevelFn :: Id -> Bool +-- SG tried to set this to True and got a +2% ghc/alloc regression in T5642 +-- (which is dominated by the Simplifier) at no gain in analysis precision. +-- If there was a gain, that regression might be acceptable. +-- Plus, we could use LetUp for thunks and share some code with local let +-- bindings. +isInterestingTopLevelFn id = + typeArity (idType id) `lengthExceeds` 0 + -- | Outputs a new copy of the Core program in which binders have been annotated -- with demand and strictness information. -- -- Note: use `seqBinds` on the result to avoid leaks due to lazyness (cf Note -- [Stamp out space leaks in demand analysis]) -dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> CoreProgram -> CoreProgram -dmdAnalProgram opts fam_envs binds = binds_plus_dmds - where - env = emptyAnalEnv opts fam_envs - binds_plus_dmds = snd $ mapAccumL dmdAnalTopBind env binds - --- Analyse a (group of) top-level binding(s) -dmdAnalTopBind :: AnalEnv - -> CoreBind - -> (AnalEnv, CoreBind) -dmdAnalTopBind env (NonRec id rhs) - = ( extendAnalEnv TopLevel env id sig - , NonRec (setIdStrictness id sig) rhs') +dmdAnalProgram :: DmdAnalOpts -> FamInstEnvs -> [CoreRule] -> CoreProgram -> CoreProgram +dmdAnalProgram opts fam_envs rules binds + = snd $ go (emptyAnalEnv opts fam_envs) binds where - ( _, sig, rhs') = dmdAnalRhsLetDown Nothing env topSubDmd id rhs + go _ [] = (nopDmdType, []) + go env (b:bs) = case b of + NonRec id rhs + | (env', lazy_fvs, id', rhs') <- dmdAnalRhsLetDown TopLevel NonRecursive env topSubDmd id rhs + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_use env' dmd_ty' id' `addLazyFVs` lazy_fvs + , (!dmd_ty''', id_dmd) <- findBndrDmd env' False dmd_ty'' id' + , let id'' = annotate_id_dmd id' id_dmd + -> (dmd_ty''', NonRec id'' rhs' : bs') + Rec pairs + | (env', lazy_fvs, pairs') <- dmdFix TopLevel env topSubDmd pairs + , let ids' = map fst pairs' + , (dmd_ty', bs') <- go env' bs + , let dmd_ty'' = add_exported_uses env' dmd_ty' ids' `addLazyFVs` lazy_fvs + , (!dmd_ty''', id_dmds) <- findBndrsDmds env' dmd_ty'' ids' + , let pairs'' = zipWith (\(id', rhs') dmd -> (annotate_id_dmd id' dmd, rhs')) pairs' id_dmds + -> (dmd_ty''', Rec pairs'' : bs') + + annotate_id_dmd id dmd + | isInterestingTopLevelFn id + = id `setIdDemandInfo` dmd + | otherwise + = id `setIdDemandInfo` topDmd -dmdAnalTopBind env (Rec pairs) - = (env', Rec pairs') - where - (env', _, pairs') = dmdFix TopLevel env topSubDmd pairs - -- We get two iterations automatically - -- c.f. the NonRec case above + add_exported_uses env = foldl' (add_exported_use env) + add_exported_use env dmd_ty id + | isExportedId id || elemVarSet id rule_fvs + -- See Note [Absence analysis for stable unfoldings and RULES] + = dmd_ty `plusDmdType` fst (dmdAnalStar env topDmd (Var id)) + | otherwise = dmd_ty + + rule_fvs = foldr (unionVarSet . ruleRhsFreeIds) emptyVarSet rules {- Note [Stamp out space leaks in demand analysis] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -194,7 +224,7 @@ dmdAnal' env dmd (App fun arg) -- Crucially, coercions /are/ handled here, because they are -- value arguments (#10288) let - call_dmd = mkCallDmd dmd + call_dmd = mkCalledOnceDmd dmd (fun_ty, fun') = dmdAnal env call_dmd fun (arg_dmd, res_ty) = splitDmdTy fun_ty (arg_ty, arg') = dmdAnalStar env (dmdTransformThunkDmd arg arg_dmd) arg @@ -320,9 +350,7 @@ dmdAnal' env dmd (Let (NonRec id rhs) body) dmdAnal' env dmd (Let (NonRec id rhs) body) = (body_ty2, Let (NonRec id2 rhs') body') where - (lazy_fv, sig, rhs') = dmdAnalRhsLetDown Nothing env dmd id rhs - id1 = setIdStrictness id sig - env1 = extendAnalEnv NotTopLevel env id sig + (env1, lazy_fv, id1, rhs') = dmdAnalRhsLetDown NotTopLevel NonRecursive env dmd id rhs (body_ty, body') = dmdAnal env1 dmd body (body_ty1, id2) = annotateBndr env body_ty id1 body_ty2 = addLazyFVs body_ty1 lazy_fv -- see Note [Lazy and unleashable free variables] @@ -344,8 +372,8 @@ dmdAnal' env dmd (Let (Rec pairs) body) = let (env', lazy_fv, pairs') = dmdFix NotTopLevel env dmd pairs (body_ty, body') = dmdAnal env' dmd body - body_ty1 = deleteFVs body_ty (map fst pairs) - body_ty2 = addLazyFVs body_ty1 lazy_fv -- see Note [Lazy and unleashable free variables] + body_ty1 = addLazyFVs body_ty lazy_fv -- see Note [Lazy and unleashable free variables] + body_ty2 = deleteFVs body_ty1 (map fst pairs) -- TODO: We could annotate idDemandInfo here in body_ty2 `seq` (body_ty2, Let (Rec pairs') body') @@ -582,9 +610,13 @@ dmdTransform env var dmd | Just (sig, top_lvl) <- lookupSigEnv env var , let fn_ty = dmdTransformSig sig dmd = -- pprTrace "dmdTransform:LetDown" (vcat [ppr var, ppr sig, ppr dmd, ppr fn_ty]) $ - if isTopLevel top_lvl - then fn_ty -- Don't record demand on top-level things - else addVarDmd fn_ty var (C_11 :* dmd) + case top_lvl of + NotTopLevel -> addVarDmd fn_ty var (C_11 :* dmd) + TopLevel + | isInterestingTopLevelFn var + -> addVarDmd fn_ty var (C_0N `multDmd` (C_11 :* dmd)) -- discard strictness + | otherwise + -> fn_ty -- don't bother tracking; just annotate with 'topDmd' later -- Everything else: -- * Local let binders for which we use LetUp (cf. 'useLetUp') -- * Lambda binders @@ -612,33 +644,36 @@ dmdTransform env var dmd -- -- This is the LetDown rule in the paper “Higher-Order Cardinality Analysis”. dmdAnalRhsLetDown - :: Maybe [Id] -- Just bs <=> recursive, Nothing <=> non-recursive + :: TopLevelFlag + -> RecFlag -> AnalEnv -> SubDemand -> Id -> CoreExpr - -> (DmdEnv, StrictSig, CoreExpr) + -> (AnalEnv, DmdEnv, Id, CoreExpr) -- Process the RHS of the binding, add the strictness signature -- to the Id, and augment the environment with the signature as well. -- See Note [NOINLINE and strictness] -dmdAnalRhsLetDown rec_flag env let_dmd id rhs +dmdAnalRhsLetDown top_lvl rec_flag env let_dmd id rhs = -- pprTrace "dmdAnalRhsLetDown" (ppr id $$ ppr let_dmd $$ ppr sig $$ ppr lazy_fv) $ - (lazy_fv, sig, rhs') + (env', lazy_fv, id', rhs') where rhs_arity = idArity id + -- See Note [Demand signatures are computed for a threshold demand based on idArity] rhs_dmd -- See Note [Demand analysis for join points] -- See Note [Invariants on join points] invariant 2b, in GHC.Core -- rhs_arity matches the join arity of the join point | isJoinId id - = mkCallDmds rhs_arity let_dmd + = mkCalledOnceDmds rhs_arity let_dmd | otherwise - -- NB: rhs_arity - -- See Note [Demand signatures are computed for a threshold demand based on idArity] - = mkRhsDmd env rhs_arity rhs + = mkCalledOnceDmds rhs_arity topSubDmd (rhs_dmd_ty, rhs') = dmdAnal env rhs_dmd rhs DmdType rhs_fv rhs_dmds rhs_div = rhs_dmd_ty sig = mkStrictSigForArity rhs_arity (DmdType sig_fv rhs_dmds rhs_div) + id' = id `setIdStrictness` sig + env' = extendAnalEnv top_lvl env id' sig + -- See Note [Aggregated demand for cardinality] -- FIXME: That Note doesn't explain the following lines at all. The reason -- is really much different: When we have a recursive function, we'd @@ -651,8 +686,8 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs -- we'd have to do an additional iteration. reuseEnv makes sure that -- we never get used-once info for FVs of recursive functions. rhs_fv1 = case rec_flag of - Just bs -> reuseEnv (delVarEnvList rhs_fv bs) - Nothing -> rhs_fv + Recursive -> reuseEnv rhs_fv + NonRecursive -> rhs_fv rhs_fv2 = rhs_fv1 `keepAliveDmdEnv` extra_fvs -- Find the RHS free vars of the unfoldings and RULES @@ -669,13 +704,6 @@ dmdAnalRhsLetDown rec_flag env let_dmd id rhs = exprFreeIds unf_body | otherwise = emptyVarSet --- | @mkRhsDmd env rhs_arity rhs@ creates a 'SubDemand' for --- unleashing on the given function's @rhs@, by creating --- a call demand of @rhs_arity@ --- See Historical Note [Product demands for function body] -mkRhsDmd :: AnalEnv -> Arity -> CoreExpr -> SubDemand -mkRhsDmd _env rhs_arity _rhs = mkCallDmds rhs_arity topSubDmd - -- | If given the (local, non-recursive) let-bound 'Id', 'useLetUp' determines -- whether we should process the binding up (body before rhs) or down (rhs -- before body). @@ -939,8 +967,6 @@ dmdFix :: TopLevelFlag dmdFix top_lvl env let_dmd orig_pairs = loop 1 initial_pairs where - bndrs = map fst orig_pairs - -- See Note [Initialising strictness] initial_pairs | ae_virgin env = [(setIdStrictness id botSig, rhs) | (id, rhs) <- orig_pairs ] | otherwise = orig_pairs @@ -990,10 +1016,8 @@ dmdFix top_lvl env let_dmd orig_pairs = -- pprTrace "my_downRhs" (ppr id $$ ppr (idStrictness id) $$ ppr sig) $ ((env', lazy_fv'), (id', rhs')) where - (lazy_fv1, sig, rhs') = dmdAnalRhsLetDown (Just bndrs) env let_dmd id rhs - lazy_fv' = plusVarEnv_C plusDmd lazy_fv lazy_fv1 - env' = extendAnalEnv top_lvl env id sig - id' = setIdStrictness id sig + (env', lazy_fv1, id', rhs') = dmdAnalRhsLetDown top_lvl Recursive env let_dmd id rhs + lazy_fv' = plusVarEnv_C plusDmd lazy_fv lazy_fv1 zapIdStrictness :: [(Id, CoreExpr)] -> [(Id, CoreExpr)] zapIdStrictness pairs = [(setIdStrictness id nopSig, rhs) | (id, rhs) <- pairs ] ===================================== compiler/GHC/Core/Opt/Pipeline.hs ===================================== @@ -65,6 +65,7 @@ import GHC.Types.SrcLoc import GHC.Types.Id import GHC.Types.Id.Info import GHC.Types.Basic +import GHC.Types.Demand ( zapDmdEnvSig ) import GHC.Types.Var.Set import GHC.Types.Var.Env import GHC.Types.Unique.Supply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply ) @@ -495,7 +496,7 @@ doCorePass CoreDoExitify = {-# SCC "Exitify" #-} doPass exitifyProgram doCorePass CoreDoDemand = {-# SCC "DmdAnal" #-} - doPassDFM dmdAnal + doPassDFRM dmdAnal doCorePass CoreDoCpr = {-# SCC "CprAnal" #-} doPassDFM cprAnalProgram @@ -575,6 +576,13 @@ doPassDFM do_pass guts = do let fam_envs = (p_fam_env, mg_fam_inst_env guts) doPassM (liftIO . do_pass dflags fam_envs) guts +doPassDFRM :: (DynFlags -> FamInstEnvs -> [CoreRule] -> CoreProgram -> IO CoreProgram) -> ModGuts -> CoreM ModGuts +doPassDFRM do_pass guts = do + dflags <- getDynFlags + p_fam_env <- getPackageFamInstEnv + let fam_envs = (p_fam_env, mg_fam_inst_env guts) + doPassM (liftIO . do_pass dflags fam_envs (mg_rules guts)) guts + doPassDFU :: (DynFlags -> FamInstEnvs -> UniqSupply -> CoreProgram -> CoreProgram) -> ModGuts -> CoreM ModGuts doPassDFU do_pass guts = do dflags <- getDynFlags @@ -1088,13 +1096,13 @@ transferIdInfo exported_id local_id -dmdAnal :: DynFlags -> FamInstEnvs -> CoreProgram -> IO CoreProgram -dmdAnal dflags fam_envs binds = do +dmdAnal :: DynFlags -> FamInstEnvs -> [CoreRule] -> CoreProgram -> IO CoreProgram +dmdAnal dflags fam_envs rules binds = do let opts = DmdAnalOpts { dmd_strict_dicts = gopt Opt_DictsStrict dflags } - binds_plus_dmds = dmdAnalProgram opts fam_envs binds + binds_plus_dmds = dmdAnalProgram opts fam_envs rules binds Err.dumpIfSet_dyn dflags Opt_D_dump_str_signatures "Strictness signatures" FormatText $ - dumpIdInfoOfProgram (ppr . strictnessInfo) binds_plus_dmds + dumpIdInfoOfProgram (ppr . zapDmdEnvSig . strictnessInfo) binds_plus_dmds -- See Note [Stamp out space leaks in demand analysis] in GHC.Core.Opt.DmdAnal seqBinds binds_plus_dmds `seq` return binds_plus_dmds ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -1275,10 +1275,14 @@ mk_absent_let dflags fam_envs arg abs_rhs = mkAbsentErrorApp arg_ty msg msg = showSDoc (gopt_set dflags Opt_SuppressUniques) - (ppr arg <+> ppr (idType arg) <+> file_msg) + (vcat + [ text "Arg:" <+> ppr arg + , text "Type:" <+> ppr arg_ty + , file_msg + ]) file_msg = case outputFile dflags of Nothing -> empty - Just f -> text "in output file " <+> quotes (text f) + Just f -> text "In output file " <+> quotes (text f) -- We need to suppress uniques here because otherwise they'd -- end up in the generated code as strings. This is bad for -- determinism, because with different uniques the strings ===================================== compiler/GHC/Core/Tidy.hs ===================================== @@ -21,7 +21,7 @@ import GHC.Core import GHC.Core.Seq ( seqUnfolding ) import GHC.Types.Id import GHC.Types.Id.Info -import GHC.Types.Demand ( zapUsageEnvSig ) +import GHC.Types.Demand ( zapDmdEnvSig ) import GHC.Core.Type ( tidyType, tidyVarBndr ) import GHC.Core.Coercion ( tidyCo ) import GHC.Types.Var @@ -206,7 +206,7 @@ tidyLetBndr rec_tidy_env env@(tidy_env, var_env) id new_info = vanillaIdInfo `setOccInfo` occInfo old_info `setArityInfo` arityInfo old_info - `setStrictnessInfo` zapUsageEnvSig (strictnessInfo old_info) + `setStrictnessInfo` zapDmdEnvSig (strictnessInfo old_info) `setDemandInfo` demandInfo old_info `setInlinePragInfo` inlinePragInfo old_info `setUnfoldingInfo` new_unf ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -34,7 +34,7 @@ module GHC.Types.Demand ( lazyApply1Dmd, lazyApply2Dmd, strictOnceApply1Dmd, strictManyApply1Dmd, -- ** Other @Demand@ operations oneifyCard, oneifyDmd, strictifyDmd, strictifyDictDmd, mkWorkerDemand, - peelCallDmd, peelManyCalls, mkCallDmd, mkCallDmds, + peelCallDmd, peelManyCalls, mkCalledOnceDmd, mkCalledOnceDmds, addCaseBndrDmd, -- ** Extracting one-shot information argOneShots, argsOneShots, saturatedByOneShots, @@ -73,7 +73,7 @@ module GHC.Types.Demand ( seqDemand, seqDemandList, seqDmdType, seqStrictSig, -- * Zapping usage information - zapUsageDemand, zapUsageEnvSig, zapUsedOnceDemand, zapUsedOnceSig + zapUsageDemand, zapDmdEnvSig, zapUsedOnceDemand, zapUsedOnceSig ) where #include "HsVersions.h" @@ -278,7 +278,8 @@ data SubDemand -- ^ @Call n sd@ describes the evaluation context of @n@ function -- applications, where every individual result is evaluated according to @sd at . -- @sd@ is /relative/ to a single call, cf. Note [Call demands are relative]. - -- Used only for values of function type. + -- Used only for values of function type. Use the smart constructor 'mkCall' + -- whenever possible! | Prod ![Demand] -- ^ @Prod ds@ describes the evaluation context of a case scrutinisation -- on an expression of product type, where the product components are @@ -306,7 +307,7 @@ polyDmd C_1N = C_1N :* poly1N polyDmd C_10 = C_10 :* poly10 -- | A smart constructor for 'Prod', applying rewrite rules along the semantic --- equalities @Prod [polyDmd n, ...] === polyDmd n@, simplifying to 'Poly' +-- equality @Prod [polyDmd n, ...] === polyDmd n@, simplifying to 'Poly' -- 'SubDemand's when possible. Note that this degrades boxity information! E.g. a -- polymorphic demand will never unbox. mkProd :: [Demand] -> SubDemand @@ -335,6 +336,13 @@ viewProd _ _ = Nothing {-# INLINE viewProd #-} -- we want to fuse away the replicate and the allocation -- for Arity. Otherwise, #18304 bites us. +-- | A smart constructor for 'Call', applying rewrite rules along the semantic +-- equality @Call n (Poly n) === Poly n@, simplifying to 'Poly' 'SubDemand's +-- when possible. +mkCall :: Card -> SubDemand -> SubDemand +mkCall n cd@(Poly m) | n == m = cd +mkCall n cd = Call n cd + -- | @viewCall sd@ interprets @sd@ as a 'Call', expanding 'Poly' demands as -- necessary. viewCall :: SubDemand -> Maybe (Card, SubDemand) @@ -356,8 +364,8 @@ lubSubDmd (Prod ds1) (viewProd (length ds1) -> Just ds2) = -- Handle Call lubSubDmd (Call n1 d1) (viewCall -> Just (n2, d2)) -- See Note [Call demands are relative] - | isAbs n2 = Call (lubCard n1 n2) (lubSubDmd d1 botSubDmd) - | otherwise = Call (lubCard n1 n2) (lubSubDmd d1 d2) + | isAbs n2 = mkCall (lubCard n1 n2) (lubSubDmd d1 botSubDmd) + | otherwise = mkCall (lubCard n1 n2) (lubSubDmd d1 d2) -- Handle Poly lubSubDmd (Poly n1) (Poly n2) = Poly (lubCard n1 n2) -- Make use of reflexivity (so we'll match the Prod or Call cases again). @@ -377,8 +385,8 @@ plusSubDmd (Prod ds1) (viewProd (length ds1) -> Just ds2) = -- Handle Call plusSubDmd (Call n1 d1) (viewCall -> Just (n2, d2)) -- See Note [Call demands are relative] - | isAbs n2 = Call (plusCard n1 n2) (lubSubDmd d1 botSubDmd) - | otherwise = Call (plusCard n1 n2) (lubSubDmd d1 d2) + | isAbs n2 = mkCall (plusCard n1 n2) (lubSubDmd d1 botSubDmd) + | otherwise = mkCall (plusCard n1 n2) (lubSubDmd d1 d2) -- Handle Poly plusSubDmd (Poly n1) (Poly n2) = Poly (plusCard n1 n2) -- Make use of reflexivity (so we'll match the Prod or Call cases again). @@ -407,7 +415,7 @@ multSubDmd :: Card -> SubDemand -> SubDemand multSubDmd n sd | Just sd' <- multTrivial n seqSubDmd sd = sd' multSubDmd n (Poly n') = Poly (multCard n n') -multSubDmd n (Call n' sd) = Call (multCard n n') sd -- See Note [Call demands are relative] +multSubDmd n (Call n' sd) = mkCall (multCard n n') sd -- See Note [Call demands are relative] multSubDmd n (Prod ds) = Prod (map (multDmd n) ds) multDmd :: Card -> Demand -> Demand @@ -457,22 +465,22 @@ evalDmd = C_1N :* topSubDmd -- | First argument of 'GHC.Exts.maskAsyncExceptions#': @SCS(U)@. -- Called exactly once. strictOnceApply1Dmd :: Demand -strictOnceApply1Dmd = C_11 :* Call C_11 topSubDmd +strictOnceApply1Dmd = C_11 :* mkCall C_11 topSubDmd -- | First argument of 'GHC.Exts.atomically#': @MCM(U)@. -- Called at least once, possibly many times. strictManyApply1Dmd :: Demand -strictManyApply1Dmd = C_1N :* Call C_1N topSubDmd +strictManyApply1Dmd = C_1N :* mkCall C_1N topSubDmd -- | First argument of catch#: @1C1(U)@. -- Evaluates its arg lazily, but then applies it exactly once to one argument. lazyApply1Dmd :: Demand -lazyApply1Dmd = C_01 :* Call C_01 topSubDmd +lazyApply1Dmd = C_01 :* mkCall C_01 topSubDmd -- | Second argument of catch#: @1C1(CS(U))@. -- Calls its arg lazily, but then applies it exactly once to an additional argument. lazyApply2Dmd :: Demand -lazyApply2Dmd = C_01 :* Call C_01 (Call C_11 topSubDmd) +lazyApply2Dmd = C_01 :* mkCall C_01 (mkCall C_11 topSubDmd) -- | Make a 'Demand' evaluated at-most-once. oneifyDmd :: Demand -> Demand @@ -512,12 +520,12 @@ strictifyDictDmd ty (n :* Prod ds) strictifyDictDmd _ dmd = dmd -- | Wraps the 'SubDemand' with a one-shot call demand: @d@ -> @CS(d)@. -mkCallDmd :: SubDemand -> SubDemand -mkCallDmd sd = Call C_11 sd +mkCalledOnceDmd :: SubDemand -> SubDemand +mkCalledOnceDmd sd = mkCall C_11 sd --- | @mkCallDmds n d@ returns @CS(CS...(CS d))@ where there are @n@ @CS@'s. -mkCallDmds :: Arity -> SubDemand -> SubDemand -mkCallDmds arity sd = iterate mkCallDmd sd !! arity +-- | @mkCalledOnceDmds n d@ returns @CS(CS...(CS d))@ where there are @n@ @CS@'s. +mkCalledOnceDmds :: Arity -> SubDemand -> SubDemand +mkCalledOnceDmds arity sd = iterate mkCalledOnceDmd sd !! arity -- | Peels one call level from the sub-demand, and also returns how many -- times we entered the lambda body. @@ -669,7 +677,7 @@ This is needed even for non-product types, in case the case-binder is used but the components of the case alternative are not. Note [Don't optimise UP(U,U,...) to U] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ These two SubDemands: UP(U,U) (@Prod [topDmd, topDmd]@) and U (@topSubDmd@) are semantically equivalent, but we do not turn the former into @@ -1571,9 +1579,9 @@ This is weird, so I'm not worried about whether this optimises brilliantly; but it should not fall over. -} -zapUsageEnvSig :: StrictSig -> StrictSig --- Remove the usage environment from the demand -zapUsageEnvSig (StrictSig (DmdType _ ds r)) = mkClosedStrictSig ds r +-- | Remove the demand environment from the signature. +zapDmdEnvSig :: StrictSig -> StrictSig +zapDmdEnvSig (StrictSig (DmdType _ ds r)) = mkClosedStrictSig ds r zapUsageDemand :: Demand -> Demand -- Remove the usage info, but not the strictness info, from the demand @@ -1615,8 +1623,8 @@ kill_usage kfs (n :* sd) = kill_usage_card kfs n :* kill_usage_sd kfs sd kill_usage_sd :: KillFlags -> SubDemand -> SubDemand kill_usage_sd kfs (Call n sd) - | kf_called_once kfs = Call (lubCard C_1N n) (kill_usage_sd kfs sd) - | otherwise = Call n (kill_usage_sd kfs sd) + | kf_called_once kfs = mkCall (lubCard C_1N n) (kill_usage_sd kfs sd) + | otherwise = mkCall n (kill_usage_sd kfs sd) kill_usage_sd kfs (Prod ds) = Prod (map (kill_usage kfs) ds) kill_usage_sd _ sd = sd @@ -1640,7 +1648,7 @@ trimToType (n :* sd) ts where go (Prod ds) (TsProd tss) | equalLength ds tss = Prod (zipWith trimToType ds tss) - go (Call n sd) (TsFun ts) = Call n (go sd ts) + go (Call n sd) (TsFun ts) = mkCall n (go sd ts) go sd at Poly{} _ = sd go _ _ = topSubDmd @@ -1804,7 +1812,7 @@ instance Binary SubDemand where h <- getByte bh case h of 0 -> Poly <$> get bh - 1 -> Call <$> get bh <*> get bh + 1 -> mkCall <$> get bh <*> get bh 2 -> Prod <$> get bh _ -> pprPanic "Binary:SubDemand" (ppr (fromIntegral h :: Int)) ===================================== compiler/GHC/Types/Id/Info.hs ===================================== @@ -650,7 +650,7 @@ zapUsageInfo info = Just (info {demandInfo = zapUsageDemand (demandInfo info)}) zapUsageEnvInfo :: IdInfo -> Maybe IdInfo zapUsageEnvInfo info | hasDemandEnvSig (strictnessInfo info) - = Just (info {strictnessInfo = zapUsageEnvSig (strictnessInfo info)}) + = Just (info {strictnessInfo = zapDmdEnvSig (strictnessInfo info)}) | otherwise = Nothing ===================================== testsuite/tests/arityanal/should_compile/Arity11.stderr ===================================== @@ -35,7 +35,7 @@ end Rec } -- RHS size: {terms: 52, types: 28, coercions: 0, joins: 0/5} F11.$wfib [InlPrag=[2]] :: forall {a} {p}. (a -> a -> Bool) -> (Num a, Num p) => a -> p -[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 460 0}] +[GblId, Arity=4, Str=, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 460 0}] F11.$wfib = \ (@a) (@p) (ww :: a -> a -> Bool) (w :: Num a) (w1 :: Num p) (w2 :: a) -> let { @@ -73,7 +73,7 @@ F11.$wfib fib [InlPrag=[2]] :: forall {a} {p}. (Eq a, Num a, Num p) => a -> p [GblId, Arity=4, - Str=, + Str=, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=4,unsat_ok=True,boring_ok=False) Tmpl= \ (@a) (@p) (w [Occ=Once1!] :: Eq a) (w1 [Occ=Once1] :: Num a) (w2 [Occ=Once1] :: Num p) (w3 [Occ=Once1] :: a) -> case w of { GHC.Classes.C:Eq ww1 [Occ=Once1] _ [Occ=Dead] -> F11.$wfib @a @p ww1 w1 w2 w3 }}] fib = \ (@a) (@p) (w :: Eq a) (w1 :: Num a) (w2 :: Num p) (w3 :: a) -> case w of { GHC.Classes.C:Eq ww1 ww2 -> F11.$wfib @a @p ww1 w1 w2 w3 } ===================================== testsuite/tests/arityanal/should_compile/Arity16.stderr ===================================== @@ -5,7 +5,7 @@ Result size of Tidy Core = {terms: 52, types: 87, coercions: 0, joins: 0/0} Rec { -- RHS size: {terms: 15, types: 17, coercions: 0, joins: 0/0} map2 [Occ=LoopBreaker] :: forall {t} {a}. (t -> a) -> [t] -> [a] -[GblId, Arity=2, Str=, Unf=OtherCon []] +[GblId, Arity=2, Str=, Unf=OtherCon []] map2 = \ (@t) (@a) (f :: t -> a) (ds :: [t]) -> case ds of { ===================================== testsuite/tests/stranal/should_compile/T18894.hs ===================================== @@ -0,0 +1,28 @@ +{-# OPTIONS_GHC -O2 -fforce-recomp #-} + +-- | The point of this test is that @g*@ get's a demand that says +-- "whenever @g*@ is called, the second component of the pair is evaluated strictly". +module T18894 (h1, h2) where + +g1 :: Int -> (Int,Int) +g1 1 = (15, 0) +g1 n = (2 * n, 2 `div` n) +{-# NOINLINE g1 #-} + +h1 :: Int -> Int +h1 1 = 0 +-- Sadly, the @g1 2@ subexpression will be floated to top-level, where we +-- don't see the specific demand placed on it by @snd at . Tracked in #19001. +h1 2 = snd (g1 2) +h1 m = uncurry (+) (g1 m) + +g2 :: Int -> Int -> (Int,Int) +g2 m 1 = (m, 0) +g2 m n = (2 * m, 2 `div` n) +{-# NOINLINE g2 #-} + +h2 :: Int -> Int +h2 1 = 0 +h2 m + | odd m = snd (g2 m 2) + | otherwise = uncurry (+) (g2 2 m) ===================================== testsuite/tests/stranal/should_compile/T18894.stderr ===================================== @@ -0,0 +1,404 @@ + +==================== Demand analysis ==================== +Result size of Demand analysis + = {terms: 177, types: 97, coercions: 0, joins: 0/0} + +-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Prim.Addr# +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}] +$trModule = "main"# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Types.TrName +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +$trModule = GHC.Types.TrNameS $trModule + +-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Prim.Addr# +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] +$trModule = "T18894"# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Types.TrName +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +$trModule = GHC.Types.TrNameS $trModule + +-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} +T18894.$trModule :: GHC.Types.Module +[LclIdX, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +T18894.$trModule = GHC.Types.Module $trModule $trModule + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 0# + +-- RHS size: {terms: 36, types: 16, coercions: 0, joins: 0/0} +g2 [InlPrag=NOINLINE, Dmd=UCU(CS(P(1P(U),SP(U))))] + :: Int -> Int -> (Int, Int) +[LclId, + Arity=2, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [20 20] 161 20}] +g2 + = \ (m [Dmd=UP(U)] :: Int) (ds [Dmd=SP(SU)] :: Int) -> + case ds of { GHC.Types.I# ds [Dmd=SU] -> + case ds of ds [Dmd=1U] { + __DEFAULT -> + (case m of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.*# 2# y) }, + case ds of wild { + __DEFAULT -> + case GHC.Classes.divInt# 2# wild of ww4 { __DEFAULT -> + GHC.Types.I# ww4 + }; + -1# -> GHC.Types.I# -2#; + 0# -> case GHC.Real.divZeroError of wild [Dmd=B] { } + }); + 1# -> (m, lvl) + } + } + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 2# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 2# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 0# + +-- RHS size: {terms: 36, types: 19, coercions: 0, joins: 0/0} +h2 :: Int -> Int +[LclIdX, + Arity=1, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [20] 162 10}] +h2 + = \ (ds [Dmd=SP(MU)] :: Int) -> + case ds of wild [Dmd=UP(U)] { GHC.Types.I# ds [Dmd=MU] -> + case ds of ds { + __DEFAULT -> + case GHC.Prim.remInt# ds 2# of { + __DEFAULT -> + case g2 wild lvl of { (ds1 [Dmd=A], y [Dmd=SU]) -> y }; + 0# -> + case g2 lvl wild of { (x [Dmd=SP(U)], ds [Dmd=SP(U)]) -> + case x of { GHC.Types.I# x -> + case ds of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } + } + } + }; + 1# -> lvl + } + } + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 15# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 0# + +-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0} +lvl :: (Int, Int) +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = (lvl, lvl) + +-- RHS size: {terms: 30, types: 11, coercions: 0, joins: 0/0} +g1 [InlPrag=NOINLINE, Dmd=UCU(P(UP(U),UP(U)))] :: Int -> (Int, Int) +[LclId, + Arity=1, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [20] 141 10}] +g1 + = \ (ds [Dmd=SP(SU)] :: Int) -> + case ds of { GHC.Types.I# ds [Dmd=SU] -> + case ds of ds { + __DEFAULT -> + (GHC.Types.I# (GHC.Prim.*# 2# ds), + case ds of wild { + __DEFAULT -> + case GHC.Classes.divInt# 2# wild of ww4 { __DEFAULT -> + GHC.Types.I# ww4 + }; + -1# -> GHC.Types.I# -2#; + 0# -> case GHC.Real.divZeroError of wild [Dmd=B] { } + }); + 1# -> lvl + } + } + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 0# + +-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} +lvl :: (Int, Int) +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, + WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 30 0}] +lvl = g1 (GHC.Types.I# 2#) + +-- RHS size: {terms: 28, types: 18, coercions: 0, joins: 0/0} +h1 :: Int -> Int +[LclIdX, + Arity=1, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [20] 111 10}] +h1 + = \ (ds [Dmd=SP(MU)] :: Int) -> + case ds of wild [Dmd=1P(1U)] { GHC.Types.I# ds [Dmd=MU] -> + case ds of { + __DEFAULT -> + case g1 wild of { (x [Dmd=SP(U)], ds [Dmd=SP(U)]) -> + case x of { GHC.Types.I# x -> + case ds of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } + } + }; + 1# -> lvl; + 2# -> case lvl of { (ds1 [Dmd=A], y [Dmd=SU]) -> y } + } + } + + + + +==================== Demand analysis ==================== +Result size of Demand analysis + = {terms: 171, types: 120, coercions: 0, joins: 0/0} + +-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Prim.Addr# +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}] +$trModule = "main"# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Types.TrName +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +$trModule = GHC.Types.TrNameS $trModule + +-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Prim.Addr# +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}] +$trModule = "T18894"# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +$trModule :: GHC.Types.TrName +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +$trModule = GHC.Types.TrNameS $trModule + +-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} +T18894.$trModule :: GHC.Types.Module +[LclIdX, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +T18894.$trModule = GHC.Types.Module $trModule $trModule + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 0# + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# -2# + +-- RHS size: {terms: 32, types: 18, coercions: 0, joins: 0/0} +$wg2 [InlPrag=NOINLINE, Dmd=UCU(CS(P(1P(U),SP(U))))] + :: Int -> GHC.Prim.Int# -> (# Int, Int #) +[LclId, + Arity=2, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [20 30] 121 20}] +$wg2 + = \ (w [Dmd=UP(U)] :: Int) (ww [Dmd=SU] :: GHC.Prim.Int#) -> + case ww of ds { + __DEFAULT -> + (# case w of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.*# 2# y) }, + case ds of { + __DEFAULT -> + case GHC.Classes.divInt# 2# ds of ww4 { __DEFAULT -> + GHC.Types.I# ww4 + }; + -1# -> lvl; + 0# -> case GHC.Real.divZeroError of wild [Dmd=B] { } + } #); + 1# -> (# w, lvl #) + } + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 2# + +-- RHS size: {terms: 34, types: 21, coercions: 0, joins: 0/0} +$wh2 [InlPrag=[2]] :: GHC.Prim.Int# -> Int +[LclId, + Arity=1, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [30] 162 10}] +$wh2 + = \ (ww [Dmd=SU] :: GHC.Prim.Int#) -> + case ww of ds { + __DEFAULT -> + case GHC.Prim.remInt# ds 2# of { + __DEFAULT -> + case $wg2 (GHC.Types.I# ds) 2# of + { (# ww [Dmd=A], ww [Dmd=SU] #) -> + ww + }; + 0# -> + case $wg2 lvl ds of { (# ww [Dmd=SP(U)], ww [Dmd=SP(U)] #) -> + case ww of { GHC.Types.I# x -> + case ww of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } + } + } + }; + 1# -> lvl + } + +-- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0} +h2 [InlPrag=[2]] :: Int -> Int +[LclIdX, + Arity=1, + Str=, + Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, + Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) + Tmpl= \ (w [Occ=Once1!] :: Int) -> + case w of { GHC.Types.I# ww [Occ=Once1, Dmd=MU] -> $wh2 ww }}] +h2 + = \ (w [Dmd=SP(SU)] :: Int) -> + case w of { GHC.Types.I# ww [Dmd=SU] -> $wh2 ww } + +-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} +lvl :: Int +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +lvl = GHC.Types.I# 15# + +-- RHS size: {terms: 28, types: 15, coercions: 0, joins: 0/0} +$wg1 [InlPrag=NOINLINE, Dmd=UCU(P(UP(U),UP(U)))] + :: GHC.Prim.Int# -> (# Int, Int #) +[LclId, + Arity=1, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [30] 111 20}] +$wg1 + = \ (ww [Dmd=SU] :: GHC.Prim.Int#) -> + case ww of ds { + __DEFAULT -> + (# GHC.Types.I# (GHC.Prim.*# 2# ds), + case ds of { + __DEFAULT -> + case GHC.Classes.divInt# 2# ds of ww4 { __DEFAULT -> + GHC.Types.I# ww4 + }; + -1# -> lvl; + 0# -> case GHC.Real.divZeroError of wild [Dmd=B] { } + } #); + 1# -> (# lvl, lvl #) + } + +-- RHS size: {terms: 7, types: 9, coercions: 0, joins: 0/0} +lvl :: (Int, Int) +[LclId, + Unf=Unf{Src=, TopLvl=True, Value=False, ConLike=False, + WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 40 10}] +lvl = case $wg1 2# of { (# ww, ww #) -> (ww, ww) } + +-- RHS size: {terms: 25, types: 18, coercions: 0, joins: 0/0} +$wh1 [InlPrag=[2]] :: GHC.Prim.Int# -> Int +[LclId, + Arity=1, + Str=, + Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, Guidance=IF_ARGS [50] 101 10}] +$wh1 + = \ (ww [Dmd=SU] :: GHC.Prim.Int#) -> + case ww of ds [Dmd=1U] { + __DEFAULT -> + case $wg1 ds of { (# ww [Dmd=SP(U)], ww [Dmd=SP(U)] #) -> + case ww of { GHC.Types.I# x -> + case ww of { GHC.Types.I# y -> GHC.Types.I# (GHC.Prim.+# x y) } + } + }; + 1# -> lvl; + 2# -> case lvl of { (ds1 [Dmd=A], y [Dmd=SU]) -> y } + } + +-- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0} +h1 [InlPrag=[2]] :: Int -> Int +[LclIdX, + Arity=1, + Str=, + Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, + WorkFree=True, Expandable=True, + Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) + Tmpl= \ (w [Occ=Once1!] :: Int) -> + case w of { GHC.Types.I# ww [Occ=Once1, Dmd=MU] -> $wh1 ww }}] +h1 + = \ (w [Dmd=SP(SU)] :: Int) -> + case w of { GHC.Types.I# ww [Dmd=SU] -> $wh1 ww } + + + ===================================== testsuite/tests/stranal/should_compile/all.T ===================================== @@ -58,3 +58,5 @@ test('T18122', [ grep_errmsg(r'wfoo =') ], compile, ['-ddump-simpl']) # We care about the call demand on $wg test('T18903', [ grep_errmsg(r'Dmd=\S+C\S+') ], compile, ['-ddump-simpl -dsuppress-uniques']) +# We care about the call demand on $wg1 and $wg2 +test('T18894', [ grep_errmsg(r'Dmd=\S+C\S+') ], compile, ['-ddump-stranal -dsuppress-uniques']) ===================================== testsuite/tests/stranal/sigs/T5075.stderr ===================================== @@ -1,7 +1,7 @@ ==================== Strictness signatures ==================== T5075.$trModule: -T5075.loop: +T5075.loop: @@ -13,6 +13,6 @@ T5075.loop: ==================== Strictness signatures ==================== T5075.$trModule: -T5075.loop: +T5075.loop: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/549af6957748293cd497ccbef421c30666b56f31...3a7344fb01f296a88e8136de47a81a5d2448d795 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/549af6957748293cd497ccbef421c30666b56f31...3a7344fb01f296a88e8136de47a81a5d2448d795 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 Fri Nov 27 14:07:39 2020 From: gitlab at gitlab.haskell.org (Matthew Pickering) Date: Fri, 27 Nov 2020 09:07:39 -0500 Subject: [Git][ghc/ghc][wip/ghc-debug_partial_tso_stack_decode] 41 commits: Add Addr# atomic primops (#17751) Message-ID: <5fc1082be5901_86c111d4a005986d2@gitlab.mail> Matthew Pickering pushed to branch wip/ghc-debug_partial_tso_stack_decode at Glasgow Haskell Compiler / GHC Commits: 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - f04840cf by David Eichmann at 2020-11-27T09:07:36-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bb4fc4d48b81897e153e9e9fd5ab7aa1cb86527a...f04840cf047f81a0c14eab54dbf4f151db89c2d7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bb4fc4d48b81897e153e9e9fd5ab7aa1cb86527a...f04840cf047f81a0c14eab54dbf4f151db89c2d7 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 Fri Nov 27 17:02:44 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 12:02:44 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] nonmoving: Ensure that evacuated large objects are marked Message-ID: <5fc131343a0fe_86c111d4a00634741@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: 3450ff5b by GHC GitLab CI at 2020-11-27T12:02:26-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 2 changed files: - rts/sm/Evac.c - rts/sm/NonMoving.c Changes: ===================================== rts/sm/Evac.c ===================================== @@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) // // However, if we are in a deadlock detection GC then we disable aging // so there is no need. + // + // See Note [Non-moving GC: Marking evacuated objects]. if (major_gc && !deadlock_detect_gc) markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to); return to; @@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ +/* + * Note [Non-moving GC: Marking evacuated objects] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * When the non-moving collector is in use we must be careful to ensure that any + * references to objects in the non-moving generation from younger generations + * are pushed to the mark queue. + * + * In particular we need to ensure that we handle newly-promoted objects are + * correctly marked. For instance, consider this case: + * + * generation 0 generation 1 + * ────────────── ────────────── + * + * ┌───────┐ + * ┌───────┐ │ A │ + * │ B │ ◁────────────────────────── │ │ + * │ │ ──┬─────────────────┐ └───────┘ + * └───────┘ ┆ after GC │ + * ┆ │ + * ┌───────┐ ┆ before GC │ ┌───────┐ + * │ C │ ◁┄┘ └─────▷ │ C' │ + * │ │ │ │ + * └───────┘ └───────┘ + * + * + * In this case object C started off in generation 0 and was evacuated into + * generation 1 during the preparatory GC. However, the only reference to C' + * is from B, which lives in the generation 0 (via aging); this reference will + * not be visible to the concurrent non-moving collector (which can only + * traverse the generation 1 heap). Consequently, upon evacuating C we need to + * ensure that C' is added to the update remembered set as we know that it will + * continue to be reachable via B (which is assumed to be reachable as it lives + * in a younger generation). + * + * Where this happens depends upon the type of the object (e.g. C'): + * + * - In the case of "normal" small heap-allocated objects this happens in + * alloc_for_copy. + * - In the case of compact region this happens in evacuate_compact. + * - In the case of large objects this happens in evacuate_large. + * + * See also Note [Aging under the non-moving collector] in NonMoving.c. + * + */ + /* size is in words */ STATIC_INLINE GNUC_ATTR_HOT void copy_tag(StgClosure **p, const StgInfoTable *info, @@ -351,6 +399,9 @@ evacuate_large(StgPtr p) __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL); if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) p); } initBdescr(bd, new_gen, new_gen->to); @@ -505,6 +556,9 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -690,13 +744,6 @@ loop: */ if (flags & BF_LARGE) { evacuate_large((P_)q); - - // We may have evacuated the block to the nonmoving generation. If so - // we need to make sure it is added to the mark queue since the only - // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { - markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); - } return; } ===================================== rts/sm/NonMoving.c ===================================== @@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock; * - Note [Aging under the non-moving collector] (NonMoving.c) describes how * we accommodate aging * + * - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how + * non-moving objects reached by evacuate() are marked, which is necessary + * due to aging. + * * - Note [Large objects in the non-moving collector] (NonMovingMark.c) * describes how we track large objects. * @@ -317,6 +321,8 @@ Mutex concurrent_coll_finished_lock; * * The non-moving collector will come to C in the mark queue and mark it. * + * The implementation details of this are described in Note [Non-moving GC: + * Marking evacuated objects] in Evac.c. * * Note [Deadlock detection under the non-moving collector] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3450ff5b7bd3f5080b8fb1195701a815c72eb4ae -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3450ff5b7bd3f5080b8fb1195701a815c72eb4ae 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 Fri Nov 27 17:04:55 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 12:04:55 -0500 Subject: [Git][ghc/ghc][wip/T18234] 32 commits: Export indexError from GHC.Ix (#18579) Message-ID: <5fc131b72d5c4_86c879fa9c6364e2@gitlab.mail> Ben Gamari pushed to branch wip/T18234 at Glasgow Haskell Compiler / GHC Commits: 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 063738a0 by Sylvain Henry at 2020-11-27T11:34:37+01:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 6b15938b by Sylvain Henry at 2020-11-27T12:04:42-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - 4c3cee5b by Ben Gamari at 2020-11-27T12:04:42-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core/Lint.hs - + compiler/GHC/Core/Opt/CallerCC.hs - + compiler/GHC/Core/Opt/CallerCC.hs-boot - compiler/GHC/Core/Opt/CprAnal.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/Monad.hs - compiler/GHC/Core/Opt/Pipeline.hs - compiler/GHC/Core/Opt/SetLevels.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/Simplify/Utils.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/CoreToStg.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Monad.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Pipeline/Monad.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/HsToCore.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b789f5f997f1873116c52486198520db1abea2e6...4c3cee5b2409ac875d0365a4e0f98cfc5850a9f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b789f5f997f1873116c52486198520db1abea2e6...4c3cee5b2409ac875d0365a4e0f98cfc5850a9f4 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 Fri Nov 27 17:09:24 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 12:09:24 -0500 Subject: [Git][ghc/ghc][wip/hugepages] rts: Add support for hugepages Message-ID: <5fc132c44562_86c3fc6ab4f115c6386ee@gitlab.mail> Ben Gamari pushed to branch wip/hugepages at Glasgow Haskell Compiler / GHC Commits: ea17a1f1 by Ben Gamari at 2020-11-27T12:09:17-05:00 rts: Add support for hugepages - - - - - 3 changed files: - includes/rts/Flags.h - rts/RtsFlags.c - rts/posix/OSMem.c Changes: ===================================== includes/rts/Flags.h ===================================== @@ -89,6 +89,7 @@ typedef struct _GC_FLAGS { bool numa; /* Use NUMA */ StgWord numaMask; + bool hugepages; /* Enable hugepages support */ } GC_FLAGS; /* See Note [Synchronization of flags and base APIs] */ ===================================== rts/RtsFlags.c ===================================== @@ -181,6 +181,7 @@ void initRtsFlagsDefaults(void) RtsFlags.GcFlags.allocLimitGrace = (100*1024) / BLOCK_SIZE; RtsFlags.GcFlags.numa = false; RtsFlags.GcFlags.numaMask = 1; + RtsFlags.GcFlags.hugepages = false; RtsFlags.GcFlags.ringBell = false; RtsFlags.GcFlags.longGCSync = 0; /* detection turned off */ @@ -516,6 +517,7 @@ usage_text[] = { #endif " -xq The allocation limit given to a thread after it receives", " an AllocationLimitExceeded exception. (default: 100k)", +" -xH Use hugepages to allocate huge", "", " -Mgrace=", " The amount of allocation after the program receives a", @@ -1694,13 +1696,18 @@ error = true; */ case 'q': - OPTION_UNSAFE; - RtsFlags.GcFlags.allocLimitGrace - = decodeSize(rts_argv[arg], 3, BLOCK_SIZE, HS_INT_MAX) - / BLOCK_SIZE; - break; + OPTION_UNSAFE; + RtsFlags.GcFlags.allocLimitGrace + = decodeSize(rts_argv[arg], 3, BLOCK_SIZE, HS_INT_MAX) + / BLOCK_SIZE; + break; - default: + case 'H': + OPTION_SAFE; + RtsFlags.GcFlags.hugepages = true; + break; + + default: OPTION_SAFE; errorBelch("unknown RTS option: %s",rts_argv[arg]); error = true; ===================================== rts/posix/OSMem.c ===================================== @@ -472,6 +472,11 @@ void setExecutable (void *p, W_ len, bool exec) #if defined(USE_LARGE_ADDRESS_SPACE) +#if defined(MAP_HUGETLB) && defined(MAP_HUGE_2MB) +#define HUGEPAGE_SIZE (2*1024*1024) +#define HUGEPAGE_FLAGS (MAP_HUGETLB | MAP_HUGE_2MB) +#endif + static void * osTryReserveHeapMemory (W_ len, void *hint) { @@ -484,7 +489,16 @@ osTryReserveHeapMemory (W_ len, void *hint) because we need memory which is MBLOCK_SIZE aligned, and then we discard what we don't need */ - base = my_mmap(hint, len + MBLOCK_SIZE, MEM_RESERVE); +#if defined(HUGEPAGE_SIZE) + const bool hugepages = RtsFlags.GcFlags.hugepages ? HUGEPAGE_FLAGS : 0; +#else + const bool hugepages = 0; +#endif + base = my_mmap(hint, len + MBLOCK_SIZE, MEM_RESERVE | hugepages); + + // If failed then try again without hugepages + if (base == NULL && hugepages) + base = my_mmap(hint, len + MBLOCK_SIZE, MEM_RESERVE); if (base == NULL) return NULL; @@ -643,6 +657,18 @@ void *osReserveHeapMemory(void *startAddressPtr, W_ *len) void osCommitMemory(void *at, W_ size) { +#if defined(HUGEPAGE_SIZE) + // Try committing with hugepages, if available. + if (RtsFlags.GcFlags.hugepages + && ((uintptr_t) at & (HUGEPAGE_SIZE - 1) == 0) + && (size & (HUGEPAGE_SIZE - 1) == 0)) { + void *r = my_mmap(at, size, MEM_COMMIT | HUGEPAGE_FLAGS); + if (r != NULL) { + return; + } + } +#endif + void *r = my_mmap(at, size, MEM_COMMIT); if (r == NULL) { barf("Unable to commit %" FMT_Word " bytes of memory", size); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ea17a1f1dc628da0a85fec8774b2060f364a1c06 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ea17a1f1dc628da0a85fec8774b2060f364a1c06 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 Fri Nov 27 17:26:11 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 12:26:11 -0500 Subject: [Git][ghc/ghc][wip/facebook/ghc-8.8-unloading] 2 commits: rts: Introduce highMemDynamic Message-ID: <5fc136b3e54d2_86ce89fc5c64012b@gitlab.mail> Ben Gamari pushed to branch wip/facebook/ghc-8.8-unloading at Glasgow Haskell Compiler / GHC Commits: 7fa83863 by GHC GitLab CI at 2020-11-27T12:26:00-05:00 rts: Introduce highMemDynamic - - - - - 68d227d5 by GHC GitLab CI at 2020-11-27T12:26:00-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 26 changed files: - includes/rts/storage/GC.h - libffi-tarballs - libraries/Cabal - libraries/Win32 - libraries/array - libraries/binary - libraries/bytestring - libraries/containers - libraries/deepseq - libraries/directory - libraries/filepath - libraries/haskeline - libraries/hpc - libraries/parsec - libraries/process - libraries/stm - libraries/terminfo - libraries/text - libraries/time - libraries/unix - nofib - rts/sm/Storage.c - + testsuite/tests/rts/linker/Makefile - + testsuite/tests/rts/linker/all.T - + testsuite/tests/rts/linker_unload_native.c - + testsuite/tests/rts/linker_unload_native.stdout Changes: ===================================== includes/rts/storage/GC.h ===================================== @@ -227,6 +227,10 @@ void revertCAFs (void); // (preferably use RtsConfig.keep_cafs instead) void setKeepCAFs (void); +// Let the runtime know that all the CAFs in high mem are not +// to be retained. Useful in conjunction with loadNativeObj +void setHighMemDynamic (void); + /* ----------------------------------------------------------------------------- This is the write barrier for MUT_VARs, a.k.a. IORefs. A MUT_VAR_CLEAN object is not on the mutable list; a MUT_VAR_DIRTY ===================================== libffi-tarballs ===================================== @@ -1 +1 @@ -Subproject commit 96d02800759dcedb9c98a18a5797b86eb3b6e7c2 +Subproject commit 14c0d0caed5ffbcd4407a5eb1c27b744ef15b510 ===================================== libraries/Cabal ===================================== @@ -1 +1 @@ -Subproject commit 8199c3f838a15fb9b7c8d3527603084b2474d877 +Subproject commit d30b8f3ec0b0873b9d2eb245afdd53fabacdb884 ===================================== libraries/Win32 ===================================== @@ -1 +1 @@ -Subproject commit ca5fbc12851b98a52f96a43ea19c54c9ecf0f9e3 +Subproject commit d68374423fa3d3edd6b776e412e4093cc69b5f64 ===================================== libraries/array ===================================== @@ -1 +1 @@ -Subproject commit ba4d0dedd156009fbbe12a1ab8c96d537226a529 +Subproject commit 10e6c7e0522367677e4c33cc1c56eb852ef13420 ===================================== libraries/binary ===================================== @@ -1 +1 @@ -Subproject commit fcd9d3cb2a942c54347d28bcb80a1b46d2d7d673 +Subproject commit dfaf780596328c9184758452b78288e8f405fcc1 ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit 95fe6bdf13c9cc86c1c880164f7844d61d989574 +Subproject commit e043aacfc4202a59ccae8b8c8cf0e1ad83a3f209 ===================================== libraries/containers ===================================== @@ -1 +1 @@ -Subproject commit aaeda192b34a66b1c5359a85271adf8fed26dd12 +Subproject commit 648fdb95cb4cf406ed7364533de6314069e3ffa5 ===================================== libraries/deepseq ===================================== @@ -1 +1 @@ -Subproject commit a2d507af21a8f538b7c2fa129f0ce7ab6a7667dc +Subproject commit 0fd7fc88aded7d7a7a1c1250fd3dcd9152edba34 ===================================== libraries/directory ===================================== @@ -1 +1 @@ -Subproject commit 36bd1921258b759724a95ce56c5e880edf0972a2 +Subproject commit 0633b48b010093f64f98ee494265436e96456aed ===================================== libraries/filepath ===================================== @@ -1 +1 @@ -Subproject commit 39035d6433fff2356cf65747649666ed9b6e83e1 +Subproject commit e60969e693ffea59725cc3ebcae415343ddd0692 ===================================== libraries/haskeline ===================================== @@ -1 +1 @@ -Subproject commit fdc6c2cced525b8f8a95f38bfc45d9362785e9ae +Subproject commit 28ee26ad5b4ae1c0584f2ec11ac53be9671bf878 ===================================== libraries/hpc ===================================== @@ -1 +1 @@ -Subproject commit 42bb0059dc535948ce87b846611968c1c01ae049 +Subproject commit 59e6ba02f3fa5c8f4901b4ce21777c4a9beb14b6 ===================================== libraries/parsec ===================================== @@ -1 +1 @@ -Subproject commit 60dfb0cb6a711f141e5d8728af37de894e33795e +Subproject commit 905bc2e3e1c374934d49e16dc5b7c49bf2c3c815 ===================================== libraries/process ===================================== @@ -1 +1 @@ -Subproject commit 26ea79ceb2193a86f76a302a126be3319f22700d +Subproject commit 102f5ca98661d3a6118e6610e59579c715a8ffd1 ===================================== libraries/stm ===================================== @@ -1 +1 @@ -Subproject commit f9979c926ca539362b5a2412359750e8b498e53a +Subproject commit a439b76a645a903757d2410dd70fe44538f45759 ===================================== libraries/terminfo ===================================== @@ -1 +1 @@ -Subproject commit 6065302a4f75649f14397833766e82c8182935bf +Subproject commit 9add7edcc04a9a86aa84a7faea203b654da447d1 ===================================== libraries/text ===================================== @@ -1 +1 @@ -Subproject commit ebb98f3929360f3abb681dfca4caa8a190f9c5a8 +Subproject commit 80cb9ee2eb7141171171318bbd6760fe80012524 ===================================== libraries/time ===================================== @@ -1 +1 @@ -Subproject commit 5319bed3b14c21de5410ead88ec8aaa838d7339c +Subproject commit c25d6a76702b454426e149fb590da5cb69f3bd0a ===================================== libraries/unix ===================================== @@ -1 +1 @@ -Subproject commit bd2631b375f8c2e1d9f6c778065d0ef699cf853a +Subproject commit e079823775066bcab56b22842be6cce6e060fb9f ===================================== nofib ===================================== @@ -1 +1 @@ -Subproject commit f87d446b4e361cc82f219cf78917db9681af69b3 +Subproject commit cef118de79b16fc2dddc147393a46c20f126e4a3 ===================================== rts/sm/Storage.c ===================================== @@ -44,6 +44,7 @@ StgIndStatic *dyn_caf_list = NULL; StgIndStatic *debug_caf_list = NULL; StgIndStatic *revertible_caf_list = NULL; bool keepCAFs; +bool highMemDynamic; W_ large_alloc_lim; /* GC if n_large_blocks in any nursery * reaches this. */ @@ -427,7 +428,7 @@ newCAF(StgRegTable *reg, StgIndStatic *caf) bh = lockCAF(reg, caf); if (!bh) return NULL; - if(keepCAFs) + if(keepCAFs && !(highMemDynamic && (void*) caf > (void*) 0x80000000)) { // Note [dyn_caf_list] // If we are in GHCi _and_ we are using dynamic libraries, @@ -479,6 +480,12 @@ setKeepCAFs (void) keepCAFs = 1; } +void +setHighMemDynamic (void) +{ + highMemDynamic = 1; +} + // An alternate version of newCAF which is used for dynamically loaded // object code in GHCi. In this case we want to retain *all* CAFs in // the object code, because they might be demanded at any time from an ===================================== testsuite/tests/rts/linker/Makefile ===================================== @@ -0,0 +1,121 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +unsigned_reloc_macho_x64: + as -o unsigned_reloc_macho_x64.o unsigned_reloc_macho_x64.s + '$(TEST_HC)' $(TEST_HC_OPTS_NO_RTSOPTS) -v0 --make -no-rtsopts-suggestions -no-hs-main -o runner runner.c + ./runner unsigned_reloc_macho_x64.o getAnswer + +section_alignment: + cc -c -o section_alignment.o section_alignment.c + '$(TEST_HC)' $(TEST_HC_OPTS_NO_RTSOPTS) -v0 --make -no-rtsopts-suggestions -no-hs-main -o runner runner.c + ./runner section_alignment.o isAligned + +T2615-prep: + $(RM) libfoo_T2615.so + '$(TEST_HC)' $(TEST_HC_OPTS) -fPIC -c libfoo_T2615.c -o libfoo_T2615.o + '$(TEST_HC)' $(filter-out -rtsopts, $(TEST_HC_OPTS)) -shared -no-auto-link-packages libfoo_T2615.o -o libfoo_T2615.so + +#-------------------------------------------------------------------- +define run_T5435_v +$(RM) T5435_load_v_$(1) T5435_v_$(1)$(exeext) +'$(TEST_HC)' $(TEST_HC_OPTS) -optc-D$(HostOS)_HOST_OS -optc-DLOAD_CONSTR=$(2) -v0 -c T5435_$(1).c -o T5435_load_v_$(1).o +'$(TEST_HC)' $(TEST_HC_OPTS) -v0 T5435.hs -osuf main_v_$(1)_o -o T5435_v_$(1)$(exeext) +./T5435_v_$(1) v ./T5435_load_v_$(1).o +endef + +define run_T5435_dyn +$(RM) T5435_load_dyn_$(1) T5435_dyn_$(1)$(exeext) +'$(TEST_HC)' $(filter-out -rtsopts, $(TEST_HC_OPTS)) -optc-D$(HostOS)_HOST_OS -v0 -fPIC -shared -c T5435_$(1).c -osuf dyn_$(1)_o -o T5435_load_dyn_$(1)$(dllext) +'$(TEST_HC)' $(TEST_HC_OPTS) -v0 T5435.hs -osuf main_dyn_$(1)_o -o T5435_dyn_$(1)$(exeext) +./T5435_dyn_$(1) dyn ./T5435_load_dyn_$(1)$(dllext) +endef + +.PHONY: T5435_v_gcc +T5435_v_gcc : + $(call run_T5435_v,gcc,0) + +.PHONY: T5435_v_asm_a T5435_v_asm_b +T5435_v_asm_a : + $(call run_T5435_v,asm,0) +T5435_v_asm_b : + $(call run_T5435_v,asm,1) + +.PHONY: T5435_dyn_gcc +T5435_dyn_gcc : + $(call run_T5435_dyn,gcc) + +.PHONY: T5435_dyn_asm +T5435_dyn_asm : + $(call run_T5435_dyn,asm) + +#-------------------------------------------------------------------- +.PHONY: linker_unload +linker_unload: + $(RM) Test.o Test.hi + "$(TEST_HC)" $(TEST_HC_OPTS) -c Test.hs -v0 + # -rtsopts causes a warning + "$(TEST_HC)" LinkerUnload.hs -package ghc $(filter-out -rtsopts, $(TEST_HC_OPTS)) linker_unload.c -o linker_unload -no-hs-main -optc-Werror + ./linker_unload "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" + +.PHONY: linker_unload_native +linker_unload_native: + $(RM) Test.o Test.hi Test.a Test.so Test2.so + "$(TEST_HC)" $(TEST_HC_OPTS) -c Test.hs -v0 -dynamic -fPIC -o Test.a + # only libraries without DT_NEEDED are supported + "$(CC)" -shared -Wl,-Bsymbolic -nostdlib -o Test.so -Wl,-nostdlib \ + -Wl,--whole-archive Test.a + cp Test.so Test2.so + + # -rtsopts causes a warning + "$(TEST_HC)" LinkerUnload.hs -optl-Wl,--export-dynamic -package ghc \ + $(filter-out -rtsopts, $(TEST_HC_OPTS)) linker_unload_native.c \ + -o linker_unload_native -no-hs-main -optc-Werror + ./linker_unload_native \ + "`'$(TEST_HC)' $(TEST_HC_OPTS) --print-libdir | tr -d '\r'`" + +# ----------------------------------------------------------------------------- +# Testing failures in the RTS linker. We should be able to repeatedly +# load bogus object files of various kinds without crashing and +# without any memory leaks. +# +# Check for memory leaks manually by running e.g. +# +# make linker_error1 +# valgrind --leak-check=full --show-reachable=yes ./linker_error1 linker_error1_o.o + +# linker_error1: not a valid object file + +.PHONY: linker_error1 +linker_error1: + "$(TEST_HC)" -c linker_error.c -o linker_error1.o + "$(TEST_HC)" linker_error1.o -o linker_error1 -no-hs-main -optc-g -debug -threaded + ./linker_error1 linker_error.c + +# linker_error2: the object file has an unknown symbol (fails in +# resolveObjs()) + +.PHONY: linker_error2 +linker_error2: + "$(TEST_HC)" -c linker_error.c -o linker_error2.o + "$(TEST_HC)" -c linker_error2.c -o linker_error2_o.o + "$(TEST_HC)" linker_error2.o -o linker_error2 -no-hs-main -optc-g -debug -threaded + ./linker_error2 linker_error2_o.o + +# linker_error3: the object file duplicates an existing symbol (fails +# in loadObj()) + +.PHONY: linker_error3 +linker_error3: + "$(TEST_HC)" -c linker_error.c -o linker_error3.o + "$(TEST_HC)" -c linker_error3.c -o linker_error3_o.o + "$(TEST_HC)" linker_error3.o -o linker_error3 -no-hs-main -optc-g -debug -threaded + ./linker_error3 linker_error3_o.o + +.PHONY: T7072 +T7072: + "$(TEST_HC)" -c T7072-obj.c -o T7072-obj.o + "$(TEST_HC)" -c T7072-main.c -o T7072-main.o + "$(TEST_HC)" T7072-main.c -o T7072-main -no-hs-main -debug + ./T7072-main T7072-obj.o ===================================== testsuite/tests/rts/linker/all.T ===================================== @@ -0,0 +1,116 @@ +# -*-: mode: python -*- + +test('unsigned_reloc_macho_x64', + [ + extra_files(['runner.c', 'unsigned_reloc_macho_x64.s']), + unless(opsys('darwin'), skip), + unless(arch('x86_64'), skip) + ], + run_command, ['$MAKE -s --no-print-directory unsigned_reloc_macho_x64']) + +###################################### +test('section_alignment', + [ + extra_files(['runner.c', 'section_alignment.c']), + unless(opsys('darwin') and arch('x86_64'), expect_broken(13624)) + ], + run_command, ['$MAKE -s --no-print-directory section_alignment']) + +###################################### +# Test to see if linker scripts link properly to real ELF files +test('T2615', + [extra_files(['libfoo_T2615.c', 'libfoo_script_T2615.so']), + when(opsys('mingw32'), skip), + # OS X doesn't seem to support linker scripts + when(opsys('darwin'), skip), + # Solaris' linker does not support GNUish linker scripts + when(opsys('solaris2'), skip), + pre_cmd('$MAKE -s --no-print-directory T2615-prep'), + # Add current directory to dlopen search path + cmd_prefix('LD_LIBRARY_PATH=$LD_LIBRARY_PATH:. '), + extra_clean(['libfoo_T2615.so', 'libfoo_T2615.o'])], + compile_and_run, + ['-package ghc']) + +###################################### +# Workaround bug #8458: old dlopen opens sections in the wrong order, +# so we just accept both orders. +def checkDynAsm(actual_file, normaliser): + actual_raw = read_no_crs(actual_file) + actual_str = normaliser(actual_raw) + actual = actual_str.split() + if actual == ['initArray1', 'initArray2', 'success']: + return True + elif opsys('darwin') and actual == ['modInitFunc1', 'modInitFunc2', 'success']: + return True + elif opsys('mingw32') and actual == ['ctors1', 'ctors2', 'success']: + return True + else: + if_verbose(1, 'T5435_dyn_asm failed with %s, see all.T for details' % actual) + return False + +# T5435_v_asm got split into two tests because depending +# on the linker, .init_array and .ctors sections are loaded +# in a different order (but all entries within a section +# do get loaded in a deterministic order). So we test each +# separately now. +# These should have extra_clean() arguments, but I need +# to somehow extract out the name of DLLs to do that +test('T5435_v_asm_a', + [extra_files(['T5435.hs', 'T5435_asm.c']), + req_rts_linker, + when(arch('arm'), expect_broken(17559))], + makefile_test, ['T5435_v_asm_a']) +# this one just needs to run on linux, as darwin/mingw32 are covered +# by the _a test already. +test('T5435_v_asm_b', + [extra_files(['T5435.hs', 'T5435_asm.c']), + req_rts_linker, + when(arch('arm'), expect_broken(17559)), + when(opsys('darwin') or opsys('mingw32'), skip)], + makefile_test, ['T5435_v_asm_b']) +test('T5435_v_gcc', + [extra_files(['T5435.hs', 'T5435_gcc.c']), + req_rts_linker, + when(arch('arm'), expect_broken(17559))], + makefile_test, ['T5435_v_gcc']) +test('T5435_dyn_asm', + [extra_files(['T5435.hs', 'T5435_asm.c']), + check_stdout(checkDynAsm)], + makefile_test, ['T5435_dyn_asm']) +test('T5435_dyn_gcc', extra_files(['T5435.hs', 'T5435_gcc.c']) , makefile_test, ['T5435_dyn_gcc']) + +###################################### +test('linker_unload', + [extra_files(['LinkerUnload.hs', 'Test.hs']), req_rts_linker], + makefile_test, ['linker_unload']) + +test('linker_unload_native', + [extra_files(['LinkerUnload.hs', 'Test.hs']), req_rts_linker, + when(opsys('darwin') or opsys('mingw32'), skip)], + makefile_test, ['linker_unload_native']) + +###################################### +test('linker_error1', [extra_files(['linker_error.c']), + ignore_stderr], makefile_test, ['linker_error1']) + +test('linker_error2', [extra_files(['linker_error.c']), + ignore_stderr], makefile_test, ['linker_error2']) + +test('linker_error3', [extra_files(['linker_error.c']), + ignore_stderr], makefile_test, ['linker_error3']) + +###################################### +test('rdynamic', [ unless(opsys('linux') or opsys('mingw32'), skip) + # this needs runtime infrastructure to do in ghci: + # '-rdynamic' ghc, load modules only via dlopen(RTLD_BLOBAL) and more. + , omit_ways(['ghci']) + ], + compile_and_run, ['-rdynamic -package ghc']) + + +test('T7072', + [extra_files(['T7072-main.c', 'T7072-obj.c']), + unless(opsys('linux'), skip), + req_rts_linker], + makefile_test, ['T7072']) ===================================== testsuite/tests/rts/linker_unload_native.c ===================================== @@ -0,0 +1,93 @@ +#include "ghcconfig.h" +#include +#include +#include "Rts.h" +#include +#include + +// poke into linker internals +extern void *objects; + +#define ITERATIONS 1000 + +#if defined(mingw32_HOST_OS) +#define OBJPATH L"Test.so" +#define OBJPATH2 L"Test2.so" +#else +#define OBJPATH "./Test.so" +#define OBJPATH2 "./Test2.so" +#endif + +typedef int testfun(int); + +extern void loadPackages(void); + +int main (int argc, char *argv[]) +{ + testfun *f, *f2; + int i, r; + + RtsConfig conf = defaultRtsConfig; + conf.rts_opts_enabled = RtsOptsAll; + // we want to preserve static CAFs and unload dynamic CAFs + conf.keep_cafs = true; + setHighMemDynamic(); + hs_init_ghc(&argc, &argv, conf); + + initLinker_(0); + + loadPackages(); + + for (i=0; i < ITERATIONS; i++) { + char* errmsg; + // load 2 libraries at once + void* handle = loadNativeObj(OBJPATH, &errmsg); + if (!handle) { + errorBelch("loadNativeObj(%s) failed: %s", OBJPATH, errmsg); + free(errmsg); + exit(1); + } + + void* handle2 = loadNativeObj(OBJPATH2, &errmsg); + if (!handle2) { + errorBelch("loadNativeObj(%s) failed: %s", OBJPATH2, errmsg); + free(errmsg); + exit(1); + } +#if LEADING_UNDERSCORE + f = dlsym(handle, "_f"); + f2 = dlsym(handle2, "_f"); +#else + f = dlsym(handle, "f"); + f2 = dlsym(handle2, "f"); +#endif + if (!f) { + errorBelch("dlsym failed"); + exit(1); + } + r = f(3); + if (r != 4) { + errorBelch("call failed; %d", r); + exit(1); + } + if (!f2) { + errorBelch("dlsym failed"); + exit(1); + } + r = f2(3); + if (r != 4) { + errorBelch("call failed; %d", r); + exit(1); + } + unloadNativeObj(handle); + unloadNativeObj(handle2); + performMajorGC(); + printf("%d ", i); + fflush(stdout); + } + + // Verify that Test.so isn't still loaded. + int res = getObjectLoadStatus("Test.so") != OBJECT_NOT_LOADED; + hs_exit(); + exit(res); +} ===================================== testsuite/tests/rts/linker_unload_native.stdout ===================================== @@ -0,0 +1,3 @@ +[1 of 1] Compiling LinkerUnload ( LinkerUnload.hs, LinkerUnload.o ) +Linking linker_unload_native ... +0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399 400 401 402 403 404 405 406 407 408 409 410 411 412 413 414 415 416 417 418 419 420 421 422 423 424 425 426 427 428 429 430 431 432 433 434 435 436 437 438 439 440 441 442 443 444 445 446 447 448 449 450 451 452 453 454 455 456 457 458 459 460 461 462 463 464 465 466 467 468 469 470 471 472 473 474 475 476 477 478 479 480 481 482 483 484 485 486 487 488 489 490 491 492 493 494 495 496 497 498 499 500 501 502 503 504 505 506 507 508 509 510 511 512 513 514 515 516 517 518 519 520 521 522 523 524 525 526 527 528 529 530 531 532 533 534 535 536 537 538 539 540 541 542 543 544 545 546 547 548 549 550 551 552 553 554 555 556 557 558 559 560 561 562 563 564 565 566 567 568 569 570 571 572 573 574 575 576 577 578 579 580 581 582 583 584 585 586 587 588 589 590 591 592 593 594 595 596 597 598 599 600 601 602 603 604 605 606 607 608 609 610 611 612 613 614 615 616 617 618 619 620 621 622 623 624 625 626 627 628 629 630 631 632 633 634 635 636 637 638 639 640 641 642 643 644 645 646 647 648 649 650 651 652 653 654 655 656 657 658 659 660 661 662 663 664 665 666 667 668 669 670 671 672 673 674 675 676 677 678 679 680 681 682 683 684 685 686 687 688 689 690 691 692 693 694 695 696 697 698 699 700 701 702 703 704 705 706 707 708 709 710 711 712 713 714 715 716 717 718 719 720 721 722 723 724 725 726 727 728 729 730 731 732 733 734 735 736 737 738 739 740 741 742 743 744 745 746 747 748 749 750 751 752 753 754 755 756 757 758 759 760 761 762 763 764 765 766 767 768 769 770 771 772 773 774 775 776 777 778 779 780 781 782 783 784 785 786 787 788 789 790 791 792 793 794 795 796 797 798 799 800 801 802 803 804 805 806 807 808 809 810 811 812 813 814 815 816 817 818 819 820 821 822 823 824 825 826 827 828 829 830 831 832 833 834 835 836 837 838 839 840 841 842 843 844 845 846 847 848 849 850 851 852 853 854 855 856 857 858 859 860 861 862 863 864 865 866 867 868 869 870 871 872 873 874 875 876 877 878 879 880 881 882 883 884 885 886 887 888 889 890 891 892 893 894 895 896 897 898 899 900 901 902 903 904 905 906 907 908 909 910 911 912 913 914 915 916 917 918 919 920 921 922 923 924 925 926 927 928 929 930 931 932 933 934 935 936 937 938 939 940 941 942 943 944 945 946 947 948 949 950 951 952 953 954 955 956 957 958 959 960 961 962 963 964 965 966 967 968 969 970 971 972 973 974 975 976 977 978 979 980 981 982 983 984 985 986 987 988 989 990 991 992 993 994 995 996 997 998 999 \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/958aba5ae6b579646c3c8055b1c9d3c17c3bbb03...68d227d5da4028fbb1e79cf8d743d25bfd47605b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/958aba5ae6b579646c3c8055b1c9d3c17c3bbb03...68d227d5da4028fbb1e79cf8d743d25bfd47605b 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 Fri Nov 27 17:31:33 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 12:31:33 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] 16 commits: rts: Post ticky entry counts to the eventlog Message-ID: <5fc137f5e2733_86ce89fc5c640316@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 29e7322e by Ben Gamari at 2020-11-27T17:31:07+00:00 rts/linker: Don't allow shared libraries to be loaded multiple times - - - - - cdc12086 by Ben Gamari at 2020-11-27T17:31:07+00:00 rts/linker: Initialise CCSs from native shared objects - - - - - ca3d02f6 by Ben Gamari at 2020-11-27T17:31:07+00:00 rts/linker: Move shared library loading logic into Elf.c - - - - - 28e537b5 by GHC GitLab CI at 2020-11-27T17:31:07+00:00 rts/linker: Don't declare dynamic objects with image_mapped This previously resulted in warnings due to spurious unmap failures. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Session.hs - compiler/ghc.cabal.in - docs/users_guide/debugging.rst - docs/users_guide/eventlog-formats.rst - docs/users_guide/expected-undocumented-flags.txt - docs/users_guide/profiling.rst - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/RtsAPI.h - includes/rts/EventLogFormat.h - includes/rts/EventLogWriter.h - includes/rts/Flags.h - libraries/Cabal - libraries/base/Debug/Trace.hs - libraries/directory - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/hpc - libraries/time - libraries/unix - rts/Capability.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c463ca00e278f0db179f60e75bebc5729ed80263...28e537b5b86da7a1ea821fd7950650e6aa751658 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c463ca00e278f0db179f60e75bebc5729ed80263...28e537b5b86da7a1ea821fd7950650e6aa751658 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 Fri Nov 27 17:44:00 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Fri, 27 Nov 2020 12:44:00 -0500 Subject: [Git][ghc/ghc][wip/T18599] 542 commits: Do not print synonyms in :i (->), :i Type (#18594) Message-ID: <5fc13ae01aaa3_86ce89fc5c6425f4@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - b3915e9c by Shayne Fletcher at 2020-11-27T12:43:10-05:00 Record dot syntax - - - - - 19 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b55cfb6777e4d32be25d2c4f6ea67a0f03be049b...b3915e9c503854839651b8b6917c1fef4d10f7b7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b55cfb6777e4d32be25d2c4f6ea67a0f03be049b...b3915e9c503854839651b8b6917c1fef4d10f7b7 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 Fri Nov 27 18:01:47 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 13:01:47 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] 2 commits: rts/linker: Move shared library loading logic into Elf.c Message-ID: <5fc13f0bc3b8_86ce89fc5c64444c@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: 0fd2288e by Ben Gamari at 2020-11-27T18:01:19+00:00 rts/linker: Move shared library loading logic into Elf.c - - - - - ea36515e by GHC GitLab CI at 2020-11-27T18:01:19+00:00 rts/linker: Don't declare dynamic objects with image_mapped This previously resulted in warnings due to spurious unmap failures. - - - - - 4 changed files: - rts/Linker.c - rts/LinkerInternals.h - rts/linker/Elf.c - rts/linker/Elf.h Changes: ===================================== rts/Linker.c ===================================== @@ -64,7 +64,6 @@ # include "linker/Elf.h" # include // regex is already used by dlopen() so this is OK // to use here without requiring an additional lib -# include #elif defined(OBJFORMAT_PEi386) # include "linker/PEi386.h" # include @@ -171,8 +170,6 @@ Mutex linker_mutex; /* Generic wrapper function to try and Resolve and RunInit oc files */ int ocTryLoad( ObjectCode* oc ); -static void freeNativeCode_ELF (ObjectCode *nc); - /* Link objects into the lower 2Gb on x86_64 and AArch64. GHC assumes the * small memory model on this architecture (see gcc docs, * -mcmodel=small). @@ -399,7 +396,7 @@ static void *dl_prog_handle; static regex_t re_invalid; static regex_t re_realso; #if defined(THREADED_RTS) -static Mutex dl_mutex; // mutex to protect dlopen/dlerror critical section +Mutex dl_mutex; // mutex to protect dlopen/dlerror critical section #endif #endif @@ -1871,7 +1868,7 @@ HsInt purgeObj (pathchar *path) return r; } -static OStatus getObjectLoadStatus_ (pathchar *path) +OStatus getObjectLoadStatus_ (pathchar *path) { for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { @@ -1961,141 +1958,6 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc, size, kind )); } - -# if defined(OBJFORMAT_ELF) -static int loadNativeObjCb_(struct dl_phdr_info *info, - size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { - ObjectCode* nc = (ObjectCode*) data; - - // This logic mimicks _dl_addr_inside_object from glibc - // For reference: - // int - // internal_function - // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) - // { - // int n = l->l_phnum; - // const ElfW(Addr) reladdr = addr - l->l_addr; - // - // while (--n >= 0) - // if (l->l_phdr[n].p_type == PT_LOAD - // && reladdr - l->l_phdr[n].p_vaddr >= 0 - // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) - // return 1; - // return 0; - // } - - if ((void*) info->dlpi_addr == nc->l_addr) { - int n = info->dlpi_phnum; - while (--n >= 0) { - if (info->dlpi_phdr[n].p_type == PT_LOAD) { - NativeCodeRange* ncr = - stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); - ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); - ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); - - ncr->next = nc->nc_ranges; - nc->nc_ranges = ncr; - } - } - } - return 0; -} - -static void copyErrmsg(char** errmsg_dest, char* errmsg) { - if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; - *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); - strcpy(*errmsg_dest, errmsg); -} - -// need dl_mutex -static void freeNativeCode_ELF (ObjectCode *nc) { - dlclose(nc->dlopen_handle); - - NativeCodeRange *ncr = nc->nc_ranges; - while (ncr) { - NativeCodeRange* last_ncr = ncr; - ncr = ncr->next; - stgFree(last_ncr); - } -} - -static void * loadNativeObj_ELF (pathchar *path, char **errmsg) -{ - ObjectCode* nc; - void *hdl, *retval; - - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); - - retval = NULL; - ACQUIRE_LOCK(&dl_mutex); - - /* Loading the same object multiple times will lead to chaos - * as we will have two ObjectCodes but one underlying dlopen - * handle. Fail if this happens. - */ - if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { - copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); - goto dlopen_fail; - } - - nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, true, NULL, 0); - - foreignExportsLoadingObject(nc); - hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); - foreignExportsFinishedLoadingObject(); - if (hdl == NULL) { - /* dlopen failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlopen_fail; - } - - struct link_map *map; - if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { - /* dlinfo failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlinfo_fail; - } - - nc->l_addr = (void*) map->l_addr; - nc->dlopen_handle = hdl; - hdl = NULL; // pass handle ownership to nc - - dl_iterate_phdr(loadNativeObjCb_, nc); - if (!nc->nc_ranges) { - copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); - goto dl_iterate_phdr_fail; - } - - insertOCSectionIndices(nc); - - nc->next_loaded_object = loaded_objects; - loaded_objects = nc; - - retval = nc->dlopen_handle; - -#if defined(PROFILING) - // collect any new cost centres that were defined in the loaded object. - refreshProfilingCCSs(); -#endif - - goto success; - -dl_iterate_phdr_fail: - // already have dl_mutex - freeNativeCode_ELF(nc); -dlinfo_fail: - if (hdl) dlclose(hdl); -dlopen_fail: -success: - - RELEASE_LOCK(&dl_mutex); - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); - - return retval; -} - -# endif - #define UNUSED(x) (void)(x) void * loadNativeObj (pathchar *path, char **errmsg) ===================================== rts/LinkerInternals.h ===================================== @@ -306,6 +306,10 @@ typedef struct _ObjectCode { #if defined(THREADED_RTS) extern Mutex linker_mutex; + +#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) +extern Mutex dl_mutex; +#endif #endif /* Type of the initializer */ @@ -388,6 +392,7 @@ resolveSymbolAddr (pathchar* buffer, int size, #endif HsInt isAlreadyLoaded( pathchar *path ); +OStatus getObjectLoadStatus_ (pathchar *path); HsInt loadOc( ObjectCode* oc ); ObjectCode* mkOc( ObjectType type, pathchar *path, char *image, int imageSize, bool mapped, pathchar *archiveMemberName, ===================================== rts/linker/Elf.c ===================================== @@ -15,15 +15,19 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" +#include "CheckUnload.h" +#include "LinkerInternals.h" #include "linker/Elf.h" #include "linker/CacheFlush.h" #include "linker/M32Alloc.h" #include "linker/SymbolExtras.h" +#include "ForeignExports.h" #include "sm/OSMem.h" #include "GetEnv.h" #include "linker/util.h" #include "linker/elf_util.h" +#include #include #include #if defined(HAVE_SYS_STAT_H) @@ -1969,6 +1973,143 @@ int ocRunInit_ELF( ObjectCode *oc ) return 1; } +/* + * Shared object loading + */ + +static int loadNativeObjCb_(struct dl_phdr_info *info, + size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { + ObjectCode* nc = (ObjectCode*) data; + + // This logic mimicks _dl_addr_inside_object from glibc + // For reference: + // int + // internal_function + // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) + // { + // int n = l->l_phnum; + // const ElfW(Addr) reladdr = addr - l->l_addr; + // + // while (--n >= 0) + // if (l->l_phdr[n].p_type == PT_LOAD + // && reladdr - l->l_phdr[n].p_vaddr >= 0 + // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) + // return 1; + // return 0; + // } + + if ((void*) info->dlpi_addr == nc->l_addr) { + int n = info->dlpi_phnum; + while (--n >= 0) { + if (info->dlpi_phdr[n].p_type == PT_LOAD) { + NativeCodeRange* ncr = + stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); + ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); + ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); + + ncr->next = nc->nc_ranges; + nc->nc_ranges = ncr; + } + } + } + return 0; +} + +static void copyErrmsg(char** errmsg_dest, char* errmsg) { + if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; + *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); + strcpy(*errmsg_dest, errmsg); +} + +// need dl_mutex +void freeNativeCode_ELF (ObjectCode *nc) { + dlclose(nc->dlopen_handle); + + NativeCodeRange *ncr = nc->nc_ranges; + while (ncr) { + NativeCodeRange* last_ncr = ncr; + ncr = ncr->next; + stgFree(last_ncr); + } +} + +void * loadNativeObj_ELF (pathchar *path, char **errmsg) +{ + ObjectCode* nc; + void *hdl, *retval; + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); + + retval = NULL; + ACQUIRE_LOCK(&dl_mutex); + + /* Loading the same object multiple times will lead to chaos + * as we will have two ObjectCodes but one underlying dlopen + * handle. Fail if this happens. + */ + if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { + copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); + goto dlopen_fail; + } + + nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, false, NULL, 0); + + foreignExportsLoadingObject(nc); + hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); + foreignExportsFinishedLoadingObject(); + if (hdl == NULL) { + /* dlopen failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlopen_fail; + } + + struct link_map *map; + if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { + /* dlinfo failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlinfo_fail; + } + + nc->l_addr = (void*) map->l_addr; + nc->dlopen_handle = hdl; + hdl = NULL; // pass handle ownership to nc + + dl_iterate_phdr(loadNativeObjCb_, nc); + if (!nc->nc_ranges) { + copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); + goto dl_iterate_phdr_fail; + } + + insertOCSectionIndices(nc); + + nc->next_loaded_object = loaded_objects; + loaded_objects = nc; + + retval = nc->dlopen_handle; + +#if defined(PROFILING) + // collect any new cost centres that were defined in the loaded object. + refreshProfilingCCSs(); +#endif + + goto success; + +dl_iterate_phdr_fail: + // already have dl_mutex + freeNativeCode_ELF(nc); +dlinfo_fail: + if (hdl) dlclose(hdl); +dlopen_fail: +success: + + RELEASE_LOCK(&dl_mutex); + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); + + return retval; +} + + /* * PowerPC & X86_64 ELF specifics */ ===================================== rts/linker/Elf.h ===================================== @@ -14,5 +14,7 @@ int ocGetNames_ELF ( ObjectCode* oc ); int ocResolve_ELF ( ObjectCode* oc ); int ocRunInit_ELF ( ObjectCode* oc ); int ocAllocateExtras_ELF ( ObjectCode *oc ); +void freeNativeCode_ELF ( ObjectCode *nc ); +void *loadNativeObj_ELF ( pathchar *path, char **errmsg ); #include "EndPrivate.h" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/28e537b5b86da7a1ea821fd7950650e6aa751658...ea36515eeda8132513fc26d60731b1c6907b5baa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/28e537b5b86da7a1ea821fd7950650e6aa751658...ea36515eeda8132513fc26d60731b1c6907b5baa 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 Fri Nov 27 18:18:22 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Fri, 27 Nov 2020 13:18:22 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fc142eeb9f9e_86cfd752bc6509b@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: d73ad2d6 by Shayne Fletcher at 2020-11-27T13:18:05-05:00 Record dot syntax - - - - - 28 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3728,6 +3728,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,9 @@ {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE UndecidableInstances #-} -- Wrinkle in Note [Trees That Grow] -- in module GHC.Hs.Extension +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -240,6 +243,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pu_flds :: [Located FastString] + , pu_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate { pu_flds = flds, pu_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -459,6 +482,51 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_field :: Located FastString + , gf_getField :: LHsExpr p -- Desugared equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnComma, 'GHC.Parser.Annotation.AnnDot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Desugared equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_flds :: [Located FastString] + , proj_proj :: LHsExpr p -- Desugared equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -654,6 +722,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1188,6 +1268,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_field = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_flds = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1346,6 +1434,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -557,6 +557,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -277,6 +277,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1154,6 +1154,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -64,7 +67,7 @@ import GHC.Utils.Outputable import GHC.Utils.Misc ( looksLikePackageName, fstOf3, sndOf3, thdOf3 ) import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, occNameFS ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, occNameFS, mkVarOcc, occNameString) import GHC.Types.SrcLoc import GHC.Types.Basic import GHC.Types.Fixity @@ -641,6 +644,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } PREFIX_PERCENT { L _ ITpercent } -- for linear types @@ -2711,6 +2716,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2800,10 +2821,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2832,6 +2855,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2881,6 +2912,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3297,33 +3336,63 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError $ Error ErrNamedFieldPunsNotEnabled [] l + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3617,6 +3686,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Errors.hs ===================================== @@ -148,6 +148,9 @@ data ErrorDesc | ErrDotsInRecordUpdate -- ^ Dots used in record update + | ErrRecordDotSyntaxInvalid + -- ^ Invalid use of record-dot-syntax + | ErrPrecedenceOutOfRange !Int -- ^ Precedence out of range @@ -335,6 +338,9 @@ data ErrorDesc | ErrExpectedHyphen -- ^ Expected a hyphen + | ErrNamedFieldPunsNotEnabled + -- ^ Named field puns should be enabled + | ErrSpaceInSCC -- ^ Found a space in a SCC ===================================== compiler/GHC/Parser/Errors/Ppr.hs ===================================== @@ -233,6 +233,9 @@ pp_err = \case ErrDotsInRecordUpdate -> text "You cannot use `..' in a record update" + ErrRecordDotSyntaxInvalid + -> text "Use of RecordDotSyntax `.' not valid." + ErrPrecedenceOutOfRange i -> text "Precedence out of range: " <> int i @@ -537,6 +540,9 @@ pp_err = \case ErrExpectedHyphen -> text "Expected a hyphen" + ErrNamedFieldPunsNotEnabled + -> text "For this to work enable NamedFieldPuns" + ErrSpaceInSCC -> text "Spaces are not allowed in SCCs" @@ -610,4 +616,3 @@ pp_hint = \case perhaps_as_pat :: SDoc perhaps_as_pat = text "Perhaps you meant an as-pattern, which must not be surrounded by whitespace" - ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -616,6 +616,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -777,6 +790,7 @@ data Token | ITpercent -- Prefix (%) only, e.g. a %1 -> b | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1594,6 +1608,9 @@ varsym_prefix = sym $ \span exts s -> | s == fsLit "-" -> return ITprefixminus -- Only when LexicalNegation is on, otherwise we get ITminus -- and don't hit this code path. See Note [Minus tokens] + | s == fsLit ".", RecordDotSyntaxBit `xtest` exts -> + return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> @@ -1614,8 +1631,10 @@ varsym_suffix = sym $ \span _ s -> -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \span _ s -> +varsym_tight_infix = sym $ \span exts s -> if | s == fsLit "@" -> return ITat + | s == fsLit ".", RecordDotSyntaxBit `xtest` exts -> return (ITproj False) + | s == fsLit "." -> return ITdot | otherwise -> do { addWarning Opt_WarnOperatorWhitespace $ WarnOperatorWhitespace (mkSrcSpanPs span) s @@ -1624,7 +1643,11 @@ varsym_tight_infix = sym $ \span _ s -> -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ _ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ _ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_span _exts s -> return $ ITconsym s) @@ -1632,8 +1655,13 @@ consym = sym (\_span _exts s -> return $ ITconsym s) sym :: (PsSpan -> ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con span exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2639,6 +2667,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2715,6 +2745,8 @@ mkParserOpts warningFlags extensionFlags .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} @@ -15,6 +16,7 @@ -- Functions over HsSyn specialised to RdrName. module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -27,7 +29,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -135,6 +137,7 @@ import GHC.Data.Maybe import GHC.Data.Bag import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Flags ( WarningFlag(..) ) @@ -148,6 +151,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1267,6 +1286,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1323,10 +1344,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1345,7 +1367,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1394,6 +1415,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = addFatalError $ Error ErrRecordDotSyntaxInvalid [] l mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1424,8 +1446,11 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError $ Error ErrRecordDotSyntaxInvalid [] l + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1451,6 +1476,7 @@ instance DisambECP (HsExpr GhcPs) where addError $ Error (ErrArrowCmdInExpr c) [] l return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1480,8 +1506,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (hsTypeToHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1509,6 +1535,7 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError $ Error (ErrArrowExprInPat e) [] l mkHsLamPV l _ = addFatalError $ Error ErrLambdaInPat [] l mkHsLetPV l _ _ = addFatalError $ Error ErrLetInPat [] l + mkHsProjUpdatePV l _ _ = addFatalError $ Error ErrRecordDotSyntaxInvalid [] l type InfixOp (PatBuilder GhcPs) = RdrName superInfixOp m = m mkHsOpAppPV l p1 op p2 = return $ L l $ PatBuilderOpApp p1 op p2 @@ -1534,9 +1561,13 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError $ Error ErrRecordDotSyntaxInvalid [] l + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2132,17 +2163,50 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _lrec (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError $ Error ErrRecordDotSyntaxInvalid [] (getLoc (head ps)) + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError $ Error ErrDotsInRecordUpdate [] dd_loc - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2629,3 +2693,132 @@ mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok)) starSym :: Bool -> String starSym True = "★" starSym False = "*" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fieldS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @field x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (field : fieldS) = foldl' f (proj field) fieldS + where + f acc field = (mkParen . mkOpApp (proj field) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg field calcuates a get_field @field arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg field = head $ mkGet' [arg] field +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ field) = get_field `mkAppType` mkSelector field `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg field = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_field = field + , gf_getField = mkGet arg field + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible has happened!" +mkProjection loc flds = + L loc Projection { + proj_ext = noExtField + , proj_flds = flds + , proj_proj = mkProj flds + } + +-- e.g. foo.bar.baz.quux = 1 +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate _ [] _ = panic "mkProjUpdate: The impossible has happened!" +mkProjUpdate loc flds arg = + L loc ProjUpdate { + pu_flds = flds + , pu_arg = arg + } + +-- mkSet a field b calculates a set_field @field expression. +-- e.g mkSet a field b = set_field @"field" a b (read as "set field 'field' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ field) b = set_field `mkAppType` mkSelector field `mkApp` a `mkApp` b + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pu_flds = flds, pu_arg = arg } )) + = let { + ; final = last flds -- quux + ; fields = init flds -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (field, g) = mkSet (mkParen g) field (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pu_flds = fs, pu_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -927,6 +927,17 @@ tcExpr expr@(RecordUpd { rupd_expr = record_expr, rupd_flds = rbnds }) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -493,6 +493,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -505,6 +507,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -174,3 +174,8 @@ test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) test('T12446', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d73ad2d65fba8ae01978a6c0270147d6ac6199e7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d73ad2d65fba8ae01978a6c0270147d6ac6199e7 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 Fri Nov 27 18:19:36 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 13:19:36 -0500 Subject: [Git][ghc/ghc][wip/win32-m32] 16 commits: Bump time submodule to 1.11.1 Message-ID: <5fc1433825ab7_86c111d4a006517d@gitlab.mail> Ben Gamari pushed to branch wip/win32-m32 at Glasgow Haskell Compiler / GHC Commits: 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 635f863b by Ben Gamari at 2020-11-27T18:19:09+00:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - 4c747c28 by Ben Gamari at 2020-11-27T18:19:09+00:00 rts: Introduce mmapAnonForLinker Previously most of the uses of mmapForLinker were mapping anonymous memory, resulting in a great deal of unnecessary repetition. Factor this out into a new helper. Also fixes a few places where error checking was missing or suboptimal. - - - - - 60978706 by Ben Gamari at 2020-11-27T18:19:09+00:00 rts/linker: Introduce munmapForLinker Consolidates munmap calls to ensure consistent error handling. - - - - - 35ab0f10 by Ben Gamari at 2020-11-27T18:19:09+00:00 rts/Linker: Introduce Windows implementations for mmapForLinker, et al. - - - - - 0bb88f57 by Ben Gamari at 2020-11-27T18:19:09+00:00 rts/m32: Introduce NEEDS_M32 macro Instead of relying on RTS_LINKER_USE_MMAP - - - - - f6c843a8 by Ben Gamari at 2020-11-27T18:19:09+00:00 rts/linker: Use m32 to allocate symbol extras in PEi386 - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/CmmToLlvm/Base.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - hadrian/doc/flavours.md - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - − hadrian/src/Settings/Flavours/Llvm.hs - − hadrian/src/Settings/Flavours/Profiled.hs - − hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/RtsAPI.h - includes/rts/EventLogWriter.h - libraries/Cabal - libraries/base/Debug/Trace.hs - libraries/directory - libraries/ghc-boot/GHC/Data/ShortText.hs - libraries/hpc - libraries/time - libraries/unix - rts/Capability.c - rts/Capability.h - rts/Linker.c - rts/LinkerInternals.h - rts/RtsSymbols.c - rts/Schedule.c - rts/Trace.c - rts/Trace.h - rts/eventlog/EventLog.c - rts/eventlog/EventLog.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/267c1245823d18567e00663c10c0afd92e5b3977...f6c843a8da43748f0365fbac1b73c80883b64499 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/267c1245823d18567e00663c10c0afd92e5b3977...f6c843a8da43748f0365fbac1b73c80883b64499 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 Fri Nov 27 18:23:01 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 13:23:01 -0500 Subject: [Git][ghc/ghc][wip/no-assert] 21 commits: Bump time submodule to 1.11.1 Message-ID: <5fc144059f728_86c3fc6ab4f115c65250@gitlab.mail> Ben Gamari pushed to branch wip/no-assert at Glasgow Haskell Compiler / GHC Commits: 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 32a4d677 by Ben Gamari at 2020-11-27T13:21:25-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 0946529c by Ben Gamari at 2020-11-27T13:22:47-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - compiler/ghc.cabal.in The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ed9d5a1e195f7ce19ea27dec040d8e9bbb18e661...0946529c941194902e7944d54cc3571301d6bf5f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ed9d5a1e195f7ce19ea27dec040d8e9bbb18e661...0946529c941194902e7944d54cc3571301d6bf5f 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 Fri Nov 27 18:31:15 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 13:31:15 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-8.10] 73 commits: rts/SpinLock: Move to proper atomics Message-ID: <5fc145f337b6b_86c11450e28653729@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: f8da754c by Ben Gamari at 2020-11-27T13:28:30-05:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - 2f6d3907 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - cca9c1cb by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/ClosureMaros: Use relaxed atomics - - - - - 7dc087c5 by Ben Gamari at 2020-11-27T13:28:34-05:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - 11791ecf by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - f9936c89 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2526bae7 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Annotate benign race in waitForCapability - - - - - fc42a34c by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Clarify locking behavior of releaseCapability_ - - - - - f569c301 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Add assertions for task ownership of capabilities - - - - - b3262547 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 9b546265 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Mitigate races in capability interruption logic - - - - - 8dbaa27c by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - bd5ec309 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 41e854b7 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Schedule: Use relaxed operations for sched_state - - - - - f54d381b by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 5a29a9ac by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Eliminate data races on pending_sync - - - - - 3b56d934 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - 5eec2560 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Avoid data races in message handling - - - - - 014482a8 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - 5ad949c8 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/ThreadPaused: Avoid data races - - - - - 3a61a624 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Schedule: Eliminate data races in run queue management - - - - - 6b0c4a4d by Ben Gamari at 2020-11-27T13:28:34-05:00 rts: Eliminate shutdown data race on task counters - - - - - d035205e by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 47b3aa0f by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Messages: Annotate benign race - - - - - 8dff50c6 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/RaiseAsync: Synchronize what_next read - - - - - c28b7cc2 by Ben Gamari at 2020-11-27T13:28:34-05:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - 041c2e85 by Ben Gamari at 2020-11-27T13:28:34-05:00 Disable flawed assertion - - - - - c12ef8b2 by Ben Gamari at 2020-11-27T13:28:35-05:00 Document schedulePushWork race - - - - - 82ddaf61 by Ben Gamari at 2020-11-27T13:28:35-05:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - 46866cfd by Ben Gamari at 2020-11-27T13:28:35-05:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 3b827993 by Ben Gamari at 2020-11-27T13:28:35-05:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 43913d14 by GHC GitLab CI at 2020-11-27T13:28:35-05:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - a3cff132 by GHC GitLab CI at 2020-11-27T13:28:35-05:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - 49b08d4b by Ben Gamari at 2020-11-27T13:28:35-05:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - e0019742 by Ben Gamari at 2020-11-27T13:28:35-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - 09882529 by Ben Gamari at 2020-11-27T13:28:35-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 7f9413ae by Ben Gamari at 2020-11-27T13:28:35-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - e7560554 by Ben Gamari at 2020-11-27T13:28:35-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 55500716 by Ben Gamari at 2020-11-27T13:28:35-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - 4197478e by Ben Gamari at 2020-11-27T13:28:35-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - e6029389 by Ben Gamari at 2020-11-27T13:28:35-05:00 rts/BlockAlloc: Use relaxed operations - - - - - 0772dac6 by Ben Gamari at 2020-11-27T13:28:35-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - d623201e by Ben Gamari at 2020-11-27T13:28:35-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 62dc2674 by Ben Gamari at 2020-11-27T13:28:35-05:00 rts/Storage: Use atomics - - - - - 948cfaf2 by Ben Gamari at 2020-11-27T13:28:35-05:00 rts/Updates: Use proper atomic operations - - - - - c84d1546 by Ben Gamari at 2020-11-27T13:28:35-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - 18f1cd4f by Ben Gamari at 2020-11-27T13:28:35-05:00 rts/GC: Use atomics - - - - - 8d181e61 by Ben Gamari at 2020-11-27T13:28:35-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - f6e6ae9a by Ben Gamari at 2020-11-27T13:28:35-05:00 rts/Storage: Accept races on heap size counters - - - - - 7672301d by Ben Gamari at 2020-11-27T13:28:35-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - 81731699 by GHC GitLab CI at 2020-11-27T13:28:35-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 2222390f by Ben Gamari at 2020-11-27T13:30:25-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - 840cd2d3 by Ben Gamari at 2020-11-27T13:31:02-05:00 rts: Use relaxed ordering on spinlock counters - - - - - aade2cdd by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 574181f4 by Ben Gamari at 2020-11-27T13:31:04-05:00 Strengthen ordering in releaseGCThreads - - - - - c5fcb0f2 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - 4e57a865 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 5e9a359e by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - f7607554 by GHC GitLab CI at 2020-11-27T13:31:04-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - a6fdae36 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 798a81d5 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - 8a4c40c4 by Ben Gamari at 2020-11-27T13:31:04-05:00 Mitigate data races in event manager startup/shutdown - - - - - 1f636c10 by Ben Gamari at 2020-11-27T13:31:04-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - 8f0d6db9 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Accept benign races in Proftimer - - - - - 52704812 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - e09376e0 by Ben Gamari at 2020-11-27T13:31:04-05:00 Fix #17289 - - - - - d7761be1 by Ben Gamari at 2020-11-27T13:31:04-05:00 suppress #17289 (ticker) race - - - - - dab8b674 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - 11fa84bf by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - dfb50537 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - b9541309 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5a46207b by Ben Gamari at 2020-11-27T13:31:04-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - a3152aa0 by Ben Gamari at 2020-11-27T13:31:04-05:00 rts/Stats: Reintroduce mut_user_time Fix the previous backport; this function was dead code in master but is still needed due to ProfHeap.c in ghc-8.10. - - - - - 30 changed files: - .gitlab-ci.yml - hadrian/src/Flavour.hs - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - includes/rts/TSANUtils.h - includes/rts/storage/ClosureMacros.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Schedule.h - rts/Sparks.c - + rts/SpinLock.c - rts/StablePtr.c - rts/Stats.c - rts/Stats.h - rts/Task.c - rts/ThreadPaused.c - rts/Threads.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51d95b564fa7319719c1c810df4faeb983f281bb...a3152aa057644dac7b8df4c30c3034d3ab180748 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51d95b564fa7319719c1c810df4faeb983f281bb...a3152aa057644dac7b8df4c30c3034d3ab180748 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 Fri Nov 27 18:39:02 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 13:39:02 -0500 Subject: [Git][ghc/ghc][wip/ci-only-tests] gitlab-ci: Introduce ONLY_TESTS variable Message-ID: <5fc147c6ddb6a_86cf574568654333@gitlab.mail> Ben Gamari pushed to branch wip/ci-only-tests at Glasgow Haskell Compiler / GHC Commits: 005227ec by Ben Gamari at 2020-11-27T13:38:54-05:00 gitlab-ci: Introduce ONLY_TESTS variable When using ci.sh manually it is often useful to run just a subset of tests. - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -45,6 +45,7 @@ Environment variables affecting both build systems: VERBOSE Set to non-empty for verbose build output MSYSTEM (Windows-only) Which platform to build form (MINGW64 or MINGW32). + ONLY_TESTS Select a subset of tests to run Environment variables determining build configuration of Make system: @@ -430,10 +431,15 @@ function determine_metric_baseline() { } function test_make() { + local args=( + "THREADS=$cores" + "JUNIT_FILE=../../junit.xml" + ) + if [[ -n "$ONLY_TESTS" ]]; then + args+=( "TEST=$ONLY_TESTS" ) + fi run "$MAKE" test_bindist TEST_PREP=YES - run "$MAKE" V=0 test \ - THREADS="$cores" \ - JUNIT_FILE=../../junit.xml + run "$MAKE" V=0 test "${args[@]}" } function build_hadrian() { @@ -450,6 +456,11 @@ function build_hadrian() { } function test_hadrian() { + local tests="" + if [[ -n "$ONLY_TESTS" ]]; then + tests="--only=$ONLY_TESTS" + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -458,7 +469,8 @@ function test_hadrian() { run_hadrian \ test \ --summary-junit=./junit.xml \ - --test-compiler="$TOP"/_build/install/bin/ghc + --test-compiler="$TOP"/_build/install/bin/ghc \ + "$tests" } function cabal_test() { @@ -498,13 +510,15 @@ function clean() { function run_hadrian() { if [ -z "$BIGNUM_BACKEND" ]; then BIGNUM_BACKEND="gmp"; fi if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi - run hadrian/build-cabal \ - --flavour="$BUILD_FLAVOUR" \ - -j"$cores" \ - --broken-test="$BROKEN_TESTS" \ - --bignum=$BIGNUM_BACKEND \ - $HADRIAN_ARGS \ - $@ + local args=( + "--flavour=$BUILD_FLAVOUR" + "-j$cores" + "--broken-test=$BROKEN_TESTS" + "--bignum=$BIGNUM_BACKEND" + "${HADRIAN_ARGS[@]}" + "$@" + ) + run hadrian/build-cabal "${args[@]}" } # A convenience function to allow debugging in the CI environment. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/005227ecc4be13957d9ff5ea38a802954cdb4d28 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/005227ecc4be13957d9ff5ea38a802954cdb4d28 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 Fri Nov 27 19:11:17 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 14:11:17 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T14702-fragile Message-ID: <5fc14f552c36c_86c3fc6a6aa1b2465976e@gitlab.mail> Ben Gamari pushed new branch wip/T14702-fragile at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T14702-fragile 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 Fri Nov 27 21:13:46 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Fri, 27 Nov 2020 16:13:46 -0500 Subject: [Git][ghc/ghc][wip/interal-primop-naming-consistency] 11 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc16c0a1ee51_86c3fc6ab4f115c679331@gitlab.mail> John Ericson pushed to branch wip/interal-primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - b654f828 by John Ericson at 2020-11-27T21:06:24+00:00 Make primop handler indentation more consistent - - - - - 32e0ca22 by John Ericson at 2020-11-27T21:06:24+00:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d9b490fd27e645fd839eeb2316d36bf076d4479...32e0ca22340238a34b730c376ba73d1b8691e38e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3d9b490fd27e645fd839eeb2316d36bf076d4479...32e0ca22340238a34b730c376ba73d1b8691e38e 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 Fri Nov 27 21:13:47 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Fri, 27 Nov 2020 16:13:47 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] 12 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc16c0b4d731_86ce89fc5c6795b5@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - b654f828 by John Ericson at 2020-11-27T21:06:24+00:00 Make primop handler indentation more consistent - - - - - 32e0ca22 by John Ericson at 2020-11-27T21:06:24+00:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 401dfcb8 by John Ericson at 2020-11-27T21:06:24+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f0a3896b9a845bf00283eb8c961bdb0c96c80f86...401dfcb8e1d592921fdbcb66b6f568a36df3fe70 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f0a3896b9a845bf00283eb8c961bdb0c96c80f86...401dfcb8e1d592921fdbcb66b6f568a36df3fe70 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 Fri Nov 27 21:15:13 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Fri, 27 Nov 2020 16:15:13 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fc16c6170673_86c113a5b2c680599@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 4204a403 by Shayne Fletcher at 2020-11-27T16:14:48-05:00 Record dot syntax - - - - - 29 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T - utils/haddock Changes: ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -3728,6 +3728,7 @@ xFlagsDeps = [ flagSpec "Rank2Types" LangExt.RankNTypes, flagSpec "RankNTypes" LangExt.RankNTypes, flagSpec "RebindableSyntax" LangExt.RebindableSyntax, + flagSpec "RecordDotSyntax" LangExt.RecordDotSyntax, depFlagSpec' "RecordPuns" LangExt.RecordPuns (deprecatedForExtension "NamedFieldPuns"), flagSpec "RecordWildCards" LangExt.RecordWildCards, ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -12,6 +12,9 @@ {-# LANGUAGE TypeFamilyDependencies #-} {-# LANGUAGE UndecidableInstances #-} -- Wrinkle in Note [Trees That Grow] -- in module GHC.Hs.Extension +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DeriveFoldable #-} +{-# LANGUAGE DeriveTraversable #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -240,6 +243,26 @@ is Less Cool because typecheck do-notation with (>>=) :: m1 a -> (a -> m2 b) -> m2 b.) -} +-- New for RecordDotSyntax. + +data ProjUpdate' p arg = + ProjUpdate { + pu_flds :: [Located FastString] + , pu_arg :: arg -- Field's new value e.g. 42 + } + deriving (Data, Functor, Foldable, Traversable) + +type ProjUpdate p arg = ProjUpdate' p arg +type LHsProjUpdate p arg = Located (ProjUpdate p arg) +type RecUpdProj p = ProjUpdate' p (LHsExpr p) +type LHsRecUpdProj p = Located (RecUpdProj p) + +instance (Outputable arg) + => Outputable (ProjUpdate' p arg) where + -- TODO: improve in case of pun + ppr ProjUpdate { pu_flds = flds, pu_arg = arg } = + hcat (punctuate dot (map (ppr . unLoc) flds)) <+> equals <+> ppr arg + -- | A Haskell expression. data HsExpr p = HsVar (XVar p) @@ -459,6 +482,51 @@ data HsExpr p -- For a type family, the arg types are of the *instance* tycon, -- not the family tycon + + -- | Record field selection e.g @z.x at . + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDot' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | GetField { + gf_ext :: XGetField p + , gf_expr :: LHsExpr p + , gf_field :: Located FastString + , gf_getField :: LHsExpr p -- Desugared equivalent 'getField' term. + } + + -- Record dot update e.g. @a{foo.bar.baz=1, quux}@. + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'{'@, + -- 'GHC.Parser.Annotation.AnnComma, 'GHC.Parser.Annotation.AnnDot', + -- 'GHC.Parser.Annotation.AnnClose' @'}'@ + -- + -- This case only arises when the RecordDotSyntax langauge + -- extension is enabled. + + | RecordDotUpd { + rdupd_ext :: XRecordDotUpd p + , rdupd_expr :: LHsExpr p + , rdupd_upds :: [LHsRecUpdProj p] + , rdupd_setField :: LHsExpr p -- Desugared equivalent 'setField' term. + } + + -- | Record field selector. e.g. @(.x)@ or @(.x.y)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpenP' + -- 'GHC.Parser.Annotation.AnnDot', 'GHC.Parser.Annotation.AnnCloseP' + -- + -- This case only arises when the RecordDotSyntax langauge + -- extensions is enabled. + + | Projection { + proj_ext :: XProjection p + , proj_flds :: [Located FastString] + , proj_proj :: LHsExpr p -- Desugared equivalent 'getField' term. + } + -- | Expression with an explicit type signature. @e :: type@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' @@ -654,6 +722,18 @@ type instance XRecordUpd GhcPs = NoExtField type instance XRecordUpd GhcRn = NoExtField type instance XRecordUpd GhcTc = RecordUpdTc +type instance XGetField GhcPs = NoExtField +type instance XGetField GhcRn = NoExtField +type instance XGetField GhcTc = NoExtField + +type instance XProjection GhcPs = NoExtField +type instance XProjection GhcRn = NoExtField +type instance XProjection GhcTc = NoExtField + +type instance XRecordDotUpd GhcPs = NoExtField +type instance XRecordDotUpd GhcRn = NoExtField +type instance XRecordDotUpd GhcTc = NoExtField + type instance XExprWithTySig (GhcPass _) = NoExtField type instance XArithSeq GhcPs = NoExtField @@ -1188,6 +1268,14 @@ ppr_expr (RecordCon { rcon_con_name = con_id, rcon_flds = rbinds }) ppr_expr (RecordUpd { rupd_expr = L _ aexp, rupd_flds = rbinds }) = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) +ppr_expr (GetField { gf_expr = L _ fexp, gf_field = field }) + = ppr fexp <> dot <> ppr field + +ppr_expr (Projection { proj_flds = flds }) = parens (hcat (punctuate dot (map ppr flds))) + +ppr_expr (RecordDotUpd { rdupd_expr = L _ aexp, rdupd_upds = rbinds }) + = hang (ppr aexp) 2 (braces (fsep (punctuate comma (map ppr rbinds)))) + ppr_expr (ExprWithTySig _ expr sig) = hang (nest 2 (ppr_lexpr expr) <+> dcolon) 4 (ppr sig) @@ -1346,6 +1434,11 @@ hsExprNeedsParens p = go go (HsBinTick _ _ _ (L _ e)) = go e go (RecordCon{}) = False go (HsRecFld{}) = False + + go (Projection{}) = True + go (GetField{}) = False -- Remember to have a closer look at this. + go (RecordDotUpd{}) = False + go (XExpr x) | GhcTc <- ghcPass @p = case x of ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -557,6 +557,9 @@ type family XDo x type family XExplicitList x type family XRecordCon x type family XRecordUpd x +type family XGetField x +type family XProjection x +type family XRecordDotUpd x type family XExprWithTySig x type family XArithSeq x type family XBracket x ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -277,6 +277,12 @@ dsExpr (HsConLikeOut _ con) = dsConLike con dsExpr (HsIPVar {}) = panic "dsExpr: HsIPVar" dsExpr (HsOverLabel{}) = panic "dsExpr: HsOverLabel" +-- I feel these should have been eliminated by their equivalent +-- getField expressions by now. +dsExpr (GetField{}) = panic "dsExpr: GetField" +dsExpr (Projection{}) = panic "dsExpr: Projection" +dsExpr (RecordDotUpd{}) = panic "dsExpr: RecordDotUpd" + dsExpr (HsLit _ lit) = do { warnAboutOverflowedLit lit ; dsLit (convertLit lit) } ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1154,6 +1154,9 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where HsSpliceE _ x -> [ toHie $ L mspan x ] + GetField _ _ _ g -> [ toHie $ L mspan (unLoc g) ] + Projection _ _ p -> [ toHie $ L mspan (unLoc p) ] + RecordDotUpd _ _ _ u -> [ toHie $ L mspan (unLoc u) ] XExpr x | GhcTc <- ghcPass @p , WrapExpr (HsWrap w a) <- x ===================================== compiler/GHC/Parser.y ===================================== @@ -39,6 +39,9 @@ module GHC.Parser ) where +import Debug.Trace +import Data.Proxy + -- base import Control.Monad ( unless, liftM, when, (<=<) ) import GHC.Exts @@ -64,7 +67,7 @@ import GHC.Utils.Outputable import GHC.Utils.Misc ( looksLikePackageName, fstOf3, sndOf3, thdOf3 ) import GHC.Types.Name.Reader -import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, occNameFS ) +import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, occNameFS, mkVarOcc, occNameString) import GHC.Types.SrcLoc import GHC.Types.Basic import GHC.Types.Fixity @@ -641,6 +644,8 @@ are the most common patterns, rewritten as regular expressions for clarity: '-<<' { L _ (ITLarrowtail _) } -- for arrow notation '>>-' { L _ (ITRarrowtail _) } -- for arrow notation '.' { L _ ITdot } + PREFIX_PROJ { L _ (ITproj True) } -- RecordDotSyntax + TIGHT_INFIX_PROJ { L _ (ITproj False) } -- RecordDotSyntax PREFIX_AT { L _ ITtypeApp } PREFIX_PERCENT { L _ ITpercent } -- for linear types @@ -2711,6 +2716,22 @@ fexp :: { ECP } fmap ecpFromExp $ ams (sLL $1 $> $ HsStatic noExtField $2) [mj AnnStatic $1] } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | fexp TIGHT_INFIX_PROJ field + {% runPV (unECP $1) >>= \ $1 -> + -- Suppose lhs is an application term e.g. 'f a' + -- and rhs is '.b'. Usually we want the parse 'f + -- (a.b)' rather than '(f a).b.'. However, if lhs + -- is a projection 'r.a' (say) then we want the + -- parse '(r.a).b'. + fmap ecpFromExp $ ams (case $1 of + L _ (HsApp _ f arg) | not $ isGetField f -> + let l = comb2 arg $3 in + L (getLoc f `combineSrcSpans` l) + (HsApp noExtField f (mkGetField l arg $3)) + _ -> mkGetField (comb2 $1 $>) $1 $3) [mj AnnDot $2] } + | aexp { $1 } aexp :: { ECP } @@ -2800,10 +2821,12 @@ aexp :: { ECP } aexp1 :: { ECP } : aexp1 '{' fbinds '}' { ECP $ - unECP $1 >>= \ $1 -> - $3 >>= \ $3 -> - amms (mkHsRecordPV (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) - (moc $2:mcc $4:(fst $3)) } + getBit RecordDotSyntaxBit >>= \ dot -> + unECP $1 >>= \ $1 -> + $3 >>= \ $3 -> + amms (mkHsRecordPV dot (comb2 $1 $>) (comb2 $2 $4) $1 (snd $3)) + (moc $2:mcc $4:(fst $3)) + } | aexp2 { $1 } aexp2 :: { ECP } @@ -2832,6 +2855,14 @@ aexp2 :: { ECP } amms (mkSumOrTuplePV (comb2 $1 $>) Boxed (snd $2)) ((mop $1:fst $2) ++ [mcp $3]) } + -- This case is only possible when 'RecordDotSyntax' is enabled. + | '(' projection ')' { ECP $ + let (loc, (anns, fIELDS)) = $2 + span = combineSrcSpans (combineSrcSpans (getLoc $1) loc) (getLoc $3) + expr = mkProjection span (reverse fIELDS) + in amms (ecpFromExp' expr) ([mop $1] ++ reverse anns ++ [mcp $3]) + } + | '(#' texp '#)' { ECP $ unECP $2 >>= \ $2 -> amms (mkSumOrTuplePV (comb2 $1 $>) Unboxed (Tuple [L (gl $2) (Just $2)])) @@ -2881,6 +2912,14 @@ aexp2 :: { ECP } Nothing (reverse $3)) [mu AnnOpenB $1,mu AnnCloseB $4] } +projection :: { (SrcSpan, ([AddAnn], [Located FastString])) } +projection + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parsing.Lexer + : projection TIGHT_INFIX_PROJ field + { let (loc, (anns, fs)) = $1 in + (combineSrcSpans (combineSrcSpans loc (gl $2)) (gl $3), (mj AnnDot $2 : anns, $3 : fs)) } + | PREFIX_PROJ field { (comb2 $1 $2, ([mj AnnDot $1], [$2])) } + splice_exp :: { LHsExpr GhcPs } : splice_untyped { mapLoc (HsSpliceE noExtField) $1 } | splice_typed { mapLoc (HsSpliceE noExtField) $1 } @@ -3297,33 +3336,63 @@ qual :: { forall b. DisambECP b => PV (LStmt GhcPs (Located b)) } ----------------------------------------------------------------------------- -- Record Field Update/Construction -fbinds :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbinds1 { $1 } | {- empty -} { return ([],([], Nothing)) } -fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([LHsRecField GhcPs (Located b)], Maybe SrcSpan)) } +fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) } : fbind ',' fbinds1 { $1 >>= \ $1 -> $3 >>= \ $3 -> - addAnnotation (gl $1) AnnComma (gl $2) >> + let gl' = \case { Fbind (L l _) -> l; Pbind (L l _) -> l } in + addAnnotation (gl' $1) AnnComma (gl $2) >> return (case $3 of (ma,(flds, dd)) -> (ma,($1 : flds, dd))) } | fbind { $1 >>= \ $1 -> return ([],([$1], Nothing)) } | '..' { return ([mj AnnDotdot $1],([], Just (getLoc $1))) } -fbind :: { forall b. DisambECP b => PV (LHsRecField GhcPs (Located b)) } +fbind :: { forall b. DisambECP b => PV (Fbind b) } : qvar '=' texp { unECP $3 >>= \ $3 -> - ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) - [mj AnnEqual $2] } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) + -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2] + } -- RHS is a 'texp', allowing view patterns (#6038) -- and, incidentally, sections. Eg -- f (R { x = show -> s }) = ... | qvar { placeHolderPunRhs >>= \rhs -> - return $ sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True } + fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True) + } -- In the punning case, use a place-holder -- The renamer fills in the final value + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp + { do + $5 <- unECP $5 + fmap Pbind $ mkHsProjUpdatePV (comb2 $1 $5) ($1 : reverse $3) $5 + } + + -- See Note [Whitespace-sensitive operator parsing] in GHC.Parser.Lexer + | field TIGHT_INFIX_PROJ fieldToUpdate + { do + let top = $1 + fields = top : reverse $3 + final = last fields + l = comb2 top final + puns <- getBit RecordPunsBit + when (not puns) $ + addError $ Error ErrNamedFieldPunsNotEnabled [] l + var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final)) + fmap Pbind $ mkHsProjUpdatePV l fields var + } + +fieldToUpdate :: { [Located FastString] } +fieldToUpdate + -- See Note [Whitespace-sensitive operator parsing] in Lexer.x + : fieldToUpdate TIGHT_INFIX_PROJ field { $3 : $1 } + | field { [$1] } + ----------------------------------------------------------------------------- -- Implicit Parameter Bindings @@ -3617,6 +3686,10 @@ qvar :: { Located RdrName } -- whether it's a qvar or a var can be postponed until -- *after* we see the close paren. +field :: { Located FastString } + : VARID { sL1 $1 $! getVARID $1 } + | QVARID { sL1 $1 $! snd $ getQVARID $1 } + qvarid :: { Located RdrName } : varid { $1 } | QVARID { sL1 $1 $! mkQual varName (getQVARID $1) } ===================================== compiler/GHC/Parser/Errors.hs ===================================== @@ -148,6 +148,9 @@ data ErrorDesc | ErrDotsInRecordUpdate -- ^ Dots used in record update + | ErrRecordDotSyntaxInvalid + -- ^ Invalid use of record-dot-syntax + | ErrPrecedenceOutOfRange !Int -- ^ Precedence out of range @@ -335,6 +338,9 @@ data ErrorDesc | ErrExpectedHyphen -- ^ Expected a hyphen + | ErrNamedFieldPunsNotEnabled + -- ^ Named field puns should be enabled + | ErrSpaceInSCC -- ^ Found a space in a SCC ===================================== compiler/GHC/Parser/Errors/Ppr.hs ===================================== @@ -233,6 +233,9 @@ pp_err = \case ErrDotsInRecordUpdate -> text "You cannot use `..' in a record update" + ErrRecordDotSyntaxInvalid + -> text "Use of RecordDotSyntax `.' not valid." + ErrPrecedenceOutOfRange i -> text "Precedence out of range: " <> int i @@ -537,6 +540,9 @@ pp_err = \case ErrExpectedHyphen -> text "Expected a hyphen" + ErrNamedFieldPunsNotEnabled + -> text "For this to work enable NamedFieldPuns" + ErrSpaceInSCC -> text "Spaces are not allowed in SCCs" @@ -610,4 +616,3 @@ pp_hint = \case perhaps_as_pat :: SDoc perhaps_as_pat = text "Perhaps you meant an as-pattern, which must not be surrounded by whitespace" - ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -616,6 +616,19 @@ $tab { warnTab } -- | | ordinary operator or type operator, -- | | e.g. xs ~ 3, (~ x), Int ~ Bool -- ----------+---------------+------------------------------------------ +-- . | prefix | ITproj True +-- | | field projection, +-- | | e.g. .x +-- | tight infix | ITproj False +-- | | field projection, +-- | | e.g. r.x +-- | suffix | ITdot +-- | | function composition, +-- | | e.g. f. g +-- | loose infix | ITdot +-- | | function composition, +-- | | e.g. f . g +-- ----------+---------------+------------------------------------------ -- $ $$ | prefix | ITdollar, ITdollardollar -- | | untyped or typed Template Haskell splice, -- | | e.g. $(f x), $$(f x), $$"str" @@ -777,6 +790,7 @@ data Token | ITpercent -- Prefix (%) only, e.g. a %1 -> b | ITstar IsUnicodeSyntax | ITdot + | ITproj Bool -- RecordDotSyntax | ITbiglam -- GHC-extension symbols @@ -1594,6 +1608,9 @@ varsym_prefix = sym $ \span exts s -> | s == fsLit "-" -> return ITprefixminus -- Only when LexicalNegation is on, otherwise we get ITminus -- and don't hit this code path. See Note [Minus tokens] + | s == fsLit ".", RecordDotSyntaxBit `xtest` exts -> + return (ITproj True) -- e.g. '(.x)' + | s == fsLit "." -> return ITdot | s == fsLit "!" -> return ITbang | s == fsLit "~" -> return ITtilde | otherwise -> @@ -1614,8 +1631,10 @@ varsym_suffix = sym $ \span _ s -> -- See Note [Whitespace-sensitive operator parsing] varsym_tight_infix :: Action -varsym_tight_infix = sym $ \span _ s -> +varsym_tight_infix = sym $ \span exts s -> if | s == fsLit "@" -> return ITat + | s == fsLit ".", RecordDotSyntaxBit `xtest` exts -> return (ITproj False) + | s == fsLit "." -> return ITdot | otherwise -> do { addWarning Opt_WarnOperatorWhitespace $ WarnOperatorWhitespace (mkSrcSpanPs span) s @@ -1624,7 +1643,11 @@ varsym_tight_infix = sym $ \span _ s -> -- See Note [Whitespace-sensitive operator parsing] varsym_loose_infix :: Action -varsym_loose_infix = sym (\_ _ s -> return $ ITvarsym s) +varsym_loose_infix = sym $ \_ _ s -> + if | s == fsLit "." + -> return ITdot + | otherwise + -> return $ ITvarsym s consym :: Action consym = sym (\_span _exts s -> return $ ITconsym s) @@ -1632,8 +1655,13 @@ consym = sym (\_span _exts s -> return $ ITconsym s) sym :: (PsSpan -> ExtsBitmap -> FastString -> P Token) -> Action sym con span buf len = case lookupUFM reservedSymsFM fs of - Just (keyword, NormalSyntax, 0) -> - return $ L span keyword + Just (keyword, NormalSyntax, 0) -> do + exts <- getExts + if fs == fsLit "." && + exts .&. (xbit RecordDotSyntaxBit) /= 0 && + xtest RecordDotSyntaxBit exts + then L span <$!> con span exts fs -- Process by varsym_*. + else return $ L span keyword Just (keyword, NormalSyntax, i) -> do exts <- getExts if exts .&. i /= 0 @@ -2639,6 +2667,8 @@ data ExtBits | ImportQualifiedPostBit | LinearTypesBit | NoLexicalNegationBit -- See Note [Why not LexicalNegationBit] + | RecordPunsBit + | RecordDotSyntaxBit -- Flags that are updated once parsing starts | InRulePragBit @@ -2715,6 +2745,8 @@ mkParserOpts warningFlags extensionFlags .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost .|. LinearTypesBit `xoptBit` LangExt.LinearTypes .|. NoLexicalNegationBit `xoptNotBit` LangExt.LexicalNegation -- See Note [Why not LexicalNegationBit] + .|. RecordPunsBit `xoptBit` LangExt.RecordPuns + .|. RecordDotSyntaxBit `xoptBit` LangExt.RecordDotSyntax optBits = HaddockBit `setBitIf` isHaddock .|. RawTokenStreamBit `setBitIf` rawTokStream ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -5,6 +5,7 @@ {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} @@ -15,6 +16,7 @@ -- Functions over HsSyn specialised to RdrName. module GHC.Parser.PostProcess ( + mkGetField, mkProjection, isGetField, Fbind(..), -- RecordDot mkHsOpApp, mkHsIntegral, mkHsFractional, mkHsIsString, mkHsDo, mkSpliceDecl, @@ -27,7 +29,7 @@ module GHC.Parser.PostProcess ( mkFamDecl, mkInlinePragma, mkPatSynMatchGroup, - mkRecConstrOrUpdate, -- HsExp -> [HsFieldUpdate] -> P HsExp + mkRecConstrOrUpdate, mkTyClD, mkInstD, mkRdrRecordCon, mkRdrRecordUpd, setRdrNameSpace, @@ -135,6 +137,7 @@ import GHC.Data.Maybe import GHC.Data.Bag import GHC.Utils.Misc import GHC.Parser.Annotation +import Data.Either import Data.List import Data.Foldable import GHC.Driver.Flags ( WarningFlag(..) ) @@ -148,6 +151,22 @@ import Data.Kind ( Type ) #include "HsVersions.h" +data Fbind b = Fbind (LHsRecField GhcPs (Located b)) + | Pbind (LHsProjUpdate GhcPs (Located b)) + +fbindsToEithers :: [Fbind b] + -> [Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + ] +fbindsToEithers = fmap fbindToEither + where + fbindToEither :: Fbind b + -> Either + (LHsRecField GhcPs (Located b)) + (LHsProjUpdate GhcPs (Located b)) + fbindToEither (Fbind x) = Left x + fbindToEither (Pbind x) = Right x {- ********************************************************************** @@ -1267,6 +1286,8 @@ class b ~ (Body b) GhcPs => DisambECP b where ecpFromCmd' :: LHsCmd GhcPs -> PV (Located b) -- | Return an expression without ambiguity, or fail in a non-expression context. ecpFromExp' :: LHsExpr GhcPs -> PV (Located b) + -- | This can only be satified by expressions. + mkHsProjUpdatePV :: SrcSpan -> [Located FastString] -> Located b -> PV (LHsProjUpdate GhcPs (Located b)) -- | Disambiguate "\... -> ..." (lambda) mkHsLamPV :: SrcSpan -> MatchGroup GhcPs (Located b) -> PV (Located b) -- | Disambiguate "let ... in ..." @@ -1323,10 +1344,11 @@ class b ~ (Body b) GhcPs => DisambECP b where mkHsSplicePV :: Located (HsSplice GhcPs) -> PV (Located b) -- | Disambiguate "f { a = b, ... }" syntax (record construction and record updates) mkHsRecordPV :: + Bool -> -- Is RecordDotSyntax in effect? SrcSpan -> SrcSpan -> Located b -> - ([LHsRecField GhcPs (Located b)], Maybe SrcSpan) -> + ([Fbind b], Maybe SrcSpan) -> PV (Located b) -- | Disambiguate "-a" (negation) mkHsNegAppPV :: SrcSpan -> Located b -> PV (Located b) @@ -1345,7 +1367,6 @@ class b ~ (Body b) GhcPs => DisambECP b where -- | Validate infixexp LHS to reject unwanted {-# SCC ... #-} pragmas rejectPragmaPV :: Located b -> PV () - {- Note [UndecidableSuperClasses for associated types] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ (This Note is about the code in GHC, not about the user code that we are parsing) @@ -1394,6 +1415,7 @@ instance DisambECP (HsCmd GhcPs) where type Body (HsCmd GhcPs) = HsCmd ecpFromCmd' = return ecpFromExp' (L l e) = cmdFail l (ppr e) + mkHsProjUpdatePV l _ _ = addFatalError $ Error ErrRecordDotSyntaxInvalid [] l mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg) mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e) type InfixOp (HsCmd GhcPs) = HsExpr GhcPs @@ -1424,8 +1446,11 @@ instance DisambECP (HsCmd GhcPs) where mkHsExplicitListPV l xs = cmdFail l $ brackets (fsep (punctuate comma (map ppr xs))) mkHsSplicePV (L l sp) = cmdFail l (ppr sp) - mkHsRecordPV l _ a (fbinds, ddLoc) = cmdFail l $ - ppr a <+> ppr (mk_rec_fields fbinds ddLoc) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError $ Error ErrRecordDotSyntaxInvalid [] l + else cmdFail l $ ppr a <+> ppr (mk_rec_fields fs ddLoc) mkHsNegAppPV l a = cmdFail l (text "-" <> ppr a) mkHsSectionR_PV l op c = cmdFail l $ let pp_op = fromMaybe (panic "cannot print infix operator") @@ -1451,6 +1476,7 @@ instance DisambECP (HsExpr GhcPs) where addError $ Error (ErrArrowCmdInExpr c) [] l return (L l hsHoleExpr) ecpFromExp' = return + mkHsProjUpdatePV l fields arg = return $ mkProjUpdate l fields arg mkHsLamPV l mg = return $ L l (HsLam noExtField mg) mkHsLetPV l bs c = return $ L l (HsLet noExtField bs c) type InfixOp (HsExpr GhcPs) = HsExpr GhcPs @@ -1480,8 +1506,8 @@ instance DisambECP (HsExpr GhcPs) where mkHsTySigPV l a sig = return $ L l (ExprWithTySig noExtField a (hsTypeToHsSigWcType sig)) mkHsExplicitListPV l xs = return $ L l (ExplicitList noExtField Nothing xs) mkHsSplicePV sp = return $ mapLoc (HsSpliceE noExtField) sp - mkHsRecordPV l lrec a (fbinds, ddLoc) = do - r <- mkRecConstrOrUpdate a lrec (fbinds, ddLoc) + mkHsRecordPV dot l lrec a (fbinds, ddLoc) = do + r <- mkRecConstrOrUpdate dot a lrec (fbinds, ddLoc) checkRecordSyntax (L l r) mkHsNegAppPV l a = return $ L l (NegApp noExtField a noSyntaxExpr) mkHsSectionR_PV l op e = return $ L l (SectionR noExtField op e) @@ -1509,6 +1535,7 @@ instance DisambECP (PatBuilder GhcPs) where ecpFromExp' (L l e) = addFatalError $ Error (ErrArrowExprInPat e) [] l mkHsLamPV l _ = addFatalError $ Error ErrLambdaInPat [] l mkHsLetPV l _ _ = addFatalError $ Error ErrLetInPat [] l + mkHsProjUpdatePV l _ _ = addFatalError $ Error ErrRecordDotSyntaxInvalid [] l type InfixOp (PatBuilder GhcPs) = RdrName superInfixOp m = m mkHsOpAppPV l p1 op p2 = return $ L l $ PatBuilderOpApp p1 op p2 @@ -1534,9 +1561,13 @@ instance DisambECP (PatBuilder GhcPs) where ps <- traverse checkLPat xs return (L l (PatBuilderPat (ListPat noExtField ps))) mkHsSplicePV (L l sp) = return $ L l (PatBuilderPat (SplicePat noExtField sp)) - mkHsRecordPV l _ a (fbinds, ddLoc) = do - r <- mkPatRec a (mk_rec_fields fbinds ddLoc) - checkRecordSyntax (L l r) + mkHsRecordPV _ l _ a (fbinds, ddLoc) = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError $ Error ErrRecordDotSyntaxInvalid [] l + else do + r <- mkPatRec a (mk_rec_fields fs ddLoc) + checkRecordSyntax (L l r) mkHsNegAppPV l (L lp p) = do lit <- case p of PatBuilderOverLit pos_lit -> return (L lp pos_lit) @@ -2132,17 +2163,50 @@ checkPrecP (L l (_,i)) (L _ ol) , getRdrName unrestrictedFunTyCon ] mkRecConstrOrUpdate - :: LHsExpr GhcPs + :: Bool + -> LHsExpr GhcPs -> SrcSpan - -> ([LHsRecField GhcPs (LHsExpr GhcPs)], Maybe SrcSpan) + -> ([Fbind (HsExpr GhcPs)], Maybe SrcSpan) -> PV (HsExpr GhcPs) - -mkRecConstrOrUpdate (L l (HsVar _ (L _ c))) _ (fs,dd) +mkRecConstrOrUpdate _ (L l (HsVar _ (L _ c))) _lrec (fbinds,dd) | isRdrDataCon c - = return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) -mkRecConstrOrUpdate exp _ (fs,dd) + = do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then addFatalError $ Error ErrRecordDotSyntaxInvalid [] (getLoc (head ps)) + else return (mkRdrRecordCon (L l c) (mk_rec_fields fs dd)) +mkRecConstrOrUpdate dot exp _ (fs,dd) | Just dd_loc <- dd = addFatalError $ Error ErrDotsInRecordUpdate [] dd_loc - | otherwise = return (mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs)) + | otherwise = mkRdrRecordDotUpd dot exp fs + +mkRdrRecordDotUpd :: Bool -> LHsExpr GhcPs -> [Fbind (HsExpr GhcPs)] -> PV (HsExpr GhcPs) +mkRdrRecordDotUpd dot exp@(L _ _) fbinds = + if not dot + then do + let (fs, ps) = partitionEithers $ fbindsToEithers fbinds + if not (null ps) + then + -- If RecordDotSyntax is not enabled (as indicated by the + -- value of 'dot'), then the lexer can't ever issue an ITproj + -- token and so this case is refuted. + panic "mkRdrRecordUpd': The impossible happened!" + else return $ mkRdrRecordUpd exp (map (fmap mk_rec_upd_field) fs) + else + let updates = toProjUpdates fbinds + setField = noLoc $ foldl' fieldUpdate (unLoc exp) updates + in return RecordDotUpd { + rdupd_ext = noExtField + , rdupd_expr = exp + , rdupd_upds = updates + , rdupd_setField = setField } + where + toProjUpdates :: [Fbind (HsExpr GhcPs)] -> [LHsRecUpdProj GhcPs] + toProjUpdates = map (\case { Pbind p -> p + ; Fbind f -> recUpdFieldToProjUpdate (fmap mk_rec_upd_field f) + }) + + fieldUpdate :: HsExpr GhcPs -> LHsRecUpdProj GhcPs -> HsExpr GhcPs + fieldUpdate acc lpu = unLoc $ (mkProjUpdateSetField lpu) (noLoc acc) mkRdrRecordUpd :: LHsExpr GhcPs -> [LHsRecUpdField GhcPs] -> HsExpr GhcPs mkRdrRecordUpd exp flds @@ -2629,3 +2693,132 @@ mkMultTy u tok t = (HsExplicitMult u t, AddAnn AnnPercent (getLoc tok)) starSym :: Bool -> String starSym True = "★" starSym False = "*" + +----------------------------------------- +-- Bits and pieces for RecordDotSyntax. + +mkParen :: LHsExpr GhcPs -> LHsExpr GhcPs +mkParen = noLoc . HsPar noExtField + +mkVar :: String -> LHsExpr GhcPs +mkVar = noLoc . HsVar noExtField . noLoc . mkRdrUnqual . mkVarOcc + +mkApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkApp x = noLoc . HsApp noExtField x + +mkOpApp :: LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs -> LHsExpr GhcPs +mkOpApp x op = noLoc . OpApp noExtField x op + +mkAppType :: LHsExpr GhcPs -> GenLocated SrcSpan (HsType (NoGhcTc GhcPs)) -> LHsExpr GhcPs +mkAppType expr = noLoc . HsAppType noExtField expr . HsWC noExtField + +mkSelector :: FastString -> LHsType GhcPs +mkSelector = noLoc . HsTyLit noExtField . HsStrTy NoSourceText + +get_field, set_field :: LHsExpr GhcPs +get_field = mkVar "getField" +set_field = mkVar "setField" + +-- Test if the expression is a 'getField @"..."' expression. +isGetField :: LHsExpr GhcPs -> Bool +isGetField (L _ GetField{}) = True +isGetField _ = False + +zPat :: LPat GhcPs +zVar, circ :: LHsExpr GhcPs +zPat = noLoc $ VarPat noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +zVar = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc "z")) +circ = noLoc $ HsVar noExtField (noLoc $ mkRdrUnqual (mkVarOcc ".")) + +-- mkProj' fieldS calculates a projection. +-- e.g. .x = mkProj' x = \z -> z.x = \z -> (getField @field x) +-- .x.y = mkProj' [.x, .y] = (.y) . (.x) = (\z -> z.y) . (\z -> z.x) +mkProj :: [Located FastString] -> LHsExpr GhcPs +mkProj (field : fieldS) = foldl' f (proj field) fieldS + where + f acc field = (mkParen . mkOpApp (proj field) circ) acc + + proj f = + let body = mkGet zVar f + grhs = noLoc $ GRHS noExtField [] body + ghrss = GRHSs noExtField [grhs] (noLoc (EmptyLocalBinds noExtField)) + m = noLoc $ Match {m_ext=noExtField, m_ctxt=LambdaExpr, m_pats=[zPat], m_grhss=ghrss} in + mkParen (noLoc $ HsLam noExtField MG {mg_ext=noExtField, mg_alts=noLoc [m], mg_origin=Generated}) +mkProj [] = panic "mkProj': The impossible happened" + +-- mkGet arg field calcuates a get_field @field arg expression. +-- e.g. z.x = mkGet z x = get_field @x z +mkGet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGet arg field = head $ mkGet' [arg] field +mkGet' :: [LHsExpr GhcPs] -> Located FastString -> [LHsExpr GhcPs] +mkGet' l@(r : _) (L _ field) = get_field `mkAppType` mkSelector field `mkApp` mkParen r : l +mkGet' [] _ = panic "mkGet' : The impossible has happened!" + +mkGetField :: SrcSpan -> LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs +mkGetField loc arg field = + L loc GetField { + gf_ext = noExtField + , gf_expr = arg + , gf_field = field + , gf_getField = mkGet arg field + } + +mkProjection :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs +mkProjection _ [] = panic "mkProjection: The impossible has happened!" +mkProjection loc flds = + L loc Projection { + proj_ext = noExtField + , proj_flds = flds + , proj_proj = mkProj flds + } + +-- e.g. foo.bar.baz.quux = 1 +mkProjUpdate :: SrcSpan -> [Located FastString] -> LHsExpr GhcPs -> LHsProjUpdate GhcPs (LHsExpr GhcPs) +mkProjUpdate _ [] _ = panic "mkProjUpdate: The impossible has happened!" +mkProjUpdate loc flds arg = + L loc ProjUpdate { + pu_flds = flds + , pu_arg = arg + } + +-- mkSet a field b calculates a set_field @field expression. +-- e.g mkSet a field b = set_field @"field" a b (read as "set field 'field' on a to b"). +mkSet :: LHsExpr GhcPs -> Located FastString -> LHsExpr GhcPs -> LHsExpr GhcPs +mkSet a (L _ field) b = set_field `mkAppType` mkSelector field `mkApp` a `mkApp` b + +-- mkProjUpdateSetField calculates functions representing dot notation record updates. +mkProjUpdateSetField :: LHsProjUpdate GhcPs (LHsExpr GhcPs) -> (LHsExpr GhcPs -> LHsExpr GhcPs) +mkProjUpdateSetField (L _ (ProjUpdate { pu_flds = flds, pu_arg = arg } )) + = let { + ; final = last flds -- quux + ; fields = init flds -- [foo, bar, baz] + ; getters = \a -> foldl' mkGet' [a] fields -- Ordered from deep to shallow. + -- [getField@"baz"(getField@"bar"(getField@"foo" a), getField@"bar"(getField@"foo" a), getField@"foo" a, a] + ; zips = \a -> (final, head (getters a)) : zip (reverse fields) (tail (getters a)) -- Ordered from deep to shallow. + -- [("quux", getField@"baz"(getField@"bar"(getField@"foo" a)), ("baz", getField@"bar"(getField@"foo" a)), ("bar", getField@"foo" a), ("foo", a)] + } + in (\a -> foldl' mkSet' arg (zips a)) + -- setField@"foo" (a) (setField@"bar" (getField @"foo" (a))(setField@"baz" (getField @"bar" (getField @"foo" (a)))(setField@"quux" (getField @"baz" (getField @"bar" (getField @"foo" (a))))(quux)))) + where + mkSet' :: LHsExpr GhcPs -> (Located FastString, LHsExpr GhcPs) -> LHsExpr GhcPs + mkSet' acc (field, g) = mkSet (mkParen g) field (mkParen acc) + +-- Transform a regular record field update into a projection update. +recUpdFieldToProjUpdate :: LHsRecUpdField GhcPs -> LHsRecUpdProj GhcPs +recUpdFieldToProjUpdate (L l (HsRecField occ arg _)) = + mkProjUpdate l [L loc (fsLit f)] (val arg) + where + (loc, f) = field occ + + val :: LHsExpr GhcPs -> LHsExpr GhcPs + val arg = if isPun arg then mkVar $ snd (field occ) else arg + + isPun :: LHsExpr GhcPs -> Bool + isPun = \case + L _ (HsVar _ (L _ p)) -> p == pun_RDR + _ -> False + + field :: Located (AmbiguousFieldOcc GhcPs) -> (SrcSpan, String) + field = \case + L _ (Ambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) + L _ (Unambiguous _ (L loc lbl)) -> (loc, occNameString . rdrNameOcc $ lbl) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -210,6 +210,32 @@ rnExpr (NegApp _ e _) ; final_e <- mkNegAppRn e' neg_name ; return (final_e, fv_e `plusFV` fv_neg) } +------------------------------------------ +-- Record dot syntax +rnExpr (GetField x e f g) + = do { (e', _) <- rnLExpr e + ; (g', fv) <- rnLExpr g + ; return (GetField x e' f g', fv) + } + +rnExpr (Projection x fs p) + = do { (p', fv) <- rnLExpr p + ; return (Projection x fs p', fv) + } + +rnExpr (RecordDotUpd x e us f) + = do { (e', _) <- rnLExpr e + ; us' <- map fst <$> mapM rnRecUpdProj us + ; (f', fv) <- rnLExpr f + ; return (RecordDotUpd x e' us' f', fv) + } + where + rnRecUpdProj :: LHsRecUpdProj GhcPs -> RnM (LHsRecUpdProj GhcRn, FreeVars) + rnRecUpdProj (L l (ProjUpdate fs arg)) = do + (arg', fv) <- rnLExpr arg + return $ (L l (ProjUpdate { pu_flds = fs, pu_arg = arg' }), fv) + + ------------------------------------------ -- Template Haskell extensions rnExpr e@(HsBracket _ br_body) = rnBracket e br_body ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -927,6 +927,17 @@ tcExpr expr@(RecordUpd { rupd_expr = record_expr, rupd_flds = rbnds }) res_ty tcExpr (ArithSeq _ witness seq) res_ty = tcArithSeq witness seq res_ty +{- +************************************************************************ +* * + Record dot syntax +* * +************************************************************************ +-} +tcExpr (GetField _ _ _ (L _ g)) res_ty = tcExpr g res_ty +tcExpr (Projection _ _ (L _ p)) res_ty = tcExpr p res_ty +tcExpr (RecordDotUpd _ _ _ (L _ s)) res_ty = tcExpr s res_ty + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -493,6 +493,8 @@ exprCtOrigin (HsAppType _ e1 _) = lexprCtOrigin e1 exprCtOrigin (OpApp _ _ op _) = lexprCtOrigin op exprCtOrigin (NegApp _ e _) = lexprCtOrigin e exprCtOrigin (HsPar _ e) = lexprCtOrigin e +exprCtOrigin (GetField _ e _ _) = lexprCtOrigin e +exprCtOrigin (Projection _ _ _) = SectionOrigin exprCtOrigin (SectionL _ _ _) = SectionOrigin exprCtOrigin (SectionR _ _ _) = SectionOrigin exprCtOrigin (ExplicitTuple {}) = Shouldn'tHappenOrigin "explicit tuple" @@ -505,6 +507,7 @@ exprCtOrigin (HsDo {}) = DoOrigin exprCtOrigin (ExplicitList {}) = Shouldn'tHappenOrigin "list" exprCtOrigin (RecordCon {}) = Shouldn'tHappenOrigin "record construction" exprCtOrigin (RecordUpd {}) = Shouldn'tHappenOrigin "record update" +exprCtOrigin (RecordDotUpd {}) = Shouldn'tHappenOrigin "record dot update" exprCtOrigin (ExprWithTySig {}) = ExprSigOrigin exprCtOrigin (ArithSeq {}) = Shouldn'tHappenOrigin "arithmetic sequence" exprCtOrigin (HsPragE _ _ e) = lexprCtOrigin e ===================================== libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs ===================================== @@ -147,6 +147,7 @@ data Extension | CUSKs | StandaloneKindSignatures | LexicalNegation + | RecordDotSyntax deriving (Eq, Enum, Show, Generic, Bounded) -- 'Ord' and 'Bounded' are provided for GHC API users (see discussions -- in https://gitlab.haskell.org/ghc/ghc/merge_requests/2707 and ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no = Foo { bar.baz = 1 } + -- Syntax error: Can't use '.' in construction. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr ===================================== @@ -0,0 +1,2 @@ + RecordDotSyntaxFail0.hs:3:12: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE RecordDotSyntax #-} + +no Foo { bar.baz = x } = undefined + -- Syntax error: Field selector syntax doesn't participate + -- in patterns ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail1.hs:3:10: + Use of RecordDotSyntax `.' not valid. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs ===================================== @@ -0,0 +1,10 @@ +{-# LANGUAGE NoRecordDotSyntax #-} + +data Foo = Foo { foo :: Bar } +data Bar = Bar { bar :: Baz } +data Baz = Baz { baz :: Quux } +data Quux = Quux { quux :: Int } + +no :: Foo -> Foo +no = Foo { bar.baz = Quux { quux = 42 } } } } + -- Syntax error: RecordDotSyntax is not enabled ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail2.hs:9:15: parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs ===================================== @@ -0,0 +1,24 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) + +main = do + let b = Corge { (&&&) = 12 }; + print $ (b.(&&&)) + -- Syntax error: Dot notation is not available for fields with + -- operator names ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr ===================================== @@ -0,0 +1 @@ +RecordDotSyntaxFail3.hs:22:14: parse error on input ‘(’ ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE RecordDotSyntax #-} + +data Foo = Foo { foo :: Int } + +main = do + let a = Foo { foo = 1 } + print $ (const "hello") a .foo + -- Syntax error: f r .x is illegal. ===================================== testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr ===================================== @@ -0,0 +1,2 @@ +RecordDotSyntaxFail4.hs:7:29: error: + parse error on input ‘.’ ===================================== testsuite/tests/parser/should_fail/all.T ===================================== @@ -174,3 +174,8 @@ test('T18251d', normal, compile_fail, ['']) test('T18251e', normal, compile_fail, ['']) test('T18251f', normal, compile_fail, ['']) test('T12446', normal, compile_fail, ['']) +test('RecordDotSyntaxFail0', normal, compile_fail, ['']) +test('RecordDotSyntaxFail1', normal, compile_fail, ['']) +test('RecordDotSyntaxFail2', normal, compile_fail, ['']) +test('RecordDotSyntaxFail3', normal, compile_fail, ['']) +test('RecordDotSyntaxFail4', normal, compile_fail, ['']) ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.hs ===================================== @@ -0,0 +1,138 @@ +{-# LANGUAGE AllowAmbiguousTypes, FunctionalDependencies, ScopedTypeVariables, PolyKinds, TypeApplications, DataKinds #-} +{-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE RecordDotSyntax #-} +-- For "higher kinded data" test. +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE FlexibleInstances #-} + +-- Choice (C2a). + +import Data.Function -- for & +import Data.Functor.Identity + +class HasField x r a | x r -> a where + hasField :: r -> (a -> r, a) + +getField :: forall x r a . HasField x r a => r -> a +getField = snd . hasField @x -- Note: a.x = is getField @"x" a. + +setField :: forall x r a . HasField x r a => r -> a -> r +setField = fst . hasField @x -- Note : a{x = b} is setField @"x" a b. + +-- 'Foo' has 'foo' field of type 'Bar' +data Foo = Foo { foo :: Bar } deriving (Show, Eq) +instance HasField "foo" Foo Bar where + hasField r = (\x -> case r of Foo { .. } -> Foo { foo = x, .. }, foo r) + +-- 'Bar' has a 'bar' field of type 'Baz' +data Bar = Bar { bar :: Baz } deriving (Show, Eq) +instance HasField "bar" Bar Baz where + hasField r = (\x -> case r of Bar { .. } -> Bar { bar = x, .. }, bar r) + +-- 'Baz' has a 'baz' field of type 'Quux' +data Baz = Baz { baz :: Quux } deriving (Show, Eq) +instance HasField "baz" Baz Quux where + hasField r = (\x -> case r of Baz { .. } -> Baz { baz = x, .. }, baz r) + +-- 'Quux' has a 'quux' field of type 'Int' +data Quux = Quux { quux :: Int } deriving (Show, Eq) +instance HasField "quux" Quux Int where + hasField r = (\x -> case r of Quux { .. } -> Quux { quux = x, .. }, quux r) + +-- 'Corge' has a '&&&' field of type 'Int' +data Corge = Corge { (&&&) :: Int } deriving (Show, Eq) +instance HasField "&&&" Corge Int where + hasField r = (\x -> case r of Corge { .. } -> Corge { (&&&) = x, .. }, (&&&) r) +-- Note : Dot notation is not available for fields with operator +-- names. + +-- 'Grault' has two fields 'f' and 'g' of type 'Foo'. +data Grault = Grault {f :: Foo, g :: Foo} deriving (Show, Eq) +instance HasField "f" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { f = x, .. }, f r) +instance HasField "g" Grault Foo where + hasField r = (\x -> case r of Grault { .. } -> Grault { g = x, .. }, g r) + +-- "Higher kinded data" +-- (see https://reasonablypolymorphic.com/blog/higher-kinded-data/) +type family H f a where + H Identity a = a + H f a = f a +data P f = P + { n :: H f String + } +-- See https://github.com/ndmitchell/record-dot-preprocessor/pull/34. +instance (a ~ H f String) => HasField "n" (P f) a where + hasField r = (\x -> case r of P { .. } -> P { n = x, .. }, n r) + +main = do + let a = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 42 } } } } + let b = Corge{ (&&&) = 12 }; + let c = Grault { + f = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + , g = Foo { foo = Bar{ bar = Baz { baz = Quux { quux = 1 } } } } + } + + -- A "selector" is an expression like '(.a)' or '(.a.b)'. + putStrLn "-- selectors:" + print $ (.foo) a -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (.foo.bar) a -- Baz { baz = Quux { quux = 42 } } + print $ (.foo.bar.baz) a -- Quux { quux = 42 } + print $ (.foo.bar.baz.quux) a -- 42 + print $ ((&&&) b) -- 12 + -- print $ (b.(&&&)) -- illegal : parse error on input ‘(’ + print $ getField @"&&&" b -- 12 + + -- A "selection" is an expression like 'r.a' or '(f r).a.b'. + putStrLn "-- selections:" + print $ a.foo.bar.baz.quux -- 42 + print $ a.foo.bar.baz -- Quux { quux = 42 } + print $ a.foo.bar -- Baz { baz = Quux { quux = 42 } } + print $ a.foo -- Bar { bar = Baz { baz = Quux { quux = 42 } } } + print $ (const "hello") a.foo -- f r.x means f (r.x) + -- print $ f a .foo -- f r .x is illegal + print $ (const "hello") (id a).foo -- f (g r).x means f ((g r).x) + -- print $ f (g a) .foo -- f (g r) .x is illegal + print $ a.foo + & (.bar.baz.quux) -- 42 + print $ (a.foo + ).bar.baz.quux -- 42 + print $ (+) a.foo.bar.baz.quux 1 -- 43 + print $ (+) (id a).foo.bar.baz.quux 1 -- 43 + print $ (+) ((id a).foo.bar & (.baz.quux)) 1 -- 43 + + -- An "update" is an expression like 'r{ a.b = 12 }'. + putStrLn "-- updates:" + print $ (a.foo.bar.baz) { quux = 2 } -- Quux { quux = 2 } + print $ (\b -> b{ bar=Baz{ baz=Quux{ quux=1 } } }) a.foo -- Bar { bar = Baz { baz = Quux { quux = 1 } } } + let bar = Bar { bar = Baz { baz = Quux { quux = 44 } } } + print $ a{ foo.bar = Baz { baz = Quux { quux = 44 } } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 44 } } } } + print $ a{ foo.bar.baz = Quux { quux = 45 } } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 45 } } } } + print $ a{ foo.bar.baz.quux = 46 } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 46 } } } } + print $ c{ f.foo.bar.baz.quux = 3, g.foo.bar.baz.quux = 4 } -- Grault { f = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 3 } } } }, g = Foo { foo = Bar { bar = Baz { baz = Quux { quux = 4 } } } } } + + -- A "punned update" is an expression like 'r{ a.b }' (where it is + -- understood that 'b' is a variable binding in the environment of + -- the field update - enabled only when the extension + -- 'NamedFieldPuns' is in effect). + putStrLn "-- punned updates:" + let quux = 102; baz = Quux { quux }; bar = Baz { baz }; foo = Bar { bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz.quux } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar.baz } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo.bar } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a{ foo } -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 102 } } } } + print $ a -- Foo { foo = Bar { bar = Baz { baz = Quux { quux = 42 } } } } + print $ c{ f.foo, g.foo.bar.baz.quux = 4 } -- Mix punned and explicit; 102, 4 + f <- pure a + g <- pure a + print $ c{ f } -- 42, 1 + print $ c{ f, g } -- 42, 42 + print $ c{ f, g.foo.bar.baz.quux = 4 } -- Mix top-level and nested updates; 42, 4 + + putStrLn "-- misc:" + -- Higher kinded test. + let p = P { n = Just "me" } :: P Maybe + Just me <- pure p.n + putStrLn $ me ===================================== testsuite/tests/parser/should_run/RecordDotSyntax.stdout ===================================== @@ -0,0 +1,38 @@ +-- selectors: +Bar {bar = Baz {baz = Quux {quux = 42}}} +Baz {baz = Quux {quux = 42}} +Quux {quux = 42} +42 +12 +12 +-- selections: +42 +Quux {quux = 42} +Baz {baz = Quux {quux = 42}} +Bar {bar = Baz {baz = Quux {quux = 42}}} +"hello" +"hello" +42 +42 +43 +43 +43 +-- updates: +Quux {quux = 2} +Bar {bar = Baz {baz = Quux {quux = 1}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 44}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 45}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 46}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 3}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- punned updates: +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}} +Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 102}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 1}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}} +Grault {f = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 42}}}}, g = Foo {foo = Bar {bar = Baz {baz = Quux {quux = 4}}}}} +-- misc: +me ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -19,3 +19,4 @@ test('CountParserDeps', compile_and_run, ['-package ghc']) test('LexNegLit', normal, compile_and_run, ['']) +test('RecordDotSyntax', normal, compile_and_run, ['']) ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 2d06af2fc535dacc4bac45d45e8eb95a7620caac +Subproject commit 88f8549694b8636dd7dcabe33a4e53db7e342760 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4204a4036edeb83c27193593e2fe5c67c27f705d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4204a4036edeb83c27193593e2fe5c67c27f705d 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 Fri Nov 27 21:27:38 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Fri, 27 Nov 2020 16:27:38 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] Cleanup number primop conversion names Message-ID: <5fc16f4aeac8_86c879fa9c681158@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: 7b2ca810 by John Ericson at 2020-11-27T21:26:03+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/binary - libraries/bytestring - libraries/ghci/GHCi/BreakArray.hs - testsuite/tests/array/should_run/arr020.hs - testsuite/tests/cmm/opt/T18141.hs - testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_run/cgrun070.hs - testsuite/tests/codeGen/should_run/cgrun072.hs - testsuite/tests/codeGen/should_run/cgrun075.hs - testsuite/tests/codeGen/should_run/cgrun076.hs - testsuite/tests/codeGen/should_run/compareByteArrays.hs - testsuite/tests/ffi/should_run/PrimFFIInt16.hs - testsuite/tests/ffi/should_run/PrimFFIInt8.hs - testsuite/tests/ffi/should_run/PrimFFIWord16.hs - testsuite/tests/ffi/should_run/PrimFFIWord8.hs - testsuite/tests/ffi/should_run/T16650a.hs - testsuite/tests/ffi/should_run/T16650b.hs - testsuite/tests/ffi/should_run/UnliftedNewtypesByteArrayOffset.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b2ca8106492a0bcf119435459fa52713e2bf0bf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b2ca8106492a0bcf119435459fa52713e2bf0bf 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 Fri Nov 27 21:30:15 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Fri, 27 Nov 2020 16:30:15 -0500 Subject: [Git][ghc/ghc][wip/fixed-width-lits] 13 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc16fe74034e_86cbee25906816a@gitlab.mail> John Ericson pushed to branch wip/fixed-width-lits at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - b654f828 by John Ericson at 2020-11-27T21:06:24+00:00 Make primop handler indentation more consistent - - - - - 32e0ca22 by John Ericson at 2020-11-27T21:06:24+00:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 7b2ca810 by John Ericson at 2020-11-27T21:26:03+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 044908fd by Sylvain Henry at 2020-11-27T21:29:48+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9ffabc576acc84fd8429a12f32e76b84ef7a0003...044908fdf542d2b4b2001760fd407abb830d1a8f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9ffabc576acc84fd8429a12f32e76b84ef7a0003...044908fdf542d2b4b2001760fd407abb830d1a8f 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 Fri Nov 27 21:36:14 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Fri, 27 Nov 2020 16:36:14 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 19 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc1714ec18d9_86c3fc6aa253af468218d@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - b654f828 by John Ericson at 2020-11-27T21:06:24+00:00 Make primop handler indentation more consistent - - - - - 32e0ca22 by John Ericson at 2020-11-27T21:06:24+00:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 7b2ca810 by John Ericson at 2020-11-27T21:26:03+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 044908fd by Sylvain Henry at 2020-11-27T21:29:48+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - b9b2e9f6 by John Ericson at 2020-11-27T21:33:33+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 538b279c by John Ericson at 2020-11-27T21:33:33+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 5ba03e33 by Sylvain Henry at 2020-11-27T21:33:33+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 65161293 by John Ericson at 2020-11-27T21:33:33+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - ef772dc7 by John Ericson at 2020-11-27T21:33:33+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 56a2ac3d by John Ericson at 2020-11-27T21:33:33+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a7145381124af853815639a48b752b9ac995d2a...56a2ac3d302a5c6f949264877e999f2789efecc8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a7145381124af853815639a48b752b9ac995d2a...56a2ac3d302a5c6f949264877e999f2789efecc8 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 Fri Nov 27 21:36:20 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Fri, 27 Nov 2020 16:36:20 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere-new-float-primops] 24 commits: rts: Flush eventlog buffers from flushEventLog Message-ID: <5fc1715433522_86c113a5b2c6829ea@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere-new-float-primops at Glasgow Haskell Compiler / GHC Commits: f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - b654f828 by John Ericson at 2020-11-27T21:06:24+00:00 Make primop handler indentation more consistent - - - - - 32e0ca22 by John Ericson at 2020-11-27T21:06:24+00:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 7b2ca810 by John Ericson at 2020-11-27T21:26:03+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 044908fd by Sylvain Henry at 2020-11-27T21:29:48+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - b9b2e9f6 by John Ericson at 2020-11-27T21:33:33+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 538b279c by John Ericson at 2020-11-27T21:33:33+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 5ba03e33 by Sylvain Henry at 2020-11-27T21:33:33+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - 65161293 by John Ericson at 2020-11-27T21:33:33+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - ef772dc7 by John Ericson at 2020-11-27T21:33:33+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 56a2ac3d by John Ericson at 2020-11-27T21:33:33+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 674bde54 by John Ericson at 2020-11-27T21:35:25+00:00 WIP: Add missing floats <-> int/word 64 rule and primops - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/CPrim.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Runtime/Heap/Inspect.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/058ad8764037428307839660f5df7e38fc59fa38...674bde54111594967b8f7494bd741cb7464d7f3b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/058ad8764037428307839660f5df7e38fc59fa38...674bde54111594967b8f7494bd741cb7464d7f3b 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 Fri Nov 27 22:18:32 2020 From: gitlab at gitlab.haskell.org (Adam Gundry) Date: Fri, 27 Nov 2020 17:18:32 -0500 Subject: [Git][ghc/ghc][wip/amg/fieldselectors] 3 commits: Extend GHCiDRF test to cover ambiguous cases Message-ID: <5fc17b38e4800_86c113a5b2c6842e2@gitlab.mail> Adam Gundry pushed to branch wip/amg/fieldselectors at Glasgow Haskell Compiler / GHC Commits: 4d869ff4 by Adam Gundry at 2020-11-27T21:46:51+00:00 Extend GHCiDRF test to cover ambiguous cases - - - - - 1ab5d01d by Adam Gundry at 2020-11-27T21:58:54+00:00 More GHC.Rename.Env cleanup - - - - - 162738d2 by Adam Gundry at 2020-11-27T22:18:00+00:00 Tweak fieldSelectorSuggestions message - - - - - 10 changed files: - compiler/GHC/Rename/Env.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Unbound.hs - testsuite/tests/ghci/GHCiDRF/GHCiDRF.T - testsuite/tests/ghci/GHCiDRF/GHCiDRF.hs - testsuite/tests/ghci/GHCiDRF/GHCiDRF.script - testsuite/tests/ghci/GHCiDRF/GHCiDRF.stdout - testsuite/tests/patsyn/should_fail/records-nofieldselectors.stderr - testsuite/tests/rename/should_fail/NFSSuppressed.stderr Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -10,27 +10,38 @@ GHC.Rename.Env contains functions which convert RdrNames into Names. -} module GHC.Rename.Env ( + -- * newTopSrcBinder newTopSrcBinder, + + -- * Top-level binder occurrences lookupLocatedTopBndrRn, lookupTopBndrRn, + lookupLocatedOccRn, lookupOccRn, lookupOccRn_maybe, - lookupLocalOccRn_maybe, lookupInfoOccRn, - lookupLocalOccThLvl_maybe, lookupLocalOccRn, + lookupInfoOccRn, + lookupLocalOccRn, lookupTypeOccRn, lookupGlobalOccRn, lookupGlobalOccRn_maybe, + LookupOccResult(..), lookupOccRn_overloaded_maybe, - lookupGlobalOccRn_overloaded, + -- * lookupSubBndrOcc ChildLookupResult(..), - lookupSubBndrOcc_helper, + lookupInstDeclBndr, + lookupFamInstName, combineChildLookupResult, -- Called by lookupChildrenExport + -- * lookupBindGroupOcc HsSigCtxt(..), lookupLocalTcNames, lookupSigOccRn, lookupSigCtxtOccRn, - lookupInstDeclBndr, lookupRecFieldOcc, lookupFamInstName, + -- * Record field occurrences lookupConstructorFields, + lookupRecFieldOcc, + lookupRecFieldOcc_update, + -- * Export lists + lookupSubBndrOcc_helper, lookupGreAvailRn, -- Rebindable Syntax @@ -75,7 +86,7 @@ import GHC.Core.DataCon import GHC.Core.TyCon import GHC.Utils.Error ( MsgDoc ) import GHC.Builtin.Names( rOOT_MAIN ) -import GHC.Types.Basic ( TopLevelFlag(..), TupleSort(..) ) +import GHC.Types.Basic ( TupleSort(..) ) import GHC.Types.SrcLoc as SrcLoc import GHC.Utils.Outputable as Outputable import GHC.Types.Unique.Set ( uniqSetAny ) @@ -922,12 +933,6 @@ lookupLocalOccRn_maybe rdr_name = do { local_env <- getLocalRdrEnv ; return (lookupLocalRdrEnv local_env rdr_name) } -lookupLocalOccThLvl_maybe :: Name -> RnM (Maybe (TopLevelFlag, ThLevel)) --- Just look in the local environment -lookupLocalOccThLvl_maybe name - = do { lcl_env <- getLclEnv - ; return (lookupNameEnv (tcl_th_bndrs lcl_env) name) } - -- lookupOccRn looks up an occurrence of a RdrName lookupOccRn :: RdrName -> RnM Name lookupOccRn rdr_name @@ -946,6 +951,7 @@ lookupLocalOccRn rdr_name Nothing -> unboundName WL_LocalOnly rdr_name } -- lookupTypeOccRn looks up an optionally promoted RdrName. +-- Used for looking up type variables. lookupTypeOccRn :: RdrName -> RnM Name -- see Note [Demotion] lookupTypeOccRn rdr_name @@ -1192,7 +1198,20 @@ lookupGlobalOccRn_resolve overload_ok rdr_name res = case res of addNameClashErrRn rdr_name gres return $ Just $ LookupOccName $ gre_name (NE.head gres) --- | Used when looking up fields in record updates. +-- | Used when looking up fields in record updates. Returns 'Just' the selector +-- name, or 'Nothing' if the field is ambiguous. (Also returns 'Just' if the +-- field is not in scope.) +lookupRecFieldOcc_update + :: DuplicateRecordFields + -> RdrName + -> RnM (Maybe Name) +lookupRecFieldOcc_update overload_ok rdr_name = do + res <- lookupGlobalOccRn_overloaded IncludeFieldsWithoutSelectors overload_ok rdr_name + case res of + LookupOccName sel_name -> return (Just sel_name) + LookupOccFields (fl NE.:| []) -> return (Just (flSelector fl)) + LookupOccFields (_ NE.:| _:_) -> return Nothing + lookupGlobalOccRn_overloaded :: FieldsOrSelectors -> DuplicateRecordFields ===================================== compiler/GHC/Rename/Pat.hs ===================================== @@ -745,10 +745,10 @@ rnHsRecUpdFields flds , hsRecFieldArg = arg , hsRecPun = pun })) = do { let lbl = rdrNameAmbiguousFieldOcc f - ; sel <- setSrcSpan loc $ + ; mb_sel <- setSrcSpan loc $ -- Defer renaming of overloaded fields to the typechecker -- See Note [Disambiguating record fields] in GHC.Tc.Gen.Head - lookupGlobalOccRn_overloaded IncludeFieldsWithoutSelectors overload_ok lbl + lookupRecFieldOcc_update overload_ok lbl ; arg' <- if pun then do { checkErr pun_ok (badPun (L loc lbl)) -- Discard any module qualifier (#11662) @@ -757,18 +757,11 @@ rnHsRecUpdFields flds else return arg ; (arg'', fvs) <- rnLExpr arg' - ; let fvs' = case sel of -- AMG TODO review this - LookupOccName sel_name -> fvs `addOneFV` sel_name - LookupOccFields (fld NE.:| []) -> fvs `addOneFV` flSelector fld - _ -> fvs - lbl' = case sel of - LookupOccName sel_name -> - L loc (Unambiguous sel_name (L loc lbl)) - LookupOccFields (fld NE.:| []) -> - L loc (Unambiguous (flSelector fld) (L loc lbl)) - _ -> L loc (Ambiguous noExtField (L loc lbl)) - - ; return (L l (HsRecField { hsRecFieldLbl = lbl' + ; let (lbl', fvs') = case mb_sel of + Just sel_name -> (Unambiguous sel_name (L loc lbl), fvs `addOneFV` sel_name) + Nothing -> (Ambiguous noExtField (L loc lbl), fvs) + + ; return (L l (HsRecField { hsRecFieldLbl = L loc lbl' , hsRecFieldArg = arg'' , hsRecPun = pun }), fvs') } ===================================== compiler/GHC/Rename/Splice.hs ===================================== @@ -16,6 +16,7 @@ module GHC.Rename.Splice ( import GHC.Prelude import GHC.Types.Name +import GHC.Types.Name.Env import GHC.Types.Name.Set import GHC.Hs import GHC.Types.Name.Reader @@ -184,6 +185,12 @@ rn_bracket _ (DecBrG {}) = panic "rn_bracket: unexpected DecBrG" rn_bracket _ (TExpBr x e) = do { (e', fvs) <- rnLExpr e ; return (TExpBr x e', fvs) } +lookupLocalOccThLvl_maybe :: Name -> RnM (Maybe (TopLevelFlag, ThLevel)) +-- Just look in the local environment +lookupLocalOccThLvl_maybe name + = do { lcl_env <- getLclEnv + ; return (lookupNameEnv (tcl_th_bndrs lcl_env) name) } + quotationCtxtDoc :: HsBracket GhcPs -> SDoc quotationCtxtDoc br_body = hang (text "In the Template Haskell quotation") ===================================== compiler/GHC/Rename/Unbound.hs ===================================== @@ -119,18 +119,24 @@ unknownNameSuggestions_ where_look dflags hpt curr_mod global_env local_env extensionSuggestions tried_rdr_name $$ fieldSelectorSuggestions global_env tried_rdr_name +-- | When the name is in scope as field whose selector has been suppressed by +-- NoFieldSelectors, display a helpful message explaining this. fieldSelectorSuggestions :: GlobalRdrEnv -> RdrName -> SDoc fieldSelectorSuggestions global_env tried_rdr_name - = case filter isNoFieldSelectorGRE $ lookupGRE_RdrName' IncludeFieldsWithoutSelectors tried_rdr_name global_env of - gre : _ -> text "NB:" - <+> ppr tried_rdr_name - <+> whose gre - <+> text "field selector that has been suppressed by NoFieldSelectors" - _ -> Outputable.empty + | null gres = Outputable.empty + | otherwise = text "NB:" + <+> quotes (ppr tried_rdr_name) + <+> text "is a field selector" <+> whose + $$ text "that has been suppressed by NoFieldSelectors" where - whose gre = case gre_par gre of - NoParent -> text "is a" - ParentIs parent -> text "is" <+> ppr parent <> text "'s" + gres = filter isNoFieldSelectorGRE $ + lookupGRE_RdrName' IncludeFieldsWithoutSelectors tried_rdr_name global_env + parents = [ parent | ParentIs parent <- map gre_par gres ] + + -- parents may be empty if this is a pattern synonym field without a selector + whose | null parents = empty + | otherwise = text "belonging to the type" <> plural parents + <+> pprQuotedList parents similarNameSuggestions :: WhereLooking -> DynFlags -> GlobalRdrEnv -> LocalRdrEnv ===================================== testsuite/tests/ghci/GHCiDRF/GHCiDRF.T ===================================== @@ -1,4 +1,5 @@ test('GHCiDRF' , [extra_hc_opts("-fimplicit-import-qualified") , extra_files(['GHCiDRF.hs']) + , combined_output ], ghci_script, ['GHCiDRF.script']) ===================================== testsuite/tests/ghci/GHCiDRF/GHCiDRF.hs ===================================== @@ -1,3 +1,4 @@ {-# LANGUAGE DuplicateRecordFields #-} module GHCiDRF where -data T = MkT { foo :: Int } +data T = MkT { foo :: Int, bar :: Int } +data U = MkU { bar :: Bool } ===================================== testsuite/tests/ghci/GHCiDRF/GHCiDRF.script ===================================== @@ -1,2 +1,10 @@ :l GHCiDRF :t GHCiDRF.foo +:t GHCiDRF.bar +:info GHCiDRF.foo +:info GHCiDRF.bar +:m - GHCiDRF +:t GHCiDRF.foo +:t GHCiDRF.bar +:info GHCiDRF.foo +:info GHCiDRF.bar ===================================== testsuite/tests/ghci/GHCiDRF/GHCiDRF.stdout ===================================== @@ -1 +1,30 @@ -GHCiDRF.foo :: T -> Int \ No newline at end of file +GHCiDRF.foo :: T -> Int + +:1:1: error: + Ambiguous occurrence ‘GHCiDRF.bar’ + It could refer to + either the field ‘bar’, defined at GHCiDRF.hs:4:16 + or the field ‘bar’, defined at GHCiDRF.hs:3:28 +type T :: * +data T = MkT {foo :: Int, ...} + -- Defined at GHCiDRF.hs:3:16 +type U :: * +data U = MkU {GHCiDRF.bar :: Bool} + -- Defined at GHCiDRF.hs:4:16 + +type T :: * +data T = MkT {..., GHCiDRF.bar :: Int} + -- Defined at GHCiDRF.hs:3:28 +GHCiDRF.foo :: GHCiDRF.T -> Int + +:1:1: error: Not in scope: ‘GHCiDRF.bar’ +type GHCiDRF.T :: * +data GHCiDRF.T = GHCiDRF.MkT {GHCiDRF.foo :: Int, ...} + -- Defined at GHCiDRF.hs:3:16 +type GHCiDRF.T :: * +data GHCiDRF.T = GHCiDRF.MkT {..., GHCiDRF.bar :: Int} + -- Defined at GHCiDRF.hs:3:28 + +type GHCiDRF.U :: * +data GHCiDRF.U = GHCiDRF.MkU {GHCiDRF.bar :: Bool} + -- Defined at GHCiDRF.hs:4:16 ===================================== testsuite/tests/patsyn/should_fail/records-nofieldselectors.stderr ===================================== @@ -1,4 +1,5 @@ records-nofieldselectors.hs:9:12: error: • Variable not in scope: x :: [a0] -> Int - NB: x is a field selector that has been suppressed by NoFieldSelectors + • NB: ‘x’ is a field selector + that has been suppressed by NoFieldSelectors ===================================== testsuite/tests/rename/should_fail/NFSSuppressed.stderr ===================================== @@ -1,5 +1,6 @@ -NFSSuppressed.hs:9:5: - Variable not in scope: foo - Perhaps you meant data constructor ‘Foo’ (line 7) - NB: foo is Foo's field selector that has been suppressed by NoFieldSelectors \ No newline at end of file +NFSSuppressed.hs:9:5: error: + • Variable not in scope: foo + • Perhaps you meant data constructor ‘Foo’ (line 7) + NB: ‘foo’ is a field selector belonging to the type ‘Foo’ + that has been suppressed by NoFieldSelectors View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78970cde8c63f6243130971fe94181338a63cbc3...162738d2f027c54ea7fe081c2308ed5f10a535d7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/78970cde8c63f6243130971fe94181338a63cbc3...162738d2f027c54ea7fe081c2308ed5f10a535d7 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 Fri Nov 27 22:32:20 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 17:32:20 -0500 Subject: [Git][ghc/ghc][wip/timings-allocations] 55 commits: testsuite: Add testcase for #18733 Message-ID: <5fc17e743cc83_86cfd752bc6844a5@gitlab.mail> Ben Gamari pushed to branch wip/timings-allocations at Glasgow Haskell Compiler / GHC Commits: 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 383155a2 by Ben Gamari at 2020-11-27T17:32:17-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Dwarf.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/Dwarf/Types.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion/Opt.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5f7e3700ea6e2c310d6bf35956df2d815f31c6e...383155a2f7c28c7722f9d1574130c60cac709a3a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c5f7e3700ea6e2c310d6bf35956df2d815f31c6e...383155a2f7c28c7722f9d1574130c60cac709a3a 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 Fri Nov 27 23:16:43 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 18:16:43 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] 13 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc188db3d43e_86c3fc6aa253af46873f7@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - edf577c0 by Ben Gamari at 2020-11-27T18:16:29-05:00 rts/linker: Don't allow shared libraries to be loaded multiple times - - - - - a6378570 by Ben Gamari at 2020-11-27T18:16:29-05:00 rts/linker: Initialise CCSs from native shared objects - - - - - 80476bdb by Ben Gamari at 2020-11-27T18:16:29-05:00 rts/linker: Move shared library loading logic into Elf.c - - - - - 9e17fe18 by GHC GitLab CI at 2020-11-27T18:16:29-05:00 rts/linker: Don't declare dynamic objects with image_mapped This previously resulted in warnings due to spurious unmap failures. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ea36515eeda8132513fc26d60731b1c6907b5baa...9e17fe18742e52936211d46963b8fdc9616895bd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ea36515eeda8132513fc26d60731b1c6907b5baa...9e17fe18742e52936211d46963b8fdc9616895bd 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 Fri Nov 27 23:19:27 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Fri, 27 Nov 2020 18:19:27 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fc1897f4ee49_86cbee25906879fd@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: 9bed2088 by Shayne Fletcher at 2020-11-27T18:19:01-05:00 Record dot syntax - - - - - 30 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - + docs/users_guide/exts/record_dot_syntax.rst - docs/users_guide/exts/records.rst - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout - testsuite/tests/parser/should_run/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9bed2088684253a36f173eab5726ae74236a040d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9bed2088684253a36f173eab5726ae74236a040d 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 Fri Nov 27 23:30:52 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 18:30:52 -0500 Subject: [Git][ghc/ghc][wip/win32-m32] 15 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc18c2c8910b_86c3fc6aa253af4689244@gitlab.mail> Ben Gamari pushed to branch wip/win32-m32 at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 396fe39e by Ben Gamari at 2020-11-27T18:30:42-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - 30b4668b by Ben Gamari at 2020-11-27T18:30:42-05:00 rts: Introduce mmapAnonForLinker Previously most of the uses of mmapForLinker were mapping anonymous memory, resulting in a great deal of unnecessary repetition. Factor this out into a new helper. Also fixes a few places where error checking was missing or suboptimal. - - - - - 1e5a25a8 by Ben Gamari at 2020-11-27T18:30:42-05:00 rts/linker: Introduce munmapForLinker Consolidates munmap calls to ensure consistent error handling. - - - - - 99f82448 by Ben Gamari at 2020-11-27T18:30:42-05:00 rts/Linker: Introduce Windows implementations for mmapForLinker, et al. - - - - - 0782380e by Ben Gamari at 2020-11-27T18:30:42-05:00 rts/m32: Introduce NEEDS_M32 macro Instead of relying on RTS_LINKER_USE_MMAP - - - - - b70fa768 by Ben Gamari at 2020-11-27T18:30:42-05:00 rts/linker: Use m32 to allocate symbol extras in PEi386 - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f6c843a8da43748f0365fbac1b73c80883b64499...b70fa768dfcf58cbd67e9e2224791be1839c6945 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f6c843a8da43748f0365fbac1b73c80883b64499...b70fa768dfcf58cbd67e9e2224791be1839c6945 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 Fri Nov 27 23:33:23 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 18:33:23 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/backport/8.10/T18857 Message-ID: <5fc18cc37d88e_86c113a5b2c6963b2@gitlab.mail> Ben Gamari deleted branch wip/backport/8.10/T18857 at Glasgow Haskell Compiler / GHC -- 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 Fri Nov 27 23:33:24 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 18:33:24 -0500 Subject: [Git][ghc/ghc][ghc-8.10] CmmToLlvm: Declare signature for memcmp Message-ID: <5fc18cc49e9ff_86c879fa9c696534@gitlab.mail> Ben Gamari pushed to branch ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: 70ac4ed8 by Moritz Angermann at 2020-11-25T10:41:34+08:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 4 changed files: - compiler/llvmGen/LlvmCodeGen/Base.hs - rts/linker/Elf.c - rts/linker/elf_reloc_aarch64.c - testsuite/driver/testlib.py Changes: ===================================== compiler/llvmGen/LlvmCodeGen/Base.hs ===================================== @@ -475,13 +475,16 @@ getUniqMeta s = getEnv (flip lookupUFM s . envUniqMeta) ghcInternalFunctions :: LlvmM () ghcInternalFunctions = do dflags <- getDynFlags - mk "memcpy" i8Ptr [i8Ptr, i8Ptr, llvmWord dflags] - mk "memmove" i8Ptr [i8Ptr, i8Ptr, llvmWord dflags] - mk "memset" i8Ptr [i8Ptr, llvmWord dflags, llvmWord dflags] - mk "newSpark" (llvmWord dflags) [i8Ptr, i8Ptr] + let w = llvmWord dflags + cint = LMInt $ widthInBits $ cIntWidth dflags + mk "memcmp" cint [i8Ptr, i8Ptr, w] + mk "memcpy" i8Ptr [i8Ptr, i8Ptr, w] + mk "memmove" i8Ptr [i8Ptr, i8Ptr, w] + mk "memset" i8Ptr [i8Ptr, w, w] + mk "newSpark" w [i8Ptr, i8Ptr] where mk n ret args = do - let n' = llvmDefLabel $ fsLit n + let n' = fsLit n decl = LlvmFunctionDecl n' ExternallyVisible CC_Ccc ret FixedArgs (tysToParams args) Nothing renderLlvm $ ppLlvmFunctionDecl decl @@ -538,7 +541,10 @@ getGlobalPtr llvmLbl = do let mkGlbVar lbl ty = LMGlobalVar lbl (LMPointer ty) Private Nothing Nothing case m_ty of -- Directly reference if we have seen it already - Just ty -> return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global + Just ty -> do + if llvmLbl `elem` (map fsLit ["newSpark", "memmove", "memcpy", "memcmp", "memset"]) + then return $ mkGlbVar (llvmLbl) ty Global + else return $ mkGlbVar (llvmDefLabel llvmLbl) ty Global -- Otherwise use a forward alias of it Nothing -> do saveAlias llvmLbl ===================================== rts/linker/Elf.c ===================================== @@ -781,7 +781,12 @@ ocGetNames_ELF ( ObjectCode* oc ) else if (!oc->imageMapped || size < getPageSize() / 3) { bool executable = kind == SECTIONKIND_CODE_OR_RODATA; m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32; - start = m32_alloc(allocator, size, 8); + // align on 16 bytes. The reason being that llvm will emit see + // paddq statements for x86_64 under optimisation and load from + // RODATA sections. Specifically .rodata.cst16. However we don't + // handle the cst part in any way what so ever, so 16 seems + // better than 8. + start = m32_alloc(allocator, size, 16); if (start == NULL) goto fail; memcpy(start, oc->image + offset, size); alloc = SECTION_M32; @@ -940,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - + ASSERT(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -1866,6 +1871,7 @@ ocResolve_ELF ( ObjectCode* oc ) #endif ASSERT(symbol->elf_sym->st_name == 0); ASSERT(symbol->elf_sym->st_value == 0); + ASSERT(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1939,6 +1945,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { + ASSERT(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -297,7 +297,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(symbol != NULL); + assert(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -324,6 +324,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { ELF64_R_SYM((Elf64_Xword)rel->r_info)); assert(0x0 != symbol); + assert(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== testsuite/driver/testlib.py ===================================== @@ -2113,6 +2113,13 @@ def normalise_errmsg(s: str) -> str: s = re.sub('Failed to remove file (.*); error= (.*)$', '', s) s = re.sub('DeleteFile "(.+)": permission denied \(Access is denied\.\)(.*)$', '', s) + # filter out unsupported GNU_PROPERTY_TYPE (5), which is emitted by LLVM10 + # and not understood by older binutils (ar, ranlib, ...) + s = modify_lines(s, lambda l: re.sub('^(.+)warning: (.+): unsupported GNU_PROPERTY_TYPE \(5\) type: 0xc000000(.*)$', '', l)) + + # filter out nix garbage, that just keeps on showing up as errors on darwin + s = modify_lines(s, lambda l: re.sub('^(.+)\.dylib, ignoring unexpected dylib file$','', l)) + return s # normalise a .prof file, so that we can reasonably compare it against @@ -2183,6 +2190,9 @@ def normalise_output( s: str ) -> str: s = re.sub('([^\\s])\\.exe', '\\1', s) s = normalise_callstacks(s) s = normalise_type_reps(s) + # ghci outputs are pretty unstable with -fexternal-dynamic-refs, which is + # requires for -fPIC + s = re.sub(' -fexternal-dynamic-refs\n','',s) return s def normalise_asm( s: str ) -> str: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/70ac4ed84f4e95f3b3772242368582cf911e50c4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/70ac4ed84f4e95f3b3772242368582cf911e50c4 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 Fri Nov 27 23:41:28 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Fri, 27 Nov 2020 18:41:28 -0500 Subject: [Git][ghc/ghc][ghc-9.0] 8.10 - dirty MVAR after mutating TSO queue head Message-ID: <5fc18ea83f7a3_86c3fc6ab29b100701439@gitlab.mail> Ben Gamari pushed to branch ghc-9.0 at Glasgow Haskell Compiler / GHC Commits: b944fd08 by Viktor Dukhovni at 2020-11-27T18:39:43-05:00 8.10 - dirty MVAR after mutating TSO queue head While the original head and tail of the TSO queue may be in the same generation as the MVAR, interior elements of the queue could be younger after a GC run and may then be exposed by putMVar operation that updates the queue head. Resolves #18919 (cherry picked from commit 699facec0bc8dd7d5b82cc537fbf131b74f5bd2c) - - - - - 2 changed files: - rts/PrimOps.cmm - rts/Threads.c Changes: ===================================== rts/PrimOps.cmm ===================================== @@ -1812,9 +1812,16 @@ loop: // There are readMVar/takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1839,10 +1846,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); @@ -1897,9 +1902,16 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1924,10 +1936,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/Threads.c ===================================== @@ -803,9 +803,14 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = q->tso; - mvar->head = q->link; - if (mvar->head == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { + mvar->head = q = q->link; + if (q == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { mvar->tail = (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure; + } else { + if (info == &stg_MVAR_CLEAN_info) { + // Resolve #18919. + dirty_MVAR(&cap->r, (StgClosure*)mvar, mvar->value); + } } ASSERT(tso->block_info.closure == (StgClosure*)mvar); @@ -829,10 +834,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = ((StgMVarTSOQueue*)q)->link; + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b944fd08884527c4fee7286ac60e0a9bd6ebf424 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b944fd08884527c4fee7286ac60e0a9bd6ebf424 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 Fri Nov 27 23:46:00 2020 From: gitlab at gitlab.haskell.org (Andreas Klebinger) Date: Fri, 27 Nov 2020 18:46:00 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/opt_cmm_sink_sets Message-ID: <5fc18fb85f1c9_86c3fc6aa253af470176d@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/opt_cmm_sink_sets at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/opt_cmm_sink_sets 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 Fri Nov 27 23:59:55 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Fri, 27 Nov 2020 18:59:55 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: rts: Allocate MBlocks with MAP_TOP_DOWN on Windows Message-ID: <5fc192fb2ed41_86cfd752bc70886c@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - f04840cf by David Eichmann at 2020-11-27T09:07:36-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 50e8ca6f by Andreas Klebinger at 2020-11-27T18:59:42-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - 24 changed files: - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Runtime/Interpreter.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Heap.c - rts/PrimOps.cmm - rts/win32/OSMem.c Changes: ===================================== compiler/GHC/ByteCode/Types.hs ===================================== @@ -37,7 +37,7 @@ import Data.ByteString (ByteString) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.Maybe (catMaybes) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS -- ----------------------------------------------------------------------------- @@ -72,7 +72,7 @@ type ItblEnv = NameEnv (Name, ItblPtr) -- We need the Name in the range so we know which -- elements to filter out when unloading a module -newtype ItblPtr = ItblPtr (RemotePtr StgInfoTable) +newtype ItblPtr = ItblPtr (RemotePtr Heap.StgInfoTable) deriving (Show, NFData) data UnlinkedBCO ===================================== compiler/GHC/Cmm/Sink.hs ===================================== @@ -449,6 +449,7 @@ tryToInline platform live node assigs = go usages node emptyLRegSet assigs || l `elemLRegSet` skipped || not (okToInline platform rhs node) + -- How often is l used in the current node. l_usages = lookupUFM usages l l_live = l `elemRegSet` live @@ -554,10 +555,16 @@ addUsage m r = addToUFM_C (+) m r 1 regsUsedIn :: LRegSet -> CmmExpr -> Bool regsUsedIn ls _ | nullLRegSet ls = False -regsUsedIn ls e = wrapRecExpf f e False - where f (CmmReg (CmmLocal l)) _ | l `elemLRegSet` ls = True - f (CmmRegOff (CmmLocal l) _) _ | l `elemLRegSet` ls = True - f _ z = z +regsUsedIn ls e = go ls e False + where use :: LRegSet -> CmmExpr -> Bool -> Bool + use ls (CmmReg (CmmLocal l)) _ | l `elemLRegSet` ls = True + use ls (CmmRegOff (CmmLocal l) _) _ | l `elemLRegSet` ls = True + use _ls _ z = z + + go :: LRegSet -> CmmExpr -> Bool -> Bool + go ls (CmmMachOp _ es) z = foldr (go ls) z es + go ls (CmmLoad addr _) z = go ls addr z + go ls e z = use ls e z -- we don't inline into CmmUnsafeForeignCall if the expression refers -- to global registers. This is a HACK to avoid global registers ===================================== compiler/GHC/Runtime/Interpreter.hs ===================================== @@ -103,7 +103,7 @@ import qualified Data.ByteString.Lazy as LB import Data.Array ((!)) import Data.IORef import Foreign hiding (void) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS (CostCentre,CostCentreStack) import System.Exit import GHC.IO.Handle.Types (Handle) @@ -395,7 +395,7 @@ getBreakpointVar hsc_env ref ix = mb <- iservCmd hsc_env (GetBreakpointVar apStack ix) mapM (mkFinalizedHValue hsc_env) mb -getClosure :: HscEnv -> ForeignHValue -> IO (GenClosure ForeignHValue) +getClosure :: HscEnv -> ForeignHValue -> IO (Heap.GenClosure ForeignHValue) getClosure hsc_env ref = withForeignRef ref $ \hval -> do mb <- iservCmd hsc_env (GetClosure hval) ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -27,6 +27,9 @@ module GHC.Exts.Heap ( , GenClosure(..) , ClosureType(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , HasHeapRep(getClosureData) , getClosureDataFromHeapRep , getClosureDataFromHeapRepPrim @@ -40,6 +43,12 @@ module GHC.Exts.Heap ( , peekItbl , pokeItbl + -- * Cost Centre (profiling) types + , StgTSOProfInfo(..) + , IndexTable(..) + , CostCentre(..) + , CostCentreStack(..) + -- * Closure inspection , getBoxedClosureData , allClosures @@ -54,12 +63,14 @@ import Prelude import GHC.Exts.Heap.Closures import GHC.Exts.Heap.ClosureTypes import GHC.Exts.Heap.Constants +import GHC.Exts.Heap.ProfInfo.Types #if defined(PROFILING) import GHC.Exts.Heap.InfoTableProf #else import GHC.Exts.Heap.InfoTable #endif import GHC.Exts.Heap.Utils +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures import Control.Monad import Data.Bits @@ -330,6 +341,45 @@ getClosureDataFromHeapRepPrim getConDesc itbl heapRep pts = do , finalizer = pts !! 3 , link = pts !! 4 } + TSO | [ u_lnk, u_gbl_lnk, tso_stack, u_trec, u_blk_ex, u_bq] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekTSOFields ptr + pure $ TSOClosure + { info = itbl + , link = u_lnk + , global_link = u_gbl_lnk + , tsoStack = tso_stack + , trec = u_trec + , blocked_exceptions = u_blk_ex + , bq = u_bq + , what_next = FFIClosures.tso_what_next fields + , why_blocked = FFIClosures.tso_why_blocked fields + , flags = FFIClosures.tso_flags fields + , threadId = FFIClosures.tso_threadId fields + , saved_errno = FFIClosures.tso_saved_errno fields + , tso_dirty = FFIClosures.tso_dirty fields + , alloc_limit = FFIClosures.tso_alloc_limit fields + , tot_stack_size = FFIClosures.tso_tot_stack_size fields + , prof = FFIClosures.tso_prof fields + }) + | otherwise + -> fail $ "Expected 6 ptr arguments to TSO, found " + ++ show (length pts) + STACK + | [] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekStackFields ptr + pure $ StackClosure + { info = itbl + , stack_size = FFIClosures.stack_size fields + , stack_dirty = FFIClosures.stack_dirty fields +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking = FFIClosures.stack_marking fields +#endif + }) + | otherwise + -> fail $ "Expected 0 ptr argument to STACK, found " + ++ show (length pts) _ -> pure $ UnsupportedClosure itbl ===================================== libraries/ghc-heap/GHC/Exts/Heap/Closures.hs ===================================== @@ -12,6 +12,9 @@ module GHC.Exts.Heap.Closures ( Closure , GenClosure(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , allClosures #if __GLASGOW_HASKELL__ >= 809 -- The closureSize# primop is unsupported on earlier GHC releases but we @@ -40,6 +43,8 @@ import GHC.Exts.Heap.InfoTable import GHC.Exts.Heap.InfoTableProf () #endif +import GHC.Exts.Heap.ProfInfo.Types + import Data.Bits import Data.Int import Data.Word @@ -100,11 +105,11 @@ type Closure = GenClosure Box -- | This is the representation of a Haskell value on the heap. It reflects -- -- --- The data type is parametrized by the type to store references in. Usually --- this is a 'Box' with the type synonym 'Closure'. +-- The data type is parametrized by `b`: the type to store references in. +-- Usually this is a 'Box' with the type synonym 'Closure'. -- --- All Heap objects have the same basic layout. A header containing a pointer --- to the info table and a payload with various fields. The @info@ field below +-- All Heap objects have the same basic layout. A header containing a pointer to +-- the info table and a payload with various fields. The @info@ field below -- always refers to the info table pointed to by the header. The remaining -- fields are the payload. -- @@ -268,6 +273,39 @@ data GenClosure b , link :: !b -- ^ next weak pointer for the capability, can be NULL. } + -- | Representation of StgTSO: A Thread State Object. The values for + -- 'what_next', 'why_blocked' and 'flags' are defined in @Constants.h at . + | TSOClosure + { info :: !StgInfoTable + -- pointers + , link :: !b + , global_link :: !b + , tsoStack :: !b -- ^ stackobj from StgTSO + , trec :: !b + , blocked_exceptions :: !b + , bq :: !b + -- values + , what_next :: !WhatNext + , why_blocked :: !WhyBlocked + , flags :: ![TsoFlags] + , threadId :: !Word64 + , saved_errno :: !Word32 + , tso_dirty :: !Word32 -- ^ non-zero => dirty + , alloc_limit :: !Int64 + , tot_stack_size :: !Word32 + , prof :: !(Maybe StgTSOProfInfo) + } + + -- | Representation of StgStack: The 'tsoStack ' of a 'TSOClosure'. + | StackClosure + { info :: !StgInfoTable + , stack_size :: !Word32 -- ^ stack size in *words* + , stack_dirty :: !Word8 -- ^ non-zero => dirty +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking :: !Word8 +#endif + } + ------------------------------------------------------------ -- Unboxed unlifted closures @@ -332,6 +370,43 @@ data PrimType | PDouble deriving (Eq, Show, Generic) +data WhatNext + = ThreadRunGHC + | ThreadInterpret + | ThreadKilled + | ThreadComplete + | WhatNextUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data WhyBlocked + = NotBlocked + | BlockedOnMVar + | BlockedOnMVarRead + | BlockedOnBlackHole + | BlockedOnRead + | BlockedOnWrite + | BlockedOnDelay + | BlockedOnSTM + | BlockedOnDoProc + | BlockedOnCCall + | BlockedOnCCall_Interruptible + | BlockedOnMsgThrowTo + | ThreadMigrating + | BlockedOnIOCompletion + | WhyBlockedUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data TsoFlags + = TsoLocked + | TsoBlockx + | TsoInterruptible + | TsoStoppedOnBreakpoint + | TsoMarked + | TsoSqueezed + | TsoAllocLimit + | TsoFlagsUnknownValue Word32 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + -- | For generic code, this function returns all referenced closures. allClosures :: GenClosure b -> [b] allClosures (ConstrClosure {..}) = ptrArgs ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs ===================================== @@ -0,0 +1,47 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.FFIClosures (module Reexport) where + +-- NOTE [hsc and CPP workaround] +-- +-- # Problem +-- +-- Often, .hsc files are used to get the correct offsets of C struct fields. +-- Those structs may be affected by CPP directives e.g. profiled vs not profiled +-- closure headers is affected by the PROFILED cpp define. Since we are building +-- multiple variants of the RTS, we must support all possible offsets e.g. by +-- running hsc2hs with cpp defines corresponding to each RTS flavour. The +-- problem is that GHC's build system runs hsc2hs *only once* per .hsc file +-- without properly setting cpp defines. This results in the same (probably +-- incorrect) offsets into our C structs. +-- +-- +-- # Workaround +-- +-- To work around this issue, we create multiple .hsc files each manually +-- defining thir cpp defines (see e.g. FFIClosures_ProfilingDisabled.hsc and +-- FFIClosures_ProfilingEnabled.hsc). Then we rely on cpp defines working +-- correctly in .hs files and use CPP to switch on which .hsc module to +-- re-export (see below). In each case we import the desired .hsc module as +-- `Reexport` and we import `()` (i.e. nothing) from all other .hsc variants +-- just so that the build system sees all .hsc file as dependencies. +-- +-- +-- # Future Work +-- +-- * Duplication of the code in the .hsc files could be reduced simply by +-- placing the code in a single .hsc.in file and `#include`ing it from each +-- .hsc file. The .hsc files would only be responsible for setting the correct +-- cpp defines. This currently doesn't work as hadrian doesn't know to copy +-- the .hsc.in file to the build directory. +-- * The correct solution would be for the build system to run `hsc2hs` with the +-- correct cpp defines once per RTS flavour. +-- + +#if defined(PROFILING) +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled () +#else +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,131 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingDisabled where + +-- See [hsc and CPP workaround] + +#undef PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } + ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,130 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingEnabled where + +-- See [hsc and CPP workaround] + +#define PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo (module Reexport) where + +-- See [hsc and CPP workaround] + +#if defined(PROFILING) +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled () +#else +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,12 @@ +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled( + peekStgTSOProfInfo +) where + +import Prelude +import Foreign +import GHC.Exts.Heap.ProfInfo.Types + +-- | This implementation is used when PROFILING is undefined. +-- It always returns 'Nothing', because there is no profiling info available. +peekStgTSOProfInfo :: Ptr tsoPtr -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,165 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled( + peekStgTSOProfInfo +) where + +#if __GLASGOW_HASKELL__ >= 811 + +-- See [hsc and CPP workaround] + +#define PROFILING + +#include "Rts.h" +#undef BLOCK_SIZE +#undef MBLOCK_SIZE +#undef BLOCKS_PER_MBLOCK +#include "DerivedConstants.h" + +import Data.IntSet (IntSet) +import qualified Data.IntSet as IntSet +import Data.IntMap.Strict (IntMap) +import qualified Data.IntMap.Strict as IntMap +import Data.IORef (IORef, newIORef, readIORef, writeIORef) +import Foreign +import Foreign.C.String +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.Types +import Prelude + +-- Use Int based containers for pointers (addresses) for better performance. +-- These will be queried a lot! +type AddressSet = IntSet +type AddressMap = IntMap + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo tsoPtr = do + cccs_ptr <- peekByteOff tsoPtr cccsOffset + costCenterCacheRef <- newIORef IntMap.empty + cccs' <- peekCostCentreStack IntSet.empty costCenterCacheRef cccs_ptr + + return $ Just StgTSOProfInfo { + cccs = cccs' + } + +cccsOffset :: Int +cccsOffset = (#const OFFSET_StgTSO_cccs) + (#size StgHeader) + +peekCostCentreStack + :: AddressSet + -> IORef (AddressMap CostCentre) + -> Ptr costCentreStack + -> IO (Maybe CostCentreStack) +peekCostCentreStack _ _ ptr | ptr == nullPtr = return Nothing +peekCostCentreStack loopBreakers _ ptr | IntSet.member (ptrToInt ptr) loopBreakers = return Nothing +peekCostCentreStack loopBreakers costCenterCacheRef ptr = do + ccs_ccsID' <- (#peek struct CostCentreStack_, ccsID) ptr + ccs_cc_ptr <- (#peek struct CostCentreStack_, cc) ptr + ccs_cc' <- peekCostCentre costCenterCacheRef ccs_cc_ptr + ccs_prevStack_ptr <- (#peek struct CostCentreStack_, prevStack) ptr + let loopBreakers' = (IntSet.insert ptrAsInt loopBreakers) + ccs_prevStack' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_prevStack_ptr + ccs_indexTable_ptr <- (#peek struct CostCentreStack_, indexTable) ptr + ccs_indexTable' <- peekIndexTable loopBreakers' costCenterCacheRef ccs_indexTable_ptr + ccs_root_ptr <- (#peek struct CostCentreStack_, root) ptr + ccs_root' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_root_ptr + ccs_depth' <- (#peek struct CostCentreStack_, depth) ptr + ccs_scc_count' <- (#peek struct CostCentreStack_, scc_count) ptr + ccs_selected' <- (#peek struct CostCentreStack_, selected) ptr + ccs_time_ticks' <- (#peek struct CostCentreStack_, time_ticks) ptr + ccs_mem_alloc' <- (#peek struct CostCentreStack_, mem_alloc) ptr + ccs_inherited_alloc' <- (#peek struct CostCentreStack_, inherited_alloc) ptr + ccs_inherited_ticks' <- (#peek struct CostCentreStack_, inherited_ticks) ptr + + return $ Just CostCentreStack { + ccs_ccsID = ccs_ccsID', + ccs_cc = ccs_cc', + ccs_prevStack = ccs_prevStack', + ccs_indexTable = ccs_indexTable', + ccs_root = ccs_root', + ccs_depth = ccs_depth', + ccs_scc_count = ccs_scc_count', + ccs_selected = ccs_selected', + ccs_time_ticks = ccs_time_ticks', + ccs_mem_alloc = ccs_mem_alloc', + ccs_inherited_alloc = ccs_inherited_alloc', + ccs_inherited_ticks = ccs_inherited_ticks' + } + where + ptrAsInt = ptrToInt ptr + +peekCostCentre :: IORef (AddressMap CostCentre) -> Ptr costCentre -> IO CostCentre +peekCostCentre costCenterCacheRef ptr = do + costCenterCache <- readIORef costCenterCacheRef + case IntMap.lookup ptrAsInt costCenterCache of + (Just a) -> return a + Nothing -> do + cc_ccID' <- (#peek struct CostCentre_, ccID) ptr + cc_label_ptr <- (#peek struct CostCentre_, label) ptr + cc_label' <- peekCString cc_label_ptr + cc_module_ptr <- (#peek struct CostCentre_, module) ptr + cc_module' <- peekCString cc_module_ptr + cc_srcloc_ptr <- (#peek struct CostCentre_, srcloc) ptr + cc_srcloc' <- do + if cc_srcloc_ptr == nullPtr then + return Nothing + else + fmap Just (peekCString cc_srcloc_ptr) + cc_mem_alloc' <- (#peek struct CostCentre_, mem_alloc) ptr + cc_time_ticks' <- (#peek struct CostCentre_, time_ticks) ptr + cc_is_caf' <- (#peek struct CostCentre_, is_caf) ptr + cc_link_ptr <- (#peek struct CostCentre_, link) ptr + cc_link' <- if cc_link_ptr == nullPtr then + return Nothing + else + fmap Just (peekCostCentre costCenterCacheRef cc_link_ptr) + + let result = CostCentre { + cc_ccID = cc_ccID', + cc_label = cc_label', + cc_module = cc_module', + cc_srcloc = cc_srcloc', + cc_mem_alloc = cc_mem_alloc', + cc_time_ticks = cc_time_ticks', + cc_is_caf = cc_is_caf', + cc_link = cc_link' + } + + writeIORef costCenterCacheRef (IntMap.insert ptrAsInt result costCenterCache) + + return result + where + ptrAsInt = ptrToInt ptr + +peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable) +peekIndexTable _ _ ptr | ptr == nullPtr = return Nothing +peekIndexTable loopBreakers costCenterCacheRef ptr = do + it_cc_ptr <- (#peek struct IndexTable_, cc) ptr + it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr + it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr + it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr + it_next_ptr <- (#peek struct IndexTable_, next) ptr + it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr + it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr + + return $ Just IndexTable { + it_cc = it_cc', + it_ccs = it_ccs', + it_next = it_next', + it_back_edge = it_back_edge' + } + +-- | casts a @Ptr@ to an @Int@ +ptrToInt :: Ptr a -> Int +ptrToInt (Ptr a##) = I## (addr2Int## a##) + +#else +import Prelude +import Foreign + +import GHC.Exts.Heap.ProfInfo.Types + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs ===================================== @@ -0,0 +1,56 @@ +{-# LANGUAGE DeriveGeneric #-} + +module GHC.Exts.Heap.ProfInfo.Types where + +import Prelude +import Data.Word +import GHC.Generics + +-- | This is a somewhat faithful representation of StgTSOProfInfo. See +-- +-- for more details on this data structure. +data StgTSOProfInfo = StgTSOProfInfo { + cccs :: Maybe CostCentreStack +} deriving (Show, Generic) + +-- | This is a somewhat faithful representation of CostCentreStack. See +-- +-- for more details on this data structure. +data CostCentreStack = CostCentreStack { + ccs_ccsID :: Int, + ccs_cc :: CostCentre, + ccs_prevStack :: Maybe CostCentreStack, + ccs_indexTable :: Maybe IndexTable, + ccs_root :: Maybe CostCentreStack, + ccs_depth :: Word, + ccs_scc_count :: Word64, + ccs_selected :: Word, + ccs_time_ticks :: Word, + ccs_mem_alloc :: Word64, + ccs_inherited_alloc :: Word64, + ccs_inherited_ticks :: Word +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of CostCentre. See +-- +-- for more details on this data structure. +data CostCentre = CostCentre { + cc_ccID :: Int, + cc_label :: String, + cc_module :: String, + cc_srcloc :: Maybe String, + cc_mem_alloc :: Word64, + cc_time_ticks :: Word, + cc_is_caf :: Bool, + cc_link :: Maybe CostCentre +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of IndexTable. See +-- +-- for more details on this data structure. +data IndexTable = IndexTable { + it_cc :: CostCentre, + it_ccs :: Maybe CostCentreStack, + it_next :: Maybe IndexTable, + it_back_edge :: Bool +} deriving (Show, Generic, Eq) ===================================== libraries/ghc-heap/ghc-heap.cabal.in ===================================== @@ -25,6 +25,7 @@ library build-depends: base >= 4.9.0 && < 5.0 , ghc-prim > 0.2 && < 0.9 , rts == 1.0.* + , containers >= 0.6.2.1 && < 0.7 ghc-options: -Wall cmm-sources: cbits/HeapPrim.cmm @@ -39,3 +40,10 @@ library GHC.Exts.Heap.InfoTable.Types GHC.Exts.Heap.InfoTableProf GHC.Exts.Heap.Utils + GHC.Exts.Heap.FFIClosures + GHC.Exts.Heap.FFIClosures_ProfilingDisabled + GHC.Exts.Heap.FFIClosures_ProfilingEnabled + GHC.Exts.Heap.ProfInfo.Types + GHC.Exts.Heap.ProfInfo.PeekProfInfo + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled ===================================== libraries/ghc-heap/tests/TestUtils.hs ===================================== @@ -0,0 +1,7 @@ +{-# LANGUAGE MagicHash #-} +module TestUtils where + +assertEqual :: (Show a, Eq a) => a -> a -> IO () +assertEqual a b + | a /= b = error (show a ++ " /= " ++ show b) + | otherwise = return () ===================================== libraries/ghc-heap/tests/all.T ===================================== @@ -36,3 +36,18 @@ test('closure_size_noopt', ], compile_and_run, ['']) +test('tso_and_stack_closures', + [extra_files(['create_tso.c','create_tso.h','TestUtils.hs']), + only_ways(['profthreaded']), + ignore_stdout, + ignore_stderr + ], + multi_compile_and_run, ['tso_and_stack_closures', [('create_tso.c','')], '']) + +test('parse_tso_flags', + [extra_files(['TestUtils.hs']), + only_ways(['normal']), + ignore_stdout, + ignore_stderr + ], + compile_and_run, ['']) ===================================== libraries/ghc-heap/tests/create_tso.c ===================================== @@ -0,0 +1,82 @@ +#include "Rts.h" +#include "RtsAPI.h" + +// Assumes the rts is paused +void unpack_closure + ( StgClosure * inClosure + , const StgInfoTable ** outInfoTablePtr + , int * outHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outHeapRep // Array of words + , int * outPointersSize // Size of outPointers (in words) + , StgClosure *** outPointers // Array of all pointers of the TSO + ) +{ + *outInfoTablePtr = get_itbl(inClosure); + + // Copy TSO pointers. + StgWord closureSizeW = heap_view_closureSize(inClosure); + int closureSizeB = sizeof(StgWord) * closureSizeW; + StgClosure ** pointers = malloc(closureSizeB); + *outPointersSize = collect_pointers(inClosure, closureSizeW, pointers); + *outPointers = pointers; + + // Copy the heap rep. + StgWord * heapRep = malloc(closureSizeB); + for (int i = 0; i < closureSizeW; i++) + { + heapRep[i] = ((StgWord*)inClosure)[i]; + } + + *outHeapRepSize = closureSizeB; + *outHeapRep = heapRep; +} + +// Must be called from a safe FFI call. +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ) +{ + // Pause RTS + PauseToken * token = rts_pause(); + Capability * cap = pauseTokenCapability(token); + + // Create TSO/Stack + HaskellObj trueClosure = rts_mkBool(cap, 1); + *outTso = createGenThread(cap, 500U, trueClosure); + + // Unpack TSO + unpack_closure( + (StgClosure*)(*outTso), + outTsoInfoTablePtr, + outTsoHeapRepSize, + outTsoHeapRep, + outTsoPointersSize, + outTsoPointers); + + // Unpack STACK + StgClosure * outStackAsClosure = (*outTsoPointers)[2]; + *outStack = (StgTSO *)outStackAsClosure; + unpack_closure( + outStackAsClosure, + outStackInfoTablePtr, + outStackHeapRepSize, + outStackHeapRep, + outStackPointersSize, + outStackPointers); + + // Resume RTS + rts_resume(token); +} ===================================== libraries/ghc-heap/tests/create_tso.h ===================================== @@ -0,0 +1,19 @@ +#include "Rts.h" +#include "RtsAPI.h" + +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ); ===================================== libraries/ghc-heap/tests/parse_tso_flags.hs ===================================== @@ -0,0 +1,17 @@ +import GHC.Exts.Heap.Closures +import GHC.Exts.Heap.FFIClosures +import TestUtils + +main :: IO() +main = do + assertEqual (parseTsoFlags 0) [] + assertEqual (parseTsoFlags 1) [TsoFlagsUnknownValue 1] + assertEqual (parseTsoFlags 2) [TsoLocked] + assertEqual (parseTsoFlags 4) [TsoBlockx] + assertEqual (parseTsoFlags 8) [TsoInterruptible] + assertEqual (parseTsoFlags 16) [TsoStoppedOnBreakpoint] + assertEqual (parseTsoFlags 64) [TsoMarked] + assertEqual (parseTsoFlags 128) [TsoSqueezed] + assertEqual (parseTsoFlags 256) [TsoAllocLimit] + + assertEqual (parseTsoFlags 6) [TsoLocked, TsoBlockx] ===================================== libraries/ghc-heap/tests/tso_and_stack_closures.hs ===================================== @@ -0,0 +1,167 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} + +import Control.Monad (forM_, unless) +import Data.List (find) +import Data.Word +import Foreign +import Foreign.C.Types +import GHC.IO ( IO(..) ) +import GHC.Exts +import GHC.Exts.Heap +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures +import GHC.Word + +import TestUtils + +main :: IO () +main = do + (tso, stack) <- {-# SCC "MyCostCentre" #-} createAndUnpackTSOAndSTACKClosure + assertEqual (getClosureType tso) TSO + assertEqual (what_next tso) ThreadRunGHC + assertEqual (why_blocked tso) NotBlocked + assertEqual (saved_errno tso) 0 + forM_ (flags tso) $ \flag -> case flag of + TsoFlagsUnknownValue _ -> error $ "Unknown flag: " ++ show flag + _ | flag `elem` + [ TsoLocked + , TsoBlockx + , TsoStoppedOnBreakpoint + , TsoSqueezed + ] -> error $ "Unexpected flag: " ++ show flag + _ -> return () + + assertEqual (getClosureType stack) STACK + +#if defined(PROFILING) + let costCentre = ccs_cc <$> (cccs =<< prof tso) + case costCentre of + Nothing -> error $ "No CostCentre found in TSO: " ++ show tso + Just _ -> case findMyCostCentre (linkedCostCentres costCentre) of + Just myCostCentre -> do + assertEqual (cc_label myCostCentre) "MyCostCentre" + assertEqual (cc_module myCostCentre) "Main" + assertEqual (cc_srcloc myCostCentre) (Just "tso_and_stack_closures.hs:23:48-80") + assertEqual (cc_is_caf myCostCentre) False + Nothing -> error $ "MyCostCentre not found in:\n" ++ unlines (cc_label <$> linkedCostCentres costCentre) +#endif + +linkedCostCentres :: Maybe CostCentre -> [CostCentre] +linkedCostCentres Nothing = [] +linkedCostCentres (Just cc) = cc : linkedCostCentres (cc_link cc) + +findMyCostCentre:: [CostCentre] -> Maybe CostCentre +findMyCostCentre ccs = find (\cc -> cc_label cc == "MyCostCentre") ccs + +getClosureType :: GenClosure b -> ClosureType +getClosureType = tipe . info + +type StgTso = Any +type StgStack = Any +data MBA a = MBA (MutableByteArray# a) +data BA = BA ByteArray# + +foreign import ccall safe "create_tso.h create_and_unpack_tso_and_stack" + c_create_and_unpack_tso_and_stack + :: Ptr (Ptr StgTso) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> Ptr (Ptr StgStack) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> IO () + +createAndUnpackTSOAndSTACKClosure + :: IO ( GenClosure (Ptr Any) + , GenClosure (Ptr Any) + ) +createAndUnpackTSOAndSTACKClosure = do + + alloca $ \ptrPtrTso -> do + alloca $ \ptrPtrTsoInfoTable -> do + alloca $ \ptrTsoHeapRepSize -> do + alloca $ \ptrPtrTsoHeapRep -> do + alloca $ \ptrTsoPointersSize -> do + alloca $ \ptrPtrPtrTsoPointers -> do + + alloca $ \ptrPtrStack -> do + alloca $ \ptrPtrStackInfoTable -> do + alloca $ \ptrStackHeapRepSize -> do + alloca $ \ptrPtrStackHeapRep -> do + alloca $ \ptrStackPointersSize -> do + alloca $ \ptrPtrPtrStackPointers -> do + + c_create_and_unpack_tso_and_stack + + ptrPtrTso + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + ptrPtrStack + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + let fromHeapRep + ptrPtrClosureInfoTable + ptrClosureHeapRepSize + ptrPtrClosureHeapRep + ptrClosurePointersSize + ptrPtrPtrClosurePointers = do + ptrInfoTable :: Ptr StgInfoTable <- peek ptrPtrClosureInfoTable + + heapRepSize :: Int <- fromIntegral <$> peek ptrClosureHeapRepSize + let I# heapRepSize# = heapRepSize + ptrHeapRep :: Ptr Word8 <- peek ptrPtrClosureHeapRep + MBA mutHeapRepBA <- IO $ \s -> let + (# s', mba# #) = newByteArray# heapRepSize# s + in (# s', MBA mba# #) + forM_ [0..heapRepSize-1] $ \i@(I# i#) -> do + W8# w <- peekElemOff ptrHeapRep i + IO (\s -> (# writeWord8Array# mutHeapRepBA i# (extendWord8# w) s, () #)) + BA heapRep <- IO $ \s -> let + (# s', ba# #) = unsafeFreezeByteArray# mutHeapRepBA s + in (# s', BA ba# #) + + pointersSize :: Int <- fromIntegral <$> peek ptrClosurePointersSize + ptrPtrPointers :: Ptr (Ptr Any) <- peek ptrPtrPtrClosurePointers + ptrPtrPointers :: [Ptr Any] <- sequence + [ peekElemOff ptrPtrPointers i + | i <- [0..pointersSize-1] + ] + + getClosureDataFromHeapRep + heapRep + ptrInfoTable + ptrPtrPointers + + tso <- fromHeapRep + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + stack <- fromHeapRep + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + return (tso, stack) ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables, - GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards #-} + GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards, + CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-} -- | @@ -29,7 +30,7 @@ import GHCi.TH.Binary () -- For Binary instances import GHCi.BreakArray import GHC.LanguageExtensions -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.ForeignSrcLang import GHC.Fingerprint import Control.Concurrent @@ -110,7 +111,7 @@ data Message a where -> Int -- constr tag -> Int -- pointer tag -> ByteString -- constructor desccription - -> Message (RemotePtr StgInfoTable) + -> Message (RemotePtr Heap.StgInfoTable) -- | Evaluate a statement EvalStmt @@ -211,7 +212,7 @@ data Message a where -- type reconstruction. GetClosure :: HValueRef - -> Message (GenClosure HValueRef) + -> Message (Heap.GenClosure HValueRef) -- | Evaluate something. This is used to support :force in GHCi. Seq @@ -449,10 +450,20 @@ instance Binary (FunPtr a) where get = castPtrToFunPtr <$> get -- Binary instances to support the GetClosure message -instance Binary StgInfoTable -instance Binary ClosureType -instance Binary PrimType -instance Binary a => Binary (GenClosure a) +#if MIN_VERSION_ghc_heap(8,11,0) +instance Binary Heap.StgTSOProfInfo +instance Binary Heap.CostCentreStack +instance Binary Heap.CostCentre +instance Binary Heap.IndexTable +instance Binary Heap.WhatNext +instance Binary Heap.WhyBlocked +instance Binary Heap.TsoFlags +#endif + +instance Binary Heap.StgInfoTable +instance Binary Heap.ClosureType +instance Binary Heap.PrimType +instance Binary a => Binary (Heap.GenClosure a) data Msg = forall a . (Binary a, Show a) => Msg (Message a) ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -32,7 +32,7 @@ import Data.Binary.Get import Data.ByteString (ByteString) import qualified Data.ByteString.Unsafe as B import GHC.Exts -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack import Foreign hiding (void) import Foreign.C @@ -93,8 +93,8 @@ run m = case m of toRemotePtr <$> mkConInfoTable tc ptrs nptrs tag ptrtag desc StartTH -> startTH GetClosure ref -> do - clos <- getClosureData =<< localRef ref - mapM (\(Box x) -> mkRemoteRef (HValue x)) clos + clos <- Heap.getClosureData =<< localRef ref + mapM (\(Heap.Box x) -> mkRemoteRef (HValue x)) clos Seq ref -> doSeq ref ResumeSeq ref -> resumeSeq ref _other -> error "GHCi.Run.run" ===================================== rts/Heap.c ===================================== @@ -203,7 +203,26 @@ StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[siz ptrs[nptrs++] = (StgClosure *)((StgMVar *)closure)->tail; ptrs[nptrs++] = ((StgMVar *)closure)->value; break; + case TSO: + ASSERT((StgClosure *)((StgTSO *)closure)->_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->_link; + ASSERT((StgClosure *)((StgTSO *)closure)->global_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->global_link; + + ASSERT((StgClosure *)((StgTSO *)closure)->stackobj != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->stackobj; + + ASSERT((StgClosure *)((StgTSO *)closure)->trec != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->trec; + + ASSERT((StgClosure *)((StgTSO *)closure)->blocked_exceptions != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->blocked_exceptions; + + ASSERT((StgClosure *)((StgTSO *)closure)->bq != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->bq; + + break; case WEAK: ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->cfinalizers; ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->key; ===================================== rts/PrimOps.cmm ===================================== @@ -2371,11 +2371,11 @@ stg_unpackClosurezh ( P_ closure ) clos = UNTAG(closure); W_ len; - // The array returned is the raw data for the entire closure. + // The array returned, dat_arr, is the raw data for the entire closure. // The length is variable based upon the closure type, ptrs, and non-ptrs (len) = foreign "C" heap_view_closureSize(clos "ptr"); - W_ ptrs_arr_sz, ptrs_arr_cards, dat_arr_sz; + W_ dat_arr_sz; dat_arr_sz = SIZEOF_StgArrBytes + WDS(len); ("ptr" dat_arr) = ccall allocateMightFail(MyCapability() "ptr", BYTES_TO_WDS(dat_arr_sz)); @@ -2396,7 +2396,7 @@ for: W_ ptrArray; - // Follow the pointers + // Collect pointers. ("ptr" ptrArray) = foreign "C" heap_view_closurePtrs(MyCapability() "ptr", clos "ptr"); return (info, dat_arr, ptrArray); ===================================== rts/win32/OSMem.c ===================================== @@ -50,8 +50,11 @@ allocNew(uint32_t n) { alloc_rec* rec; rec = (alloc_rec*)stgMallocBytes(sizeof(alloc_rec),"getMBlocks: allocNew"); rec->size = ((W_)n+1)*MBLOCK_SIZE; + // N.B. We use MEM_TOP_DOWN here to ensure that we leave the bottom of the + // address space available for the linker and libraries, which in general + // want to live in low memory. See #18991. rec->base = - VirtualAlloc(NULL, rec->size, MEM_RESERVE, PAGE_READWRITE); + VirtualAlloc(NULL, rec->size, MEM_RESERVE | MEM_TOP_DOWN, PAGE_READWRITE); if(rec->base==0) { stgFree((void*)rec); rec=0; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cec7848bcb28623daceeb2ee5caa32f1d911710c...50e8ca6f04d2ad1d71867022df2a1c6d1013bd65 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cec7848bcb28623daceeb2ee5caa32f1d911710c...50e8ca6f04d2ad1d71867022df2a1c6d1013bd65 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 Sat Nov 28 13:15:41 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sat, 28 Nov 2020 08:15:41 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18021 Message-ID: <5fc24d7d8c821_86cfd752bc729638@gitlab.mail> Ryan Scott pushed new branch wip/T18021 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18021 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 Sat Nov 28 13:15:42 2020 From: gitlab at gitlab.haskell.org (Shayne Fletcher) Date: Sat, 28 Nov 2020 08:15:42 -0500 Subject: [Git][ghc/ghc][wip/T18599] Record dot syntax Message-ID: <5fc24d7e12625_86c113a5b2c7298e6@gitlab.mail> Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC Commits: f5468d60 by Shayne Fletcher at 2020-11-28T08:15:23-05:00 Record dot syntax - - - - - 30 changed files: - compiler/GHC/Driver/Session.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Types/Origin.hs - + docs/users_guide/exts/record_dot_syntax.rst - docs/users_guide/exts/records.rst - libraries/ghc-boot-th/GHC/LanguageExtensions/Type.hs - testsuite/tests/driver/T4437.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail0.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail1.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail2.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail3.stderr - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.hs - + testsuite/tests/parser/should_fail/RecordDotSyntaxFail4.stderr - testsuite/tests/parser/should_fail/all.T - + testsuite/tests/parser/should_run/RecordDotSyntax.hs - + testsuite/tests/parser/should_run/RecordDotSyntax.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5468d609a84fdd3a33487190e2d9b13a23752b4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5468d609a84fdd3a33487190e2d9b13a23752b4 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 Sat Nov 28 14:20:28 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 09:20:28 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 9 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc25cac1b031_86c3fc6a6aa1b24746271@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 64ee505e by Sylvain Henry at 2020-11-28T09:20:14-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 036ae03d by Sylvain Henry at 2020-11-28T09:20:14-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - 525f4815 by Ben Gamari at 2020-11-28T09:20:14-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - d5b30e5f by Ben Gamari at 2020-11-28T09:20:15-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 6bb70ebb by David Eichmann at 2020-11-28T09:20:16-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 7c733a78 by Andreas Klebinger at 2020-11-28T09:20:16-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - c9fa9802 by John Ericson at 2020-11-28T09:20:16-05:00 Make primop handler indentation more consistent - - - - - 260743b7 by John Ericson at 2020-11-28T09:20:16-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 0395b1b2 by Ben Gamari at 2020-11-28T09:20:17-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Heap.c - rts/PrimOps.cmm The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50e8ca6f04d2ad1d71867022df2a1c6d1013bd65...0395b1b2b4fc9a74c37f0c253a2bdbe5c6090951 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/50e8ca6f04d2ad1d71867022df2a1c6d1013bd65...0395b1b2b4fc9a74c37f0c253a2bdbe5c6090951 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 Sat Nov 28 15:22:08 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 28 Nov 2020 10:22:08 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] Try fixing it Message-ID: <5fc26b20c1331_86c879fa9c75612@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: 34cd1430 by Ben Gamari at 2020-11-28T10:21:58-05:00 Try fixing it - - - - - 1 changed file: - rts/LinkerInternals.h Changes: ===================================== rts/LinkerInternals.h ===================================== @@ -35,6 +35,7 @@ void printLoadedObjects(void); typedef void SymbolAddr; typedef char SymbolName; +typedef struct _ObjectCode ObjectCode; #if defined(OBJFORMAT_ELF) # include "linker/ElfTypes.h" @@ -199,7 +200,7 @@ typedef enum { /* Top-level structure for an object module. One of these is allocated * for each object file in use. */ -typedef struct _ObjectCode { +struct _ObjectCode { OStatus status; pathchar *fileName; int fileSize; /* also mapped image size when using mmap() */ @@ -319,7 +320,7 @@ typedef struct _ObjectCode { /* virtual memory ranges of loaded code */ NativeCodeRange *nc_ranges; -} ObjectCode; +}; #define OC_INFORMATIVE_FILENAME(OC) \ ( (OC)->archiveMemberName ? \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34cd14304c86ccc0d9d97bbca0b81830a7060d0f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34cd14304c86ccc0d9d97bbca0b81830a7060d0f 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 Sat Nov 28 15:23:02 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 28 Nov 2020 10:23:02 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] Try fixing it Message-ID: <5fc26b5654749_86c157aeee0756794@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: 53522ffc by Ben Gamari at 2020-11-28T10:22:57-05:00 Try fixing it - - - - - 2 changed files: - rts/LinkerInternals.h - rts/linker/Elf.c Changes: ===================================== rts/LinkerInternals.h ===================================== @@ -35,6 +35,7 @@ void printLoadedObjects(void); typedef void SymbolAddr; typedef char SymbolName; +typedef struct _ObjectCode ObjectCode; #if defined(OBJFORMAT_ELF) # include "linker/ElfTypes.h" @@ -199,7 +200,7 @@ typedef enum { /* Top-level structure for an object module. One of these is allocated * for each object file in use. */ -typedef struct _ObjectCode { +struct _ObjectCode { OStatus status; pathchar *fileName; int fileSize; /* also mapped image size when using mmap() */ @@ -319,7 +320,7 @@ typedef struct _ObjectCode { /* virtual memory ranges of loaded code */ NativeCodeRange *nc_ranges; -} ObjectCode; +}; #define OC_INFORMATIVE_FILENAME(OC) \ ( (OC)->archiveMemberName ? \ ===================================== rts/linker/Elf.c ===================================== @@ -22,6 +22,7 @@ #include "linker/M32Alloc.h" #include "linker/SymbolExtras.h" #include "ForeignExports.h" +#include "Profiling.h" #include "sm/OSMem.h" #include "GetEnv.h" #include "linker/util.h" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/53522ffc245d8909bd86f0092e6791ce36bf7467 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/53522ffc245d8909bd86f0092e6791ce36bf7467 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 Sat Nov 28 16:54:24 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 11:54:24 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] Cleanup number primop conversion names Message-ID: <5fc280c08e7a2_86c3fc6aabcaaec7602aa@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: 98a3e441 by John Ericson at 2020-11-28T16:53:31+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/binary - libraries/bytestring - libraries/ghci/GHCi/BreakArray.hs - testsuite/tests/array/should_run/arr020.hs - testsuite/tests/cmm/opt/T18141.hs - testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_run/cgrun070.hs - testsuite/tests/codeGen/should_run/cgrun072.hs - testsuite/tests/codeGen/should_run/cgrun075.hs - testsuite/tests/codeGen/should_run/cgrun076.hs - testsuite/tests/codeGen/should_run/compareByteArrays.hs - testsuite/tests/ffi/should_run/PrimFFIInt16.hs - testsuite/tests/ffi/should_run/PrimFFIInt8.hs - testsuite/tests/ffi/should_run/PrimFFIWord16.hs - testsuite/tests/ffi/should_run/PrimFFIWord8.hs - testsuite/tests/ffi/should_run/T16650a.hs - testsuite/tests/ffi/should_run/T16650b.hs - testsuite/tests/ffi/should_run/UnliftedNewtypesByteArrayOffset.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/98a3e44192a957a650bf1eeb9790e53efbdb65a1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/98a3e44192a957a650bf1eeb9790e53efbdb65a1 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 Sat Nov 28 17:41:06 2020 From: gitlab at gitlab.haskell.org (Ryan Scott) Date: Sat, 28 Nov 2020 12:41:06 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T18973 Message-ID: <5fc28bb24d8b8_86c157aeee0764664@gitlab.mail> Ryan Scott pushed new branch wip/T18973 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T18973 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 Sat Nov 28 18:07:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sat, 28 Nov 2020 13:07:38 -0500 Subject: [Git][ghc/ghc][wip/nonmoving-fixes] 18 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc291eacae4e_86ce89fc5c769352@gitlab.mail> Ben Gamari pushed to branch wip/nonmoving-fixes at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 3e75b0db by GHC GitLab CI at 2020-11-28T13:06:16-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - 21c807df by GHC GitLab CI at 2020-11-28T13:06:16-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 6c2faf15 by GHC GitLab CI at 2020-11-28T13:06:16-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 35c22991 by GHC GitLab CI at 2020-11-28T13:06:16-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 134f7599 by GHC GitLab CI at 2020-11-28T13:06:16-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - c488ac73 by GHC GitLab CI at 2020-11-28T13:06:16-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - ca1ef0e7 by GHC GitLab CI at 2020-11-28T13:06:17-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - a3b8375e by Ben Gamari at 2020-11-28T13:06:17-05:00 nonmoving: Add reference to Ueno 2016 - - - - - b416189e by GHC GitLab CI at 2020-11-28T13:07:30-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 30 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs - compiler/GHC/StgToCmm/Utils.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - docs/users_guide/conf.py - ghc/ghc-bin.cabal.in - includes/Rts.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3450ff5b7bd3f5080b8fb1195701a815c72eb4ae...b416189e4004506b89f06f147be37e76f4cd507f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3450ff5b7bd3f5080b8fb1195701a815c72eb4ae...b416189e4004506b89f06f147be37e76f4cd507f 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 Sat Nov 28 20:40:31 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 15:40:31 -0500 Subject: [Git][ghc/ghc][master] 3 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc2b5bf4fbdb_86cfd752bc774761@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 4 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs Changes: ===================================== .gitlab-ci.yml ===================================== @@ -257,6 +257,33 @@ validate-x86_64-linux-deb9-unreg-hadrian: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +validate-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV" + variables: + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*cross-compilation.*/' + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build needs: [lint-linters, lint-submods] ===================================== .gitlab/ci.sh ===================================== @@ -40,9 +40,9 @@ Hadrian build system build_hadrian Build GHC via the Hadrian build system test_hadrian Test GHC via the Hadrian build system - Environment variables affecting both build systems: + CROSS_TARGET Triple of cross-compilation target. VERBOSE Set to non-empty for verbose build output MSYSTEM (Windows-only) Which platform to build form (MINGW64 or MINGW32). @@ -111,11 +111,11 @@ function setup_locale() { function mingw_init() { case "$MSYSTEM" in MINGW32) - triple="i386-unknown-mingw32" + target_triple="i386-unknown-mingw32" boot_triple="i386-unknown-mingw32" # triple of bootstrap GHC ;; MINGW64) - triple="x86_64-unknown-mingw32" + target_triple="x86_64-unknown-mingw32" boot_triple="x86_64-unknown-mingw32" # triple of bootstrap GHC ;; *) @@ -378,8 +378,8 @@ function configure() { end_section "booting" local target_args="" - if [[ -n "$triple" ]]; then - target_args="--target=$triple" + if [[ -n "$target_triple" ]]; then + target_args="--target=$target_triple" fi start_section "configuring" @@ -430,6 +430,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -450,6 +455,11 @@ function build_hadrian() { } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -537,6 +547,11 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in ===================================== hadrian/src/Hadrian/Oracles/Cabal/Rules.hs ===================================== @@ -59,12 +59,20 @@ cabalOracle = do ++ quote (pkgName pkg) ++ " (" ++ show stage ++ ")..." -- Configure the package with the GHC corresponding to the given stage hcPath <- builderPath (Ghc CompileHs stage) + hcPkgPath <- builderPath (GhcPkg undefined stage) + -- N.B. the hcPath parameter of `configure` is broken when given an + -- empty ProgramDb. To work around this we manually construct an + -- appropriate ProgramDb. + -- + -- We also need to pass the path to ghc-pkg, because Cabal cannot + -- guess it (from ghc's path) when it's for a cross-compiler (e.g., + -- _build/stage0/bin/aarch64-linux-gnu-ghc-pkg). let progDb = userSpecifyPath "ghc" hcPath - $ addKnownProgram ghcProgram emptyProgramDb + $ addKnownProgram ghcProgram + $ userSpecifyPath "ghc-pkg" hcPkgPath + $ addKnownProgram ghcPkgProgram + $ emptyProgramDb (compiler, maybePlatform, _pkgdb) <- liftIO $ - -- N.B. the hcPath parameter of `configure` is broken when given an - -- empty ProgramDb. To work around this we manually construct an - -- appropriate ProgramDb. configure silent Nothing Nothing progDb let platform = fromMaybe (error msg) maybePlatform msg = "PackageConfiguration oracle: cannot detect platform" ===================================== hadrian/src/Settings/Builders/GhcPkg.hs ===================================== @@ -8,8 +8,7 @@ ghcPkgBuilderArgs = mconcat verbosity <- expr getVerbosity stage <- getStage pkgDb <- expr $ packageDbPath stage - mconcat [ arg "--global-package-db" - , arg pkgDb + mconcat [ use_db pkgDb , arg "register" , verbosity < Chatty ? arg "-v0" ] @@ -17,8 +16,7 @@ ghcPkgBuilderArgs = mconcat verbosity <- expr getVerbosity stage <- getStage pkgDb <- expr $ packageDbPath stage - mconcat [ arg "--global-package-db" - , arg pkgDb + mconcat [ use_db pkgDb , arg "unregister" , arg "--force" , verbosity < Chatty ? arg "-v0" @@ -29,10 +27,30 @@ ghcPkgBuilderArgs = mconcat config <- expr $ pkgInplaceConfig context stage <- getStage pkgDb <- expr $ packageDbPath stage - mconcat [ notStage0 ? arg "--global-package-db" - , notStage0 ? arg pkgDb + mconcat [ notStage0 ? use_db pkgDb , arg "update" , arg "--force" , verbosity < Chatty ? arg "-v0" , bootPackageDatabaseArgs , arg config ] ] + where + use_db db = mconcat + -- We use ghc-pkg's --global-package-db to manipulate our databases. + -- We can't use --package-db (at least with stage0's ghc-pkg) + -- because units in stage0's global package db would be in scope and + -- ghc-pkg would disallow us the register a second "rts" unit in our + -- database. + -- + -- However ghc-pkg uses the path to the global package db to find + -- the compiler "settings" file... So when it finds our newly + -- generated settings file in _build/stageN, it may crash if it + -- isn't the format it expects (#17601). + -- + -- By chance, ghc-pkg only needs the "settings" file to query the + -- arch/os to generate the path to the user package db, which we + -- don't need. So we disable it below to avoid failures. + [ arg "--no-user-package-db" + , arg "--global-package-db" + , arg db + ] + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1a75aa9be2c133dd1372a08eeb6a92c31688df7...e3fd4226a08ac6cd4abe9f25f764e518de66834a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a1a75aa9be2c133dd1372a08eeb6a92c31688df7...e3fd4226a08ac6cd4abe9f25f764e518de66834a 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 Sat Nov 28 20:41:08 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 15:41:08 -0500 Subject: [Git][ghc/ghc][master] gitlab-ci: Only deploy GitLab Pages in ghc/ghc> Message-ID: <5fc2b5e43c29e_86c157aeee0777457@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1252,7 +1252,9 @@ pages: EOF - cp -f index.html public/doc rules: - - if: '$CI_COMMIT_BRANCH == "master"' + # N.B. only run this on ghc/ghc since the deployed pages are quite large + # and we only serve GitLab Pages for ghc/ghc. + - if: '$CI_COMMIT_BRANCH == "master" && $CI_PROJECT_NAMESPACE == "ghc"' artifacts: paths: - public View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/698d3d9648e9cb6b3757269e21ce4fa1692a1a3b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/698d3d9648e9cb6b3757269e21ce4fa1692a1a3b 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 Sat Nov 28 20:41:47 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 15:41:47 -0500 Subject: [Git][ghc/ghc][master] ghc-heap: partial TSO/STACK decoding Message-ID: <5fc2b60b23140_86c3fc6aabcaaec7804ec@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22 changed files: - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Runtime/Interpreter.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Heap.c - rts/PrimOps.cmm Changes: ===================================== compiler/GHC/ByteCode/Types.hs ===================================== @@ -37,7 +37,7 @@ import Data.ByteString (ByteString) import Data.IntMap (IntMap) import qualified Data.IntMap as IntMap import Data.Maybe (catMaybes) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS -- ----------------------------------------------------------------------------- @@ -72,7 +72,7 @@ type ItblEnv = NameEnv (Name, ItblPtr) -- We need the Name in the range so we know which -- elements to filter out when unloading a module -newtype ItblPtr = ItblPtr (RemotePtr StgInfoTable) +newtype ItblPtr = ItblPtr (RemotePtr Heap.StgInfoTable) deriving (Show, NFData) data UnlinkedBCO ===================================== compiler/GHC/Runtime/Interpreter.hs ===================================== @@ -103,7 +103,7 @@ import qualified Data.ByteString.Lazy as LB import Data.Array ((!)) import Data.IORef import Foreign hiding (void) -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack.CCS (CostCentre,CostCentreStack) import System.Exit import GHC.IO.Handle.Types (Handle) @@ -395,7 +395,7 @@ getBreakpointVar hsc_env ref ix = mb <- iservCmd hsc_env (GetBreakpointVar apStack ix) mapM (mkFinalizedHValue hsc_env) mb -getClosure :: HscEnv -> ForeignHValue -> IO (GenClosure ForeignHValue) +getClosure :: HscEnv -> ForeignHValue -> IO (Heap.GenClosure ForeignHValue) getClosure hsc_env ref = withForeignRef ref $ \hval -> do mb <- iservCmd hsc_env (GetClosure hval) ===================================== libraries/ghc-heap/GHC/Exts/Heap.hs ===================================== @@ -27,6 +27,9 @@ module GHC.Exts.Heap ( , GenClosure(..) , ClosureType(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , HasHeapRep(getClosureData) , getClosureDataFromHeapRep , getClosureDataFromHeapRepPrim @@ -40,6 +43,12 @@ module GHC.Exts.Heap ( , peekItbl , pokeItbl + -- * Cost Centre (profiling) types + , StgTSOProfInfo(..) + , IndexTable(..) + , CostCentre(..) + , CostCentreStack(..) + -- * Closure inspection , getBoxedClosureData , allClosures @@ -54,12 +63,14 @@ import Prelude import GHC.Exts.Heap.Closures import GHC.Exts.Heap.ClosureTypes import GHC.Exts.Heap.Constants +import GHC.Exts.Heap.ProfInfo.Types #if defined(PROFILING) import GHC.Exts.Heap.InfoTableProf #else import GHC.Exts.Heap.InfoTable #endif import GHC.Exts.Heap.Utils +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures import Control.Monad import Data.Bits @@ -330,6 +341,45 @@ getClosureDataFromHeapRepPrim getConDesc itbl heapRep pts = do , finalizer = pts !! 3 , link = pts !! 4 } + TSO | [ u_lnk, u_gbl_lnk, tso_stack, u_trec, u_blk_ex, u_bq] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekTSOFields ptr + pure $ TSOClosure + { info = itbl + , link = u_lnk + , global_link = u_gbl_lnk + , tsoStack = tso_stack + , trec = u_trec + , blocked_exceptions = u_blk_ex + , bq = u_bq + , what_next = FFIClosures.tso_what_next fields + , why_blocked = FFIClosures.tso_why_blocked fields + , flags = FFIClosures.tso_flags fields + , threadId = FFIClosures.tso_threadId fields + , saved_errno = FFIClosures.tso_saved_errno fields + , tso_dirty = FFIClosures.tso_dirty fields + , alloc_limit = FFIClosures.tso_alloc_limit fields + , tot_stack_size = FFIClosures.tso_tot_stack_size fields + , prof = FFIClosures.tso_prof fields + }) + | otherwise + -> fail $ "Expected 6 ptr arguments to TSO, found " + ++ show (length pts) + STACK + | [] <- pts + -> withArray rawHeapWords (\ptr -> do + fields <- FFIClosures.peekStackFields ptr + pure $ StackClosure + { info = itbl + , stack_size = FFIClosures.stack_size fields + , stack_dirty = FFIClosures.stack_dirty fields +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking = FFIClosures.stack_marking fields +#endif + }) + | otherwise + -> fail $ "Expected 0 ptr argument to STACK, found " + ++ show (length pts) _ -> pure $ UnsupportedClosure itbl ===================================== libraries/ghc-heap/GHC/Exts/Heap/Closures.hs ===================================== @@ -12,6 +12,9 @@ module GHC.Exts.Heap.Closures ( Closure , GenClosure(..) , PrimType(..) + , WhatNext(..) + , WhyBlocked(..) + , TsoFlags(..) , allClosures #if __GLASGOW_HASKELL__ >= 809 -- The closureSize# primop is unsupported on earlier GHC releases but we @@ -40,6 +43,8 @@ import GHC.Exts.Heap.InfoTable import GHC.Exts.Heap.InfoTableProf () #endif +import GHC.Exts.Heap.ProfInfo.Types + import Data.Bits import Data.Int import Data.Word @@ -100,11 +105,11 @@ type Closure = GenClosure Box -- | This is the representation of a Haskell value on the heap. It reflects -- -- --- The data type is parametrized by the type to store references in. Usually --- this is a 'Box' with the type synonym 'Closure'. +-- The data type is parametrized by `b`: the type to store references in. +-- Usually this is a 'Box' with the type synonym 'Closure'. -- --- All Heap objects have the same basic layout. A header containing a pointer --- to the info table and a payload with various fields. The @info@ field below +-- All Heap objects have the same basic layout. A header containing a pointer to +-- the info table and a payload with various fields. The @info@ field below -- always refers to the info table pointed to by the header. The remaining -- fields are the payload. -- @@ -268,6 +273,39 @@ data GenClosure b , link :: !b -- ^ next weak pointer for the capability, can be NULL. } + -- | Representation of StgTSO: A Thread State Object. The values for + -- 'what_next', 'why_blocked' and 'flags' are defined in @Constants.h at . + | TSOClosure + { info :: !StgInfoTable + -- pointers + , link :: !b + , global_link :: !b + , tsoStack :: !b -- ^ stackobj from StgTSO + , trec :: !b + , blocked_exceptions :: !b + , bq :: !b + -- values + , what_next :: !WhatNext + , why_blocked :: !WhyBlocked + , flags :: ![TsoFlags] + , threadId :: !Word64 + , saved_errno :: !Word32 + , tso_dirty :: !Word32 -- ^ non-zero => dirty + , alloc_limit :: !Int64 + , tot_stack_size :: !Word32 + , prof :: !(Maybe StgTSOProfInfo) + } + + -- | Representation of StgStack: The 'tsoStack ' of a 'TSOClosure'. + | StackClosure + { info :: !StgInfoTable + , stack_size :: !Word32 -- ^ stack size in *words* + , stack_dirty :: !Word8 -- ^ non-zero => dirty +#if __GLASGOW_HASKELL__ >= 811 + , stack_marking :: !Word8 +#endif + } + ------------------------------------------------------------ -- Unboxed unlifted closures @@ -332,6 +370,43 @@ data PrimType | PDouble deriving (Eq, Show, Generic) +data WhatNext + = ThreadRunGHC + | ThreadInterpret + | ThreadKilled + | ThreadComplete + | WhatNextUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data WhyBlocked + = NotBlocked + | BlockedOnMVar + | BlockedOnMVarRead + | BlockedOnBlackHole + | BlockedOnRead + | BlockedOnWrite + | BlockedOnDelay + | BlockedOnSTM + | BlockedOnDoProc + | BlockedOnCCall + | BlockedOnCCall_Interruptible + | BlockedOnMsgThrowTo + | ThreadMigrating + | BlockedOnIOCompletion + | WhyBlockedUnknownValue Word16 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + +data TsoFlags + = TsoLocked + | TsoBlockx + | TsoInterruptible + | TsoStoppedOnBreakpoint + | TsoMarked + | TsoSqueezed + | TsoAllocLimit + | TsoFlagsUnknownValue Word32 -- ^ Please report this as a bug + deriving (Eq, Show, Generic) + -- | For generic code, this function returns all referenced closures. allClosures :: GenClosure b -> [b] allClosures (ConstrClosure {..}) = ptrArgs ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs ===================================== @@ -0,0 +1,47 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.FFIClosures (module Reexport) where + +-- NOTE [hsc and CPP workaround] +-- +-- # Problem +-- +-- Often, .hsc files are used to get the correct offsets of C struct fields. +-- Those structs may be affected by CPP directives e.g. profiled vs not profiled +-- closure headers is affected by the PROFILED cpp define. Since we are building +-- multiple variants of the RTS, we must support all possible offsets e.g. by +-- running hsc2hs with cpp defines corresponding to each RTS flavour. The +-- problem is that GHC's build system runs hsc2hs *only once* per .hsc file +-- without properly setting cpp defines. This results in the same (probably +-- incorrect) offsets into our C structs. +-- +-- +-- # Workaround +-- +-- To work around this issue, we create multiple .hsc files each manually +-- defining thir cpp defines (see e.g. FFIClosures_ProfilingDisabled.hsc and +-- FFIClosures_ProfilingEnabled.hsc). Then we rely on cpp defines working +-- correctly in .hs files and use CPP to switch on which .hsc module to +-- re-export (see below). In each case we import the desired .hsc module as +-- `Reexport` and we import `()` (i.e. nothing) from all other .hsc variants +-- just so that the build system sees all .hsc file as dependencies. +-- +-- +-- # Future Work +-- +-- * Duplication of the code in the .hsc files could be reduced simply by +-- placing the code in a single .hsc.in file and `#include`ing it from each +-- .hsc file. The .hsc files would only be responsible for setting the correct +-- cpp defines. This currently doesn't work as hadrian doesn't know to copy +-- the .hsc.in file to the build directory. +-- * The correct solution would be for the build system to run `hsc2hs` with the +-- correct cpp defines once per RTS flavour. +-- + +#if defined(PROFILING) +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled () +#else +import GHC.Exts.Heap.FFIClosures_ProfilingDisabled as Reexport +import GHC.Exts.Heap.FFIClosures_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,131 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingDisabled where + +-- See [hsc and CPP workaround] + +#undef PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } + ===================================== libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,130 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.FFIClosures_ProfilingEnabled where + +-- See [hsc and CPP workaround] + +#define PROFILING +#include "Rts.h" + +import Prelude +import Foreign +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.PeekProfInfo +import GHC.Exts.Heap.ProfInfo.Types +import GHC.Exts.Heap.Closures(WhatNext(..), WhyBlocked(..), TsoFlags(..)) + +data TSOFields = TSOFields { + tso_what_next :: WhatNext, + tso_why_blocked :: WhyBlocked, + tso_flags :: [TsoFlags], +-- Unfortunately block_info is a union without clear discriminator. +-- block_info :: TDB, + tso_threadId :: Word64, + tso_saved_errno :: Word32, + tso_dirty:: Word32, + tso_alloc_limit :: Int64, + tso_tot_stack_size :: Word32, + tso_prof :: Maybe StgTSOProfInfo +} + +-- | Get non-pointer fields from @StgTSO_@ (@TSO.h@) +peekTSOFields :: Ptr tsoPtr -> IO TSOFields +peekTSOFields ptr = do + what_next' <- (#peek struct StgTSO_, what_next) ptr + why_blocked' <- (#peek struct StgTSO_, why_blocked) ptr + flags' <- (#peek struct StgTSO_, flags) ptr + threadId' <- (#peek struct StgTSO_, id) ptr + saved_errno' <- (#peek struct StgTSO_, saved_errno) ptr + dirty' <- (#peek struct StgTSO_, dirty) ptr + alloc_limit' <- (#peek struct StgTSO_, alloc_limit) ptr + tot_stack_size' <- (#peek struct StgTSO_, tot_stack_size) ptr + tso_prof' <- peekStgTSOProfInfo ptr + + return TSOFields { + tso_what_next = parseWhatNext what_next', + tso_why_blocked = parseWhyBlocked why_blocked', + tso_flags = parseTsoFlags flags', + tso_threadId = threadId', + tso_saved_errno = saved_errno', + tso_dirty = dirty', + tso_alloc_limit = alloc_limit', + tso_tot_stack_size = tot_stack_size', + tso_prof = tso_prof' + } + +parseWhatNext :: Word16 -> WhatNext +parseWhatNext w = case w of + (#const ThreadRunGHC) -> ThreadRunGHC + (#const ThreadInterpret) -> ThreadInterpret + (#const ThreadKilled) -> ThreadKilled + (#const ThreadComplete) -> ThreadComplete + _ -> WhatNextUnknownValue w + +parseWhyBlocked :: Word16 -> WhyBlocked +parseWhyBlocked w = case w of + (#const NotBlocked) -> NotBlocked + (#const BlockedOnMVar) -> BlockedOnMVar + (#const BlockedOnMVarRead) -> BlockedOnMVarRead + (#const BlockedOnBlackHole) -> BlockedOnBlackHole + (#const BlockedOnRead) -> BlockedOnRead + (#const BlockedOnWrite) -> BlockedOnWrite + (#const BlockedOnDelay) -> BlockedOnDelay + (#const BlockedOnSTM) -> BlockedOnSTM + (#const BlockedOnDoProc) -> BlockedOnDoProc + (#const BlockedOnCCall) -> BlockedOnCCall + (#const BlockedOnCCall_Interruptible) -> BlockedOnCCall_Interruptible + (#const BlockedOnMsgThrowTo) -> BlockedOnMsgThrowTo + (#const ThreadMigrating) -> ThreadMigrating +#if __GLASGOW_HASKELL__ >= 811 + (#const BlockedOnIOCompletion) -> BlockedOnIOCompletion +#endif + _ -> WhyBlockedUnknownValue w + +parseTsoFlags :: Word32 -> [TsoFlags] +parseTsoFlags w | isSet (#const TSO_LOCKED) w = TsoLocked : parseTsoFlags (unset (#const TSO_LOCKED) w) + | isSet (#const TSO_BLOCKEX) w = TsoBlockx : parseTsoFlags (unset (#const TSO_BLOCKEX) w) + | isSet (#const TSO_INTERRUPTIBLE) w = TsoInterruptible : parseTsoFlags (unset (#const TSO_INTERRUPTIBLE) w) + | isSet (#const TSO_STOPPED_ON_BREAKPOINT) w = TsoStoppedOnBreakpoint : parseTsoFlags (unset (#const TSO_STOPPED_ON_BREAKPOINT) w) + | isSet (#const TSO_MARKED) w = TsoMarked : parseTsoFlags (unset (#const TSO_MARKED) w) + | isSet (#const TSO_SQUEEZED) w = TsoSqueezed : parseTsoFlags (unset (#const TSO_SQUEEZED) w) + | isSet (#const TSO_ALLOC_LIMIT) w = TsoAllocLimit : parseTsoFlags (unset (#const TSO_ALLOC_LIMIT) w) +parseTsoFlags 0 = [] +parseTsoFlags w = [TsoFlagsUnknownValue w] + +isSet :: Word32 -> Word32 -> Bool +isSet bitMask w = w .&. bitMask /= 0 + +unset :: Word32 -> Word32 -> Word32 +unset bitMask w = w `xor` bitMask + +data StackFields = StackFields { + stack_size :: Word32, + stack_dirty :: Word8, +#if __GLASGOW_HASKELL__ >= 811 + stack_marking :: Word8, +#endif + stack_sp :: Addr## +} + +-- | Get non-closure fields from @StgStack_@ (@TSO.h@) +peekStackFields :: Ptr a -> IO StackFields +peekStackFields ptr = do + stack_size' <- (#peek struct StgStack_, stack_size) ptr ::IO Word32 + dirty' <- (#peek struct StgStack_, dirty) ptr +#if __GLASGOW_HASKELL__ >= 811 + marking' <- (#peek struct StgStack_, marking) ptr +#endif + Ptr sp' <- (#peek struct StgStack_, sp) ptr + + -- TODO decode the stack. + + return StackFields { + stack_size = stack_size', + stack_dirty = dirty', +#if __GLASGOW_HASKELL__ >= 811 + stack_marking = marking', +#endif + stack_sp = sp' + } ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs ===================================== @@ -0,0 +1,13 @@ +{-# LANGUAGE CPP #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo (module Reexport) where + +-- See [hsc and CPP workaround] + +#if defined(PROFILING) +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled () +#else +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled as Reexport +import GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled () +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc ===================================== @@ -0,0 +1,12 @@ +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled( + peekStgTSOProfInfo +) where + +import Prelude +import Foreign +import GHC.Exts.Heap.ProfInfo.Types + +-- | This implementation is used when PROFILING is undefined. +-- It always returns 'Nothing', because there is no profiling info available. +peekStgTSOProfInfo :: Ptr tsoPtr -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc ===================================== @@ -0,0 +1,165 @@ +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled( + peekStgTSOProfInfo +) where + +#if __GLASGOW_HASKELL__ >= 811 + +-- See [hsc and CPP workaround] + +#define PROFILING + +#include "Rts.h" +#undef BLOCK_SIZE +#undef MBLOCK_SIZE +#undef BLOCKS_PER_MBLOCK +#include "DerivedConstants.h" + +import Data.IntSet (IntSet) +import qualified Data.IntSet as IntSet +import Data.IntMap.Strict (IntMap) +import qualified Data.IntMap.Strict as IntMap +import Data.IORef (IORef, newIORef, readIORef, writeIORef) +import Foreign +import Foreign.C.String +import GHC.Exts +import GHC.Exts.Heap.ProfInfo.Types +import Prelude + +-- Use Int based containers for pointers (addresses) for better performance. +-- These will be queried a lot! +type AddressSet = IntSet +type AddressMap = IntMap + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo tsoPtr = do + cccs_ptr <- peekByteOff tsoPtr cccsOffset + costCenterCacheRef <- newIORef IntMap.empty + cccs' <- peekCostCentreStack IntSet.empty costCenterCacheRef cccs_ptr + + return $ Just StgTSOProfInfo { + cccs = cccs' + } + +cccsOffset :: Int +cccsOffset = (#const OFFSET_StgTSO_cccs) + (#size StgHeader) + +peekCostCentreStack + :: AddressSet + -> IORef (AddressMap CostCentre) + -> Ptr costCentreStack + -> IO (Maybe CostCentreStack) +peekCostCentreStack _ _ ptr | ptr == nullPtr = return Nothing +peekCostCentreStack loopBreakers _ ptr | IntSet.member (ptrToInt ptr) loopBreakers = return Nothing +peekCostCentreStack loopBreakers costCenterCacheRef ptr = do + ccs_ccsID' <- (#peek struct CostCentreStack_, ccsID) ptr + ccs_cc_ptr <- (#peek struct CostCentreStack_, cc) ptr + ccs_cc' <- peekCostCentre costCenterCacheRef ccs_cc_ptr + ccs_prevStack_ptr <- (#peek struct CostCentreStack_, prevStack) ptr + let loopBreakers' = (IntSet.insert ptrAsInt loopBreakers) + ccs_prevStack' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_prevStack_ptr + ccs_indexTable_ptr <- (#peek struct CostCentreStack_, indexTable) ptr + ccs_indexTable' <- peekIndexTable loopBreakers' costCenterCacheRef ccs_indexTable_ptr + ccs_root_ptr <- (#peek struct CostCentreStack_, root) ptr + ccs_root' <- peekCostCentreStack loopBreakers' costCenterCacheRef ccs_root_ptr + ccs_depth' <- (#peek struct CostCentreStack_, depth) ptr + ccs_scc_count' <- (#peek struct CostCentreStack_, scc_count) ptr + ccs_selected' <- (#peek struct CostCentreStack_, selected) ptr + ccs_time_ticks' <- (#peek struct CostCentreStack_, time_ticks) ptr + ccs_mem_alloc' <- (#peek struct CostCentreStack_, mem_alloc) ptr + ccs_inherited_alloc' <- (#peek struct CostCentreStack_, inherited_alloc) ptr + ccs_inherited_ticks' <- (#peek struct CostCentreStack_, inherited_ticks) ptr + + return $ Just CostCentreStack { + ccs_ccsID = ccs_ccsID', + ccs_cc = ccs_cc', + ccs_prevStack = ccs_prevStack', + ccs_indexTable = ccs_indexTable', + ccs_root = ccs_root', + ccs_depth = ccs_depth', + ccs_scc_count = ccs_scc_count', + ccs_selected = ccs_selected', + ccs_time_ticks = ccs_time_ticks', + ccs_mem_alloc = ccs_mem_alloc', + ccs_inherited_alloc = ccs_inherited_alloc', + ccs_inherited_ticks = ccs_inherited_ticks' + } + where + ptrAsInt = ptrToInt ptr + +peekCostCentre :: IORef (AddressMap CostCentre) -> Ptr costCentre -> IO CostCentre +peekCostCentre costCenterCacheRef ptr = do + costCenterCache <- readIORef costCenterCacheRef + case IntMap.lookup ptrAsInt costCenterCache of + (Just a) -> return a + Nothing -> do + cc_ccID' <- (#peek struct CostCentre_, ccID) ptr + cc_label_ptr <- (#peek struct CostCentre_, label) ptr + cc_label' <- peekCString cc_label_ptr + cc_module_ptr <- (#peek struct CostCentre_, module) ptr + cc_module' <- peekCString cc_module_ptr + cc_srcloc_ptr <- (#peek struct CostCentre_, srcloc) ptr + cc_srcloc' <- do + if cc_srcloc_ptr == nullPtr then + return Nothing + else + fmap Just (peekCString cc_srcloc_ptr) + cc_mem_alloc' <- (#peek struct CostCentre_, mem_alloc) ptr + cc_time_ticks' <- (#peek struct CostCentre_, time_ticks) ptr + cc_is_caf' <- (#peek struct CostCentre_, is_caf) ptr + cc_link_ptr <- (#peek struct CostCentre_, link) ptr + cc_link' <- if cc_link_ptr == nullPtr then + return Nothing + else + fmap Just (peekCostCentre costCenterCacheRef cc_link_ptr) + + let result = CostCentre { + cc_ccID = cc_ccID', + cc_label = cc_label', + cc_module = cc_module', + cc_srcloc = cc_srcloc', + cc_mem_alloc = cc_mem_alloc', + cc_time_ticks = cc_time_ticks', + cc_is_caf = cc_is_caf', + cc_link = cc_link' + } + + writeIORef costCenterCacheRef (IntMap.insert ptrAsInt result costCenterCache) + + return result + where + ptrAsInt = ptrToInt ptr + +peekIndexTable :: AddressSet -> IORef (AddressMap CostCentre) -> Ptr indexTable -> IO (Maybe IndexTable) +peekIndexTable _ _ ptr | ptr == nullPtr = return Nothing +peekIndexTable loopBreakers costCenterCacheRef ptr = do + it_cc_ptr <- (#peek struct IndexTable_, cc) ptr + it_cc' <- peekCostCentre costCenterCacheRef it_cc_ptr + it_ccs_ptr <- (#peek struct IndexTable_, ccs) ptr + it_ccs' <- peekCostCentreStack loopBreakers costCenterCacheRef it_ccs_ptr + it_next_ptr <- (#peek struct IndexTable_, next) ptr + it_next' <- peekIndexTable loopBreakers costCenterCacheRef it_next_ptr + it_back_edge' <- (#peek struct IndexTable_, back_edge) ptr + + return $ Just IndexTable { + it_cc = it_cc', + it_ccs = it_ccs', + it_next = it_next', + it_back_edge = it_back_edge' + } + +-- | casts a @Ptr@ to an @Int@ +ptrToInt :: Ptr a -> Int +ptrToInt (Ptr a##) = I## (addr2Int## a##) + +#else +import Prelude +import Foreign + +import GHC.Exts.Heap.ProfInfo.Types + +peekStgTSOProfInfo :: Ptr a -> IO (Maybe StgTSOProfInfo) +peekStgTSOProfInfo _ = return Nothing +#endif ===================================== libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs ===================================== @@ -0,0 +1,56 @@ +{-# LANGUAGE DeriveGeneric #-} + +module GHC.Exts.Heap.ProfInfo.Types where + +import Prelude +import Data.Word +import GHC.Generics + +-- | This is a somewhat faithful representation of StgTSOProfInfo. See +-- +-- for more details on this data structure. +data StgTSOProfInfo = StgTSOProfInfo { + cccs :: Maybe CostCentreStack +} deriving (Show, Generic) + +-- | This is a somewhat faithful representation of CostCentreStack. See +-- +-- for more details on this data structure. +data CostCentreStack = CostCentreStack { + ccs_ccsID :: Int, + ccs_cc :: CostCentre, + ccs_prevStack :: Maybe CostCentreStack, + ccs_indexTable :: Maybe IndexTable, + ccs_root :: Maybe CostCentreStack, + ccs_depth :: Word, + ccs_scc_count :: Word64, + ccs_selected :: Word, + ccs_time_ticks :: Word, + ccs_mem_alloc :: Word64, + ccs_inherited_alloc :: Word64, + ccs_inherited_ticks :: Word +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of CostCentre. See +-- +-- for more details on this data structure. +data CostCentre = CostCentre { + cc_ccID :: Int, + cc_label :: String, + cc_module :: String, + cc_srcloc :: Maybe String, + cc_mem_alloc :: Word64, + cc_time_ticks :: Word, + cc_is_caf :: Bool, + cc_link :: Maybe CostCentre +} deriving (Show, Generic, Eq) + +-- | This is a somewhat faithful representation of IndexTable. See +-- +-- for more details on this data structure. +data IndexTable = IndexTable { + it_cc :: CostCentre, + it_ccs :: Maybe CostCentreStack, + it_next :: Maybe IndexTable, + it_back_edge :: Bool +} deriving (Show, Generic, Eq) ===================================== libraries/ghc-heap/ghc-heap.cabal.in ===================================== @@ -25,6 +25,7 @@ library build-depends: base >= 4.9.0 && < 5.0 , ghc-prim > 0.2 && < 0.9 , rts == 1.0.* + , containers >= 0.6.2.1 && < 0.7 ghc-options: -Wall cmm-sources: cbits/HeapPrim.cmm @@ -39,3 +40,10 @@ library GHC.Exts.Heap.InfoTable.Types GHC.Exts.Heap.InfoTableProf GHC.Exts.Heap.Utils + GHC.Exts.Heap.FFIClosures + GHC.Exts.Heap.FFIClosures_ProfilingDisabled + GHC.Exts.Heap.FFIClosures_ProfilingEnabled + GHC.Exts.Heap.ProfInfo.Types + GHC.Exts.Heap.ProfInfo.PeekProfInfo + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingDisabled + GHC.Exts.Heap.ProfInfo.PeekProfInfo_ProfilingEnabled ===================================== libraries/ghc-heap/tests/TestUtils.hs ===================================== @@ -0,0 +1,7 @@ +{-# LANGUAGE MagicHash #-} +module TestUtils where + +assertEqual :: (Show a, Eq a) => a -> a -> IO () +assertEqual a b + | a /= b = error (show a ++ " /= " ++ show b) + | otherwise = return () ===================================== libraries/ghc-heap/tests/all.T ===================================== @@ -36,3 +36,18 @@ test('closure_size_noopt', ], compile_and_run, ['']) +test('tso_and_stack_closures', + [extra_files(['create_tso.c','create_tso.h','TestUtils.hs']), + only_ways(['profthreaded']), + ignore_stdout, + ignore_stderr + ], + multi_compile_and_run, ['tso_and_stack_closures', [('create_tso.c','')], '']) + +test('parse_tso_flags', + [extra_files(['TestUtils.hs']), + only_ways(['normal']), + ignore_stdout, + ignore_stderr + ], + compile_and_run, ['']) ===================================== libraries/ghc-heap/tests/create_tso.c ===================================== @@ -0,0 +1,82 @@ +#include "Rts.h" +#include "RtsAPI.h" + +// Assumes the rts is paused +void unpack_closure + ( StgClosure * inClosure + , const StgInfoTable ** outInfoTablePtr + , int * outHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outHeapRep // Array of words + , int * outPointersSize // Size of outPointers (in words) + , StgClosure *** outPointers // Array of all pointers of the TSO + ) +{ + *outInfoTablePtr = get_itbl(inClosure); + + // Copy TSO pointers. + StgWord closureSizeW = heap_view_closureSize(inClosure); + int closureSizeB = sizeof(StgWord) * closureSizeW; + StgClosure ** pointers = malloc(closureSizeB); + *outPointersSize = collect_pointers(inClosure, closureSizeW, pointers); + *outPointers = pointers; + + // Copy the heap rep. + StgWord * heapRep = malloc(closureSizeB); + for (int i = 0; i < closureSizeW; i++) + { + heapRep[i] = ((StgWord*)inClosure)[i]; + } + + *outHeapRepSize = closureSizeB; + *outHeapRep = heapRep; +} + +// Must be called from a safe FFI call. +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ) +{ + // Pause RTS + PauseToken * token = rts_pause(); + Capability * cap = pauseTokenCapability(token); + + // Create TSO/Stack + HaskellObj trueClosure = rts_mkBool(cap, 1); + *outTso = createGenThread(cap, 500U, trueClosure); + + // Unpack TSO + unpack_closure( + (StgClosure*)(*outTso), + outTsoInfoTablePtr, + outTsoHeapRepSize, + outTsoHeapRep, + outTsoPointersSize, + outTsoPointers); + + // Unpack STACK + StgClosure * outStackAsClosure = (*outTsoPointers)[2]; + *outStack = (StgTSO *)outStackAsClosure; + unpack_closure( + outStackAsClosure, + outStackInfoTablePtr, + outStackHeapRepSize, + outStackHeapRep, + outStackPointersSize, + outStackPointers); + + // Resume RTS + rts_resume(token); +} ===================================== libraries/ghc-heap/tests/create_tso.h ===================================== @@ -0,0 +1,19 @@ +#include "Rts.h" +#include "RtsAPI.h" + +void create_and_unpack_tso_and_stack + // TSO + ( StgTSO ** outTso + , const StgInfoTable ** outTsoInfoTablePtr + , int * outTsoHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outTsoHeapRep // Array of words + , int * outTsoPointersSize // Size of outPointers (in words) + , StgClosure *** outTsoPointers // Array of all pointers of the TSO + // Stack + , StgTSO ** outStack + , const StgInfoTable ** outStackInfoTablePtr + , int * outStackHeapRepSize // Size of outHeapRep (in bytes) + , StgWord ** outStackHeapRep // Array of words + , int * outStackPointersSize // Size of outPointers (in words) + , StgClosure *** outStackPointers // Array of all pointers of the TSO + ); ===================================== libraries/ghc-heap/tests/parse_tso_flags.hs ===================================== @@ -0,0 +1,17 @@ +import GHC.Exts.Heap.Closures +import GHC.Exts.Heap.FFIClosures +import TestUtils + +main :: IO() +main = do + assertEqual (parseTsoFlags 0) [] + assertEqual (parseTsoFlags 1) [TsoFlagsUnknownValue 1] + assertEqual (parseTsoFlags 2) [TsoLocked] + assertEqual (parseTsoFlags 4) [TsoBlockx] + assertEqual (parseTsoFlags 8) [TsoInterruptible] + assertEqual (parseTsoFlags 16) [TsoStoppedOnBreakpoint] + assertEqual (parseTsoFlags 64) [TsoMarked] + assertEqual (parseTsoFlags 128) [TsoSqueezed] + assertEqual (parseTsoFlags 256) [TsoAllocLimit] + + assertEqual (parseTsoFlags 6) [TsoLocked, TsoBlockx] ===================================== libraries/ghc-heap/tests/tso_and_stack_closures.hs ===================================== @@ -0,0 +1,167 @@ +{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE ForeignFunctionInterface #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} + +import Control.Monad (forM_, unless) +import Data.List (find) +import Data.Word +import Foreign +import Foreign.C.Types +import GHC.IO ( IO(..) ) +import GHC.Exts +import GHC.Exts.Heap +import qualified GHC.Exts.Heap.FFIClosures as FFIClosures +import GHC.Word + +import TestUtils + +main :: IO () +main = do + (tso, stack) <- {-# SCC "MyCostCentre" #-} createAndUnpackTSOAndSTACKClosure + assertEqual (getClosureType tso) TSO + assertEqual (what_next tso) ThreadRunGHC + assertEqual (why_blocked tso) NotBlocked + assertEqual (saved_errno tso) 0 + forM_ (flags tso) $ \flag -> case flag of + TsoFlagsUnknownValue _ -> error $ "Unknown flag: " ++ show flag + _ | flag `elem` + [ TsoLocked + , TsoBlockx + , TsoStoppedOnBreakpoint + , TsoSqueezed + ] -> error $ "Unexpected flag: " ++ show flag + _ -> return () + + assertEqual (getClosureType stack) STACK + +#if defined(PROFILING) + let costCentre = ccs_cc <$> (cccs =<< prof tso) + case costCentre of + Nothing -> error $ "No CostCentre found in TSO: " ++ show tso + Just _ -> case findMyCostCentre (linkedCostCentres costCentre) of + Just myCostCentre -> do + assertEqual (cc_label myCostCentre) "MyCostCentre" + assertEqual (cc_module myCostCentre) "Main" + assertEqual (cc_srcloc myCostCentre) (Just "tso_and_stack_closures.hs:23:48-80") + assertEqual (cc_is_caf myCostCentre) False + Nothing -> error $ "MyCostCentre not found in:\n" ++ unlines (cc_label <$> linkedCostCentres costCentre) +#endif + +linkedCostCentres :: Maybe CostCentre -> [CostCentre] +linkedCostCentres Nothing = [] +linkedCostCentres (Just cc) = cc : linkedCostCentres (cc_link cc) + +findMyCostCentre:: [CostCentre] -> Maybe CostCentre +findMyCostCentre ccs = find (\cc -> cc_label cc == "MyCostCentre") ccs + +getClosureType :: GenClosure b -> ClosureType +getClosureType = tipe . info + +type StgTso = Any +type StgStack = Any +data MBA a = MBA (MutableByteArray# a) +data BA = BA ByteArray# + +foreign import ccall safe "create_tso.h create_and_unpack_tso_and_stack" + c_create_and_unpack_tso_and_stack + :: Ptr (Ptr StgTso) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> Ptr (Ptr StgStack) + -> Ptr (Ptr StgInfoTable) + -> Ptr CInt + -> Ptr (Ptr Word8) + -> Ptr CInt + -> Ptr (Ptr (Ptr Any)) + -> IO () + +createAndUnpackTSOAndSTACKClosure + :: IO ( GenClosure (Ptr Any) + , GenClosure (Ptr Any) + ) +createAndUnpackTSOAndSTACKClosure = do + + alloca $ \ptrPtrTso -> do + alloca $ \ptrPtrTsoInfoTable -> do + alloca $ \ptrTsoHeapRepSize -> do + alloca $ \ptrPtrTsoHeapRep -> do + alloca $ \ptrTsoPointersSize -> do + alloca $ \ptrPtrPtrTsoPointers -> do + + alloca $ \ptrPtrStack -> do + alloca $ \ptrPtrStackInfoTable -> do + alloca $ \ptrStackHeapRepSize -> do + alloca $ \ptrPtrStackHeapRep -> do + alloca $ \ptrStackPointersSize -> do + alloca $ \ptrPtrPtrStackPointers -> do + + c_create_and_unpack_tso_and_stack + + ptrPtrTso + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + ptrPtrStack + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + let fromHeapRep + ptrPtrClosureInfoTable + ptrClosureHeapRepSize + ptrPtrClosureHeapRep + ptrClosurePointersSize + ptrPtrPtrClosurePointers = do + ptrInfoTable :: Ptr StgInfoTable <- peek ptrPtrClosureInfoTable + + heapRepSize :: Int <- fromIntegral <$> peek ptrClosureHeapRepSize + let I# heapRepSize# = heapRepSize + ptrHeapRep :: Ptr Word8 <- peek ptrPtrClosureHeapRep + MBA mutHeapRepBA <- IO $ \s -> let + (# s', mba# #) = newByteArray# heapRepSize# s + in (# s', MBA mba# #) + forM_ [0..heapRepSize-1] $ \i@(I# i#) -> do + W8# w <- peekElemOff ptrHeapRep i + IO (\s -> (# writeWord8Array# mutHeapRepBA i# (extendWord8# w) s, () #)) + BA heapRep <- IO $ \s -> let + (# s', ba# #) = unsafeFreezeByteArray# mutHeapRepBA s + in (# s', BA ba# #) + + pointersSize :: Int <- fromIntegral <$> peek ptrClosurePointersSize + ptrPtrPointers :: Ptr (Ptr Any) <- peek ptrPtrPtrClosurePointers + ptrPtrPointers :: [Ptr Any] <- sequence + [ peekElemOff ptrPtrPointers i + | i <- [0..pointersSize-1] + ] + + getClosureDataFromHeapRep + heapRep + ptrInfoTable + ptrPtrPointers + + tso <- fromHeapRep + ptrPtrTsoInfoTable + ptrTsoHeapRepSize + ptrPtrTsoHeapRep + ptrTsoPointersSize + ptrPtrPtrTsoPointers + + stack <- fromHeapRep + ptrPtrStackInfoTable + ptrStackHeapRepSize + ptrPtrStackHeapRep + ptrStackPointersSize + ptrPtrPtrStackPointers + + return (tso, stack) ===================================== libraries/ghci/GHCi/Message.hs ===================================== @@ -1,5 +1,6 @@ {-# LANGUAGE GADTs, DeriveGeneric, StandaloneDeriving, ScopedTypeVariables, - GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards #-} + GeneralizedNewtypeDeriving, ExistentialQuantification, RecordWildCards, + CPP #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-orphans #-} -- | @@ -29,7 +30,7 @@ import GHCi.TH.Binary () -- For Binary instances import GHCi.BreakArray import GHC.LanguageExtensions -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.ForeignSrcLang import GHC.Fingerprint import Control.Concurrent @@ -110,7 +111,7 @@ data Message a where -> Int -- constr tag -> Int -- pointer tag -> ByteString -- constructor desccription - -> Message (RemotePtr StgInfoTable) + -> Message (RemotePtr Heap.StgInfoTable) -- | Evaluate a statement EvalStmt @@ -211,7 +212,7 @@ data Message a where -- type reconstruction. GetClosure :: HValueRef - -> Message (GenClosure HValueRef) + -> Message (Heap.GenClosure HValueRef) -- | Evaluate something. This is used to support :force in GHCi. Seq @@ -449,10 +450,20 @@ instance Binary (FunPtr a) where get = castPtrToFunPtr <$> get -- Binary instances to support the GetClosure message -instance Binary StgInfoTable -instance Binary ClosureType -instance Binary PrimType -instance Binary a => Binary (GenClosure a) +#if MIN_VERSION_ghc_heap(8,11,0) +instance Binary Heap.StgTSOProfInfo +instance Binary Heap.CostCentreStack +instance Binary Heap.CostCentre +instance Binary Heap.IndexTable +instance Binary Heap.WhatNext +instance Binary Heap.WhyBlocked +instance Binary Heap.TsoFlags +#endif + +instance Binary Heap.StgInfoTable +instance Binary Heap.ClosureType +instance Binary Heap.PrimType +instance Binary a => Binary (Heap.GenClosure a) data Msg = forall a . (Binary a, Show a) => Msg (Message a) ===================================== libraries/ghci/GHCi/Run.hs ===================================== @@ -32,7 +32,7 @@ import Data.Binary.Get import Data.ByteString (ByteString) import qualified Data.ByteString.Unsafe as B import GHC.Exts -import GHC.Exts.Heap +import qualified GHC.Exts.Heap as Heap import GHC.Stack import Foreign hiding (void) import Foreign.C @@ -93,8 +93,8 @@ run m = case m of toRemotePtr <$> mkConInfoTable tc ptrs nptrs tag ptrtag desc StartTH -> startTH GetClosure ref -> do - clos <- getClosureData =<< localRef ref - mapM (\(Box x) -> mkRemoteRef (HValue x)) clos + clos <- Heap.getClosureData =<< localRef ref + mapM (\(Heap.Box x) -> mkRemoteRef (HValue x)) clos Seq ref -> doSeq ref ResumeSeq ref -> resumeSeq ref _other -> error "GHCi.Run.run" ===================================== rts/Heap.c ===================================== @@ -203,7 +203,26 @@ StgWord collect_pointers(StgClosure *closure, StgWord size, StgClosure *ptrs[siz ptrs[nptrs++] = (StgClosure *)((StgMVar *)closure)->tail; ptrs[nptrs++] = ((StgMVar *)closure)->value; break; + case TSO: + ASSERT((StgClosure *)((StgTSO *)closure)->_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->_link; + ASSERT((StgClosure *)((StgTSO *)closure)->global_link != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->global_link; + + ASSERT((StgClosure *)((StgTSO *)closure)->stackobj != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->stackobj; + + ASSERT((StgClosure *)((StgTSO *)closure)->trec != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->trec; + + ASSERT((StgClosure *)((StgTSO *)closure)->blocked_exceptions != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->blocked_exceptions; + + ASSERT((StgClosure *)((StgTSO *)closure)->bq != NULL); + ptrs[nptrs++] = (StgClosure *)((StgTSO *)closure)->bq; + + break; case WEAK: ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->cfinalizers; ptrs[nptrs++] = (StgClosure *)((StgWeak *)closure)->key; ===================================== rts/PrimOps.cmm ===================================== @@ -2371,11 +2371,11 @@ stg_unpackClosurezh ( P_ closure ) clos = UNTAG(closure); W_ len; - // The array returned is the raw data for the entire closure. + // The array returned, dat_arr, is the raw data for the entire closure. // The length is variable based upon the closure type, ptrs, and non-ptrs (len) = foreign "C" heap_view_closureSize(clos "ptr"); - W_ ptrs_arr_sz, ptrs_arr_cards, dat_arr_sz; + W_ dat_arr_sz; dat_arr_sz = SIZEOF_StgArrBytes + WDS(len); ("ptr" dat_arr) = ccall allocateMightFail(MyCapability() "ptr", BYTES_TO_WDS(dat_arr_sz)); @@ -2396,7 +2396,7 @@ for: W_ ptrArray; - // Follow the pointers + // Collect pointers. ("ptr" ptrArray) = foreign "C" heap_view_closurePtrs(MyCapability() "ptr", clos "ptr"); return (info, dat_arr, ptrArray); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/625726f988852f5779825a954609d187d9865dc1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/625726f988852f5779825a954609d187d9865dc1 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 Sat Nov 28 20:42:21 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 15:42:21 -0500 Subject: [Git][ghc/ghc][master] Small optimization to CmmSink. Message-ID: <5fc2b62d7df67_86c879fa9c783397@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - 1 changed file: - compiler/GHC/Cmm/Sink.hs Changes: ===================================== compiler/GHC/Cmm/Sink.hs ===================================== @@ -449,6 +449,7 @@ tryToInline platform live node assigs = go usages node emptyLRegSet assigs || l `elemLRegSet` skipped || not (okToInline platform rhs node) + -- How often is l used in the current node. l_usages = lookupUFM usages l l_live = l `elemRegSet` live @@ -554,10 +555,16 @@ addUsage m r = addToUFM_C (+) m r 1 regsUsedIn :: LRegSet -> CmmExpr -> Bool regsUsedIn ls _ | nullLRegSet ls = False -regsUsedIn ls e = wrapRecExpf f e False - where f (CmmReg (CmmLocal l)) _ | l `elemLRegSet` ls = True - f (CmmRegOff (CmmLocal l) _) _ | l `elemLRegSet` ls = True - f _ z = z +regsUsedIn ls e = go ls e False + where use :: LRegSet -> CmmExpr -> Bool -> Bool + use ls (CmmReg (CmmLocal l)) _ | l `elemLRegSet` ls = True + use ls (CmmRegOff (CmmLocal l) _) _ | l `elemLRegSet` ls = True + use _ls _ z = z + + go :: LRegSet -> CmmExpr -> Bool -> Bool + go ls (CmmMachOp _ es) z = foldr (go ls) z es + go ls (CmmLoad addr _) z = go ls addr z + go ls e z = use ls e z -- we don't inline into CmmUnsafeForeignCall if the expression refers -- to global registers. This is a HACK to avoid global registers View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/22ea9c296906ad3a8fed384bcf6fb35d4b6ca814 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/22ea9c296906ad3a8fed384bcf6fb35d4b6ca814 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 Sat Nov 28 20:42:59 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 15:42:59 -0500 Subject: [Git][ghc/ghc][master] 2 commits: Make primop handler indentation more consistent Message-ID: <5fc2b6533d0cf_86c111d4a007862e@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - 3 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/Prim.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -327,7 +327,7 @@ primop Int8NeOp "neInt8#" Compare Int8# -> Int8# -> Int# ------------------------------------------------------------------------ section "Word8#" - {Operations on 8-bit unsigned integers.} + {Operations on 8-bit unsigned words.} ------------------------------------------------------------------------ primtype Word8# @@ -409,7 +409,7 @@ primop Int16NeOp "neInt16#" Compare Int16# -> Int16# -> Int# ------------------------------------------------------------------------ section "Word16#" - {Operations on 16-bit unsigned integers.} + {Operations on 16-bit unsigned words.} ------------------------------------------------------------------------ primtype Word16# @@ -560,19 +560,19 @@ primop IntQuotRemOp "quotRemInt#" GenPrimOp {Rounds towards zero.} with can_fail = True -primop AndIOp "andI#" GenPrimOp Int# -> Int# -> Int# +primop IntAndOp "andI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "and".} with commutable = True -primop OrIOp "orI#" GenPrimOp Int# -> Int# -> Int# +primop IntOrOp "orI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "or".} with commutable = True -primop XorIOp "xorI#" GenPrimOp Int# -> Int# -> Int# +primop IntXorOp "xorI#" GenPrimOp Int# -> Int# -> Int# {Bitwise "xor".} with commutable = True -primop NotIOp "notI#" GenPrimOp Int# -> Int# +primop IntNotOp "notI#" GenPrimOp Int# -> Int# {Bitwise "not", also known as the binary complement.} primop IntNegOp "negateInt#" GenPrimOp Int# -> Int# @@ -632,13 +632,13 @@ primop IntToDoubleOp "int2Double#" GenPrimOp Int# -> Double# primop WordToFloatOp "word2Float#" GenPrimOp Word# -> Float# primop WordToDoubleOp "word2Double#" GenPrimOp Word# -> Double# -primop ISllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# +primop IntSllOp "uncheckedIShiftL#" GenPrimOp Int# -> Int# -> Int# {Shift left. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop ISraOp "uncheckedIShiftRA#" GenPrimOp Int# -> Int# -> Int# +primop IntSraOp "uncheckedIShiftRA#" GenPrimOp Int# -> Int# -> Int# {Shift right arithmetic. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop ISrlOp "uncheckedIShiftRL#" GenPrimOp Int# -> Int# -> Int# +primop IntSrlOp "uncheckedIShiftRL#" GenPrimOp Int# -> Int# -> Int# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} @@ -698,21 +698,21 @@ primop WordQuotRem2Op "quotRemWord2#" GenPrimOp Requires that high word < divisor.} with can_fail = True -primop AndOp "and#" GenPrimOp Word# -> Word# -> Word# +primop WordAndOp "and#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop OrOp "or#" GenPrimOp Word# -> Word# -> Word# +primop WordOrOp "or#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop XorOp "xor#" GenPrimOp Word# -> Word# -> Word# +primop WordXorOp "xor#" GenPrimOp Word# -> Word# -> Word# with commutable = True -primop NotOp "not#" GenPrimOp Word# -> Word# +primop WordNotOp "not#" GenPrimOp Word# -> Word# -primop SllOp "uncheckedShiftL#" GenPrimOp Word# -> Int# -> Word# +primop WordSllOp "uncheckedShiftL#" GenPrimOp Word# -> Int# -> Word# {Shift left logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} -primop SrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# +primop WordSrlOp "uncheckedShiftRL#" GenPrimOp Word# -> Int# -> Word# {Shift right logical. Result undefined if shift amount is not in the range 0 to word size - 1 inclusive.} ===================================== compiler/GHC/Core/Opt/ConstantFold.hs ===================================== @@ -135,24 +135,24 @@ primOpRules nm = \case retLit zeroi , equalArgs >> retLit zeroi , equalArgs >> retLit zeroi ] - AndIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.&.)) + IntAndOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.&.)) , idempotent , zeroElem zeroi ] - OrIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) + IntOrOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 (.|.)) , idempotent , identityPlatform zeroi ] - XorIOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) + IntXorOp -> mkPrimOpRule nm 2 [ binaryLit (intOp2 xor) , identityPlatform zeroi , equalArgs >> retLit zeroi ] - NotIOp -> mkPrimOpRule nm 1 [ unaryLit complementOp - , inversePrimOp NotIOp ] + IntNotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp IntNotOp ] IntNegOp -> mkPrimOpRule nm 1 [ unaryLit negOp , inversePrimOp IntNegOp ] - ISllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftL) + IntSllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftL) , rightIdentityPlatform zeroi ] - ISraOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftR) + IntSraOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt (const Bits.shiftR) , rightIdentityPlatform zeroi ] - ISrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt shiftRightLogical + IntSrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumInt shiftRightLogical , rightIdentityPlatform zeroi ] -- Word operations @@ -183,19 +183,19 @@ primOpRules nm = \case guard (l == onew platform) retLit zerow , equalArgs >> retLit zerow ] - AndOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.&.)) + WordAndOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.&.)) , idempotent , zeroElem zerow ] - OrOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) + WordOrOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 (.|.)) , idempotent , identityPlatform zerow ] - XorOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) + WordXorOp -> mkPrimOpRule nm 2 [ binaryLit (wordOp2 xor) , identityPlatform zerow , equalArgs >> retLit zerow ] - NotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp - , inversePrimOp NotOp ] - SllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord (const Bits.shiftL) ] - SrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] + WordNotOp -> mkPrimOpRule nm 1 [ unaryLit complementOp + , inversePrimOp WordNotOp ] + WordSllOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord (const Bits.shiftL) ] + WordSrlOp -> mkPrimOpRule nm 2 [ shiftRule LitNumWord shiftRightLogical ] -- coercions @@ -204,16 +204,16 @@ primOpRules nm = \case Int32ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendIntLit ] Int8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt8Lit , subsumedByPrimOp Int8NarrowOp - , narrowSubsumesAnd AndIOp Int8NarrowOp 8 ] + , narrowSubsumesAnd IntAndOp Int8NarrowOp 8 ] Int16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt16Lit , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp - , narrowSubsumesAnd AndIOp Int16NarrowOp 16 ] + , narrowSubsumesAnd IntAndOp Int16NarrowOp 16 ] Int32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowInt32Lit , subsumedByPrimOp Int8NarrowOp , subsumedByPrimOp Int16NarrowOp , subsumedByPrimOp Int32NarrowOp - , narrowSubsumesAnd AndIOp Int32NarrowOp 32 ] + , narrowSubsumesAnd IntAndOp Int32NarrowOp 32 ] Word8ExtendOp -> mkPrimOpRule nm 1 [ liftLitPlatform extendWordLit , extendNarrowPassthrough Word8NarrowOp 0xFF @@ -226,16 +226,16 @@ primOpRules nm = \case ] Word8NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord8Lit , subsumedByPrimOp Word8NarrowOp - , narrowSubsumesAnd AndOp Word8NarrowOp 8 ] + , narrowSubsumesAnd WordAndOp Word8NarrowOp 8 ] Word16NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord16Lit , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp - , narrowSubsumesAnd AndOp Word16NarrowOp 16 ] + , narrowSubsumesAnd WordAndOp Word16NarrowOp 16 ] Word32NarrowOp -> mkPrimOpRule nm 1 [ liftLit narrowWord32Lit , subsumedByPrimOp Word8NarrowOp , subsumedByPrimOp Word16NarrowOp , subsumedByPrimOp Word32NarrowOp - , narrowSubsumesAnd AndOp Word32NarrowOp 32 ] + , narrowSubsumesAnd WordAndOp Word32NarrowOp 32 ] WordToIntOp -> mkPrimOpRule nm 1 [ liftLitPlatform wordToIntLit @@ -246,34 +246,34 @@ primOpRules nm = \case , subsumedByPrimOp Narrow8IntOp , Narrow8IntOp `subsumesPrimOp` Narrow16IntOp , Narrow8IntOp `subsumesPrimOp` Narrow32IntOp - , narrowSubsumesAnd AndIOp Narrow8IntOp 8 ] + , narrowSubsumesAnd IntAndOp Narrow8IntOp 8 ] Narrow16IntOp -> mkPrimOpRule nm 1 [ liftLit narrow16IntLit , subsumedByPrimOp Narrow8IntOp , subsumedByPrimOp Narrow16IntOp , Narrow16IntOp `subsumesPrimOp` Narrow32IntOp - , narrowSubsumesAnd AndIOp Narrow16IntOp 16 ] + , narrowSubsumesAnd IntAndOp Narrow16IntOp 16 ] Narrow32IntOp -> mkPrimOpRule nm 1 [ liftLit narrow32IntLit , subsumedByPrimOp Narrow8IntOp , subsumedByPrimOp Narrow16IntOp , subsumedByPrimOp Narrow32IntOp , removeOp32 - , narrowSubsumesAnd AndIOp Narrow32IntOp 32 ] + , narrowSubsumesAnd IntAndOp Narrow32IntOp 32 ] Narrow8WordOp -> mkPrimOpRule nm 1 [ liftLit narrow8WordLit , subsumedByPrimOp Narrow8WordOp , Narrow8WordOp `subsumesPrimOp` Narrow16WordOp , Narrow8WordOp `subsumesPrimOp` Narrow32WordOp - , narrowSubsumesAnd AndOp Narrow8WordOp 8 ] + , narrowSubsumesAnd WordAndOp Narrow8WordOp 8 ] Narrow16WordOp -> mkPrimOpRule nm 1 [ liftLit narrow16WordLit , subsumedByPrimOp Narrow8WordOp , subsumedByPrimOp Narrow16WordOp , Narrow16WordOp `subsumesPrimOp` Narrow32WordOp - , narrowSubsumesAnd AndOp Narrow16WordOp 16 ] + , narrowSubsumesAnd WordAndOp Narrow16WordOp 16 ] Narrow32WordOp -> mkPrimOpRule nm 1 [ liftLit narrow32WordLit , subsumedByPrimOp Narrow8WordOp , subsumedByPrimOp Narrow16WordOp , subsumedByPrimOp Narrow32WordOp , removeOp32 - , narrowSubsumesAnd AndOp Narrow32WordOp 32 ] + , narrowSubsumesAnd WordAndOp Narrow32WordOp 32 ] OrdOp -> mkPrimOpRule nm 1 [ liftLit charToIntLit , inversePrimOp ChrOp ] ChrOp -> mkPrimOpRule nm 1 [ do [Lit lit] <- getArgs @@ -529,8 +529,8 @@ shiftRule :: LitNumType -- Type of the result, either LitNumInt or LitNumWord -> RuleM CoreExpr -- Shifts take an Int; hence third arg of op is Int -- Used for shift primops --- ISllOp, ISraOp, ISrlOp :: Int# -> Int# -> Int# --- SllOp, SrlOp :: Word# -> Int# -> Word# +-- IntSllOp, IntSraOp, IntSrlOp :: Int# -> Int# -> Int# +-- SllOp, SrlOp :: Word# -> Int# -> Word# shiftRule lit_num_ty shift_op = do { platform <- getPlatform ; [e1, Lit (LitNumber LitNumInt shift_len)] <- getArgs @@ -754,7 +754,7 @@ extendNarrowPassthrough :: PrimOp -> Integer -> RuleM CoreExpr extendNarrowPassthrough narrow_primop n = do [Var primop_id `App` x] <- getArgs matchPrimOpId narrow_primop primop_id - return (Var (mkPrimOpId AndOp) `App` x `App` Lit (LitNumber LitNumWord n)) + return (Var (mkPrimOpId WordAndOp) `App` x `App` Lit (LitNumber LitNumWord n)) -- | narrow subsumes bitwise `and` with full mask (cf #16402): -- @@ -851,7 +851,7 @@ transform the invalid shift into an "obviously incorrect" value. There are two cases: -- Shifting fixed-width things: the primops ISll, Sll, etc +- Shifting fixed-width things: the primops IntSll, Sll, etc These are handled by shiftRule. We are happy to shift by any amount up to wordSize but no more. @@ -1381,7 +1381,7 @@ builtinRules enableBignumRules [arg, Lit (LitNumber LitNumInt d)] <- getArgs Just n <- return $ exactLog2 d platform <- getPlatform - return $ Var (mkPrimOpId ISraOp) `App` arg `App` mkIntVal platform n + return $ Var (mkPrimOpId IntSraOp) `App` arg `App` mkIntVal platform n ], mkBasicRule modIntName 2 $ msum @@ -1391,7 +1391,7 @@ builtinRules enableBignumRules [arg, Lit (LitNumber LitNumInt d)] <- getArgs Just _ <- return $ exactLog2 d platform <- getPlatform - return $ Var (mkPrimOpId AndIOp) + return $ Var (mkPrimOpId IntAndOp) `App` arg `App` mkIntVal platform (d - 1) ] ] @@ -2365,8 +2365,8 @@ adjustDyadicRight op lit IntAddOp -> Just (\y -> y-lit ) WordSubOp -> Just (\y -> y+lit ) IntSubOp -> Just (\y -> y+lit ) - XorOp -> Just (\y -> y `xor` lit) - XorIOp -> Just (\y -> y `xor` lit) + WordXorOp -> Just (\y -> y `xor` lit) + IntXorOp -> Just (\y -> y `xor` lit) _ -> Nothing adjustDyadicLeft :: Integer -> PrimOp -> Maybe (Integer -> Integer) @@ -2377,8 +2377,8 @@ adjustDyadicLeft lit op IntAddOp -> Just (\y -> y-lit ) WordSubOp -> Just (\y -> lit-y ) IntSubOp -> Just (\y -> lit-y ) - XorOp -> Just (\y -> y `xor` lit) - XorIOp -> Just (\y -> y `xor` lit) + WordXorOp -> Just (\y -> y `xor` lit) + IntXorOp -> Just (\y -> y `xor` lit) _ -> Nothing @@ -2386,8 +2386,8 @@ adjustUnary :: PrimOp -> Maybe (Integer -> Integer) -- Given (op x) return a function 'f' s.t. f (op x) = x adjustUnary op = case op of - NotOp -> Just (\y -> complement y) - NotIOp -> Just (\y -> complement y) + WordNotOp -> Just (\y -> complement y) + IntNotOp -> Just (\y -> complement y) IntNegOp -> Just (\y -> negate y ) _ -> Nothing ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1147,12 +1147,12 @@ emitPrimOp dflags primop = case primop of AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - AndOp -> \args -> opTranslate args (mo_wordAnd platform) - OrOp -> \args -> opTranslate args (mo_wordOr platform) - XorOp -> \args -> opTranslate args (mo_wordXor platform) - NotOp -> \args -> opTranslate args (mo_wordNot platform) - SllOp -> \args -> opTranslate args (mo_wordShl platform) - SrlOp -> \args -> opTranslate args (mo_wordUShr platform) + WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) + WordOrOp -> \args -> opTranslate args (mo_wordOr platform) + WordXorOp -> \args -> opTranslate args (mo_wordXor platform) + WordNotOp -> \args -> opTranslate args (mo_wordNot platform) + WordSllOp -> \args -> opTranslate args (mo_wordShl platform) + WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) @@ -1169,13 +1169,13 @@ emitPrimOp dflags primop = case primop of IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - AndIOp -> \args -> opTranslate args (mo_wordAnd platform) - OrIOp -> \args -> opTranslate args (mo_wordOr platform) - XorIOp -> \args -> opTranslate args (mo_wordXor platform) - NotIOp -> \args -> opTranslate args (mo_wordNot platform) - ISllOp -> \args -> opTranslate args (mo_wordShl platform) - ISraOp -> \args -> opTranslate args (mo_wordSShr platform) - ISrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) + IntOrOp -> \args -> opTranslate args (mo_wordOr platform) + IntXorOp -> \args -> opTranslate args (mo_wordXor platform) + IntNotOp -> \args -> opTranslate args (mo_wordNot platform) + IntSllOp -> \args -> opTranslate args (mo_wordShl platform) + IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) + IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) -- Native word unsigned ops @@ -1213,67 +1213,67 @@ emitPrimOp dflags primop = case primop of -- Word8# unsigned ops - Word8ExtendOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - Word8NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) - Word8NotOp -> \args -> opTranslate args (MO_Not W8) - Word8AddOp -> \args -> opTranslate args (MO_Add W8) - Word8SubOp -> \args -> opTranslate args (MO_Sub W8) - Word8MulOp -> \args -> opTranslate args (MO_Mul W8) - Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) - Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) - - Word8EqOp -> \args -> opTranslate args (MO_Eq W8) - Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) - Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) - Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) - Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) - Word8NeOp -> \args -> opTranslate args (MO_Ne W8) + Word8ExtendOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) + Word8NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) + Word8NotOp -> \args -> opTranslate args (MO_Not W8) + Word8AddOp -> \args -> opTranslate args (MO_Add W8) + Word8SubOp -> \args -> opTranslate args (MO_Sub W8) + Word8MulOp -> \args -> opTranslate args (MO_Mul W8) + Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) + Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) + + Word8EqOp -> \args -> opTranslate args (MO_Eq W8) + Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) + Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) + Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) + Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) + Word8NeOp -> \args -> opTranslate args (MO_Ne W8) -- Int16# signed ops - Int16ExtendOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - Int16NarrowOp -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) - Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) - Int16AddOp -> \args -> opTranslate args (MO_Add W16) - Int16SubOp -> \args -> opTranslate args (MO_Sub W16) - Int16MulOp -> \args -> opTranslate args (MO_Mul W16) - Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) - Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) - - Int16EqOp -> \args -> opTranslate args (MO_Eq W16) - Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) - Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) - Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) - Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) - Int16NeOp -> \args -> opTranslate args (MO_Ne W16) + Int16ExtendOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) + Int16NarrowOp -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) + Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) + Int16AddOp -> \args -> opTranslate args (MO_Add W16) + Int16SubOp -> \args -> opTranslate args (MO_Sub W16) + Int16MulOp -> \args -> opTranslate args (MO_Mul W16) + Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) + Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) + + Int16EqOp -> \args -> opTranslate args (MO_Eq W16) + Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) + Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) + Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) + Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) + Int16NeOp -> \args -> opTranslate args (MO_Ne W16) -- Word16# unsigned ops - Word16ExtendOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - Word16NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) - Word16NotOp -> \args -> opTranslate args (MO_Not W16) - Word16AddOp -> \args -> opTranslate args (MO_Add W16) - Word16SubOp -> \args -> opTranslate args (MO_Sub W16) - Word16MulOp -> \args -> opTranslate args (MO_Mul W16) - Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) - Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) - - Word16EqOp -> \args -> opTranslate args (MO_Eq W16) - Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) - Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) - Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) - Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) - Word16NeOp -> \args -> opTranslate args (MO_Ne W16) + Word16ExtendOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) + Word16NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) + Word16NotOp -> \args -> opTranslate args (MO_Not W16) + Word16AddOp -> \args -> opTranslate args (MO_Add W16) + Word16SubOp -> \args -> opTranslate args (MO_Sub W16) + Word16MulOp -> \args -> opTranslate args (MO_Mul W16) + Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) + Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) + + Word16EqOp -> \args -> opTranslate args (MO_Eq W16) + Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) + Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) + Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) + Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) + Word16NeOp -> \args -> opTranslate args (MO_Ne W16) -- Int32# signed ops - Int32ExtendOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - Int32NarrowOp -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) + Int32ExtendOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) + Int32NarrowOp -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) -- Word32# unsigned ops - Word32ExtendOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) - Word32NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) + Word32ExtendOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) + Word32NarrowOp -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) -- Char# ops View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22ea9c296906ad3a8fed384bcf6fb35d4b6ca814...c82bc8e9d444d6d61198f3bfbcc7c5bb5f6ce13c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/22ea9c296906ad3a8fed384bcf6fb35d4b6ca814...c82bc8e9d444d6d61198f3bfbcc7c5bb5f6ce13c 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 Sat Nov 28 20:43:33 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sat, 28 Nov 2020 15:43:33 -0500 Subject: [Git][ghc/ghc][master] testsuite: Mark T14702 as fragile on Windows Message-ID: <5fc2b67589e4d_86c3fc6a6aa1b24788948@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 1 changed file: - testsuite/tests/rts/all.T Changes: ===================================== testsuite/tests/rts/all.T ===================================== @@ -359,6 +359,7 @@ test('T14497', [omit_ways(['profasm']), multi_cpu_race], compile_and_run, ['-O'] test('T14695', [normal, ignore_stderr], makefile_test, ['T14695']) test('T14702', [ ignore_stdout , when(unregisterised(), skip) + , when(opsys('mingw32'), fragile(18953)) , only_ways(['threaded1', 'threaded2']) , extra_run_opts('+RTS -A32m -N8 -T -RTS') ] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ae14f160c64d20880486ba365348ef3900c84a60 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ae14f160c64d20880486ba365348ef3900c84a60 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 Sat Nov 28 23:48:50 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 18:48:50 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] 10 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc2e1e2a8ace_86ce89fc5c791171@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - d891d942 by John Ericson at 2020-11-28T23:48:23+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - libraries/array - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/binary - libraries/bytestring - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/98a3e44192a957a650bf1eeb9790e53efbdb65a1...d891d9423957e052d81a6807691f6cf013eaa84b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/98a3e44192a957a650bf1eeb9790e53efbdb65a1...d891d9423957e052d81a6807691f6cf013eaa84b 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 Sat Nov 28 23:49:16 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 18:49:16 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/interal-primop-naming-consistency Message-ID: <5fc2e1fc84660_86cf5745687916cc@gitlab.mail> John Ericson deleted branch wip/interal-primop-naming-consistency at Glasgow Haskell Compiler / GHC -- 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 Sat Nov 28 23:49:54 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 18:49:54 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/fix-64-toArgRep Message-ID: <5fc2e222c1f78_86cf5745687918b5@gitlab.mail> John Ericson deleted branch wip/fix-64-toArgRep at Glasgow Haskell Compiler / GHC -- 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 Sat Nov 28 23:52:24 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 18:52:24 -0500 Subject: [Git][ghc/ghc][wip/fixed-width-lits] 11 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc2e2b89cbb0_86c3fc6a6aa1b24792039@gitlab.mail> John Ericson pushed to branch wip/fixed-width-lits at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - d891d942 by John Ericson at 2020-11-28T23:48:23+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 4d6a5a08 by Sylvain Henry at 2020-11-28T23:50:24+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 29 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - libraries/array - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/binary - libraries/bytestring - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/044908fdf542d2b4b2001760fd407abb830d1a8f...4d6a5a08fed7d8ca83423010b1426ad87687c9c1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/044908fdf542d2b4b2001760fd407abb830d1a8f...4d6a5a08fed7d8ca83423010b1426ad87687c9c1 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 Sun Nov 29 02:17:43 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 21:17:43 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere] 17 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc304c759c0d_86ce89fc5c793741@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - d891d942 by John Ericson at 2020-11-28T23:48:23+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 4d6a5a08 by Sylvain Henry at 2020-11-28T23:50:24+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 7aaba66d by John Ericson at 2020-11-28T23:50:24+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 7b485b79 by John Ericson at 2020-11-28T23:50:24+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 043b3f3d by Sylvain Henry at 2020-11-28T23:50:24+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - b0c80603 by John Ericson at 2020-11-28T23:50:24+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 54559349 by John Ericson at 2020-11-28T23:50:24+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 7135eb06 by John Ericson at 2020-11-28T23:50:24+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - includes/stg/Prim.h - libraries/array - libraries/base/GHC/Exts.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/56a2ac3d302a5c6f949264877e999f2789efecc8...7135eb06cf3e45edc85bffe299b7d0890aded7d1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/56a2ac3d302a5c6f949264877e999f2789efecc8...7135eb06cf3e45edc85bffe299b7d0890aded7d1 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 Sun Nov 29 02:18:11 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sat, 28 Nov 2020 21:18:11 -0500 Subject: [Git][ghc/ghc][wip/int64-everywhere-new-float-primops] 18 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc304e33517f_86c3fc6a6aa1b24794540@gitlab.mail> John Ericson pushed to branch wip/int64-everywhere-new-float-primops at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - d891d942 by John Ericson at 2020-11-28T23:48:23+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 4d6a5a08 by Sylvain Henry at 2020-11-28T23:50:24+00:00 Make proper fixed-with number literals (Progress towards #11953, #17377, #17375) Besides being nicer to use, this also will allow for better constant folding for the fixed-width types, on par with what `Int#` and `Word#` have today. - - - - - 7aaba66d by John Ericson at 2020-11-28T23:50:24+00:00 Make fixed-size `Int32#` and `Int64#` The boxed Int64 uses Int64#, but Int32# still uses Int#. The 32-bit case is less pressing to change because it is not a source of brittle CPP---it is the same thing on all platforms. We need Int64/Word64 constant folding to avoid the let/app restriction on Core, so that is implemented now. 32-bit constant unfolding and 32-bit literals are left as follow-up. This is the bulk of #11953 Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 7b485b79 by John Ericson at 2020-11-28T23:50:24+00:00 Inline INT64 and WORD64 macros in primops.txt.pp The definition is now unconditional so there is no reason for that CPP. - - - - - 043b3f3d by Sylvain Henry at 2020-11-28T23:50:24+00:00 Adapt rules from #16402 to Word64#/Int64# - - - - - b0c80603 by John Ericson at 2020-11-28T23:50:24+00:00 Copy enumFrom* implementations from Int/Word for Int64/Word64 Without this, we don't get proper list fusion. I think this sort of copying is OK for now, but we absolutely need something better if we are going to make `IntN` use `IntN#` for all `N`. The degree to which proper metaprogramming has been punted upon by factoring everything through the native-sized types is disconcerting. - - - - - 54559349 by John Ericson at 2020-11-28T23:50:24+00:00 `integerFromInt64#` can be inlined when the word size is >= 64 bits Maybe this will help with the renaming test failure? - - - - - 7135eb06 by John Ericson at 2020-11-28T23:50:24+00:00 Add builtin rule for `divInt64#` and `modInt64#` - - - - - f82c273c by John Ericson at 2020-11-28T23:50:24+00:00 WIP: Add missing floats <-> int/word 64 rule and primops - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/CPrim.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/SPARC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Platform.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Utils/Outputable.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - includes/stg/Prim.h - libraries/array The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/674bde54111594967b8f7494bd741cb7464d7f3b...f82c273ce0c3b3033698e64fd21e2f7dc858016a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/674bde54111594967b8f7494bd741cb7464d7f3b...f82c273ce0c3b3033698e64fd21e2f7dc858016a 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 Sun Nov 29 06:50:15 2020 From: gitlab at gitlab.haskell.org (John Ericson) Date: Sun, 29 Nov 2020 01:50:15 -0500 Subject: [Git][ghc/ghc][wip/primop-naming-consistency] Cleanup number primop conversion names Message-ID: <5fc344a76b3a8_86cf7c522c797952@gitlab.mail> John Ericson pushed to branch wip/primop-naming-consistency at Glasgow Haskell Compiler / GHC Commits: a1ac0418 by John Ericson at 2020-11-29T06:49:51+00:00 Cleanup number primop conversion names Don't use "extend" or "narrow" in some of the user-facing primops names for conversions. - Names like `narrowInt32#` are misleading when `Int` is 32-bits. - Names like `extendInt64#` are flat-out wrong when `Int is 32-bits. - `narrow{Int,Word}<N>#` however map a type to itself, and so don't suffer from this problem. They are left as-is. - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Deriv/Generate.hs - libraries/array - libraries/base/GHC/IO/Encoding/CodePage.hs - libraries/base/GHC/IO/Encoding/UTF16.hs - libraries/base/GHC/IO/Encoding/UTF32.hs - libraries/base/GHC/IO/Encoding/UTF8.hs - libraries/base/GHC/Int.hs - libraries/base/GHC/Storable.hs - libraries/base/GHC/Word.hs - libraries/binary - libraries/bytestring - libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/BreakArray.hs - libraries/text - testsuite/tests/array/should_run/arr020.hs - testsuite/tests/cmm/opt/T18141.hs - testsuite/tests/codeGen/should_compile/T18614.hs - testsuite/tests/codeGen/should_run/cgrun070.hs - testsuite/tests/codeGen/should_run/cgrun072.hs - testsuite/tests/codeGen/should_run/cgrun075.hs - testsuite/tests/codeGen/should_run/cgrun076.hs - testsuite/tests/codeGen/should_run/compareByteArrays.hs - testsuite/tests/ffi/should_run/PrimFFIInt16.hs - testsuite/tests/ffi/should_run/PrimFFIInt8.hs - testsuite/tests/ffi/should_run/PrimFFIWord16.hs - testsuite/tests/ffi/should_run/PrimFFIWord8.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1ac041835e2c6aa4a4e10727015a6c0604360e7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a1ac041835e2c6aa4a4e10727015a6c0604360e7 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 Sun Nov 29 14:53:04 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 09:53:04 -0500 Subject: [Git][ghc/ghc][wip/unloading-fixes] 13 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc3b5d08087_86c111d4a0080993f@gitlab.mail> Ben Gamari pushed to branch wip/unloading-fixes at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 5bf85a6f by Ben Gamari at 2020-11-29T09:52:59-05:00 rts/linker: Don't allow shared libraries to be loaded multiple times - - - - - be6b148c by Ben Gamari at 2020-11-29T09:52:59-05:00 rts/linker: Initialise CCSs from native shared objects - - - - - 39e08bb5 by Ben Gamari at 2020-11-29T09:52:59-05:00 rts/linker: Move shared library loading logic into Elf.c - - - - - bf272659 by GHC GitLab CI at 2020-11-29T09:52:59-05:00 rts/linker: Don't declare dynamic objects with image_mapped This previously resulted in warnings due to spurious unmap failures. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs - rts/Heap.c - rts/Linker.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53522ffc245d8909bd86f0092e6791ce36bf7467...bf27265901c7a8ff2facbdcd3a1710905576d88e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53522ffc245d8909bd86f0092e6791ce36bf7467...bf27265901c7a8ff2facbdcd3a1710905576d88e 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 Sun Nov 29 14:53:19 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 29 Nov 2020 09:53:19 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 19 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc3b5dfcede3_86c157b6ce4814664@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - fa760ccc by Ben Gamari at 2020-11-29T09:53:11-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - 4fe6a8b4 by GHC GitLab CI at 2020-11-29T09:53:12-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - c5000ab5 by GHC GitLab CI at 2020-11-29T09:53:12-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - a0262806 by GHC GitLab CI at 2020-11-29T09:53:12-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 72c4c6de by GHC GitLab CI at 2020-11-29T09:53:12-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - cc0030c6 by GHC GitLab CI at 2020-11-29T09:53:12-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 60c68389 by GHC GitLab CI at 2020-11-29T09:53:12-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - 4b26ec51 by GHC GitLab CI at 2020-11-29T09:53:12-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 2f49bd67 by Ben Gamari at 2020-11-29T09:53:12-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 1d18e37b by GHC GitLab CI at 2020-11-29T09:53:12-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Utils/Error.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - includes/rts/storage/ClosureMacros.h - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0395b1b2b4fc9a74c37f0c253a2bdbe5c6090951...1d18e37b595c91f6fd4ab8b50fdd6f747b5fa235 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0395b1b2b4fc9a74c37f0c253a2bdbe5c6090951...1d18e37b595c91f6fd4ab8b50fdd6f747b5fa235 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 Sun Nov 29 14:56:19 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 09:56:19 -0500 Subject: [Git][ghc/ghc][wip/m32-fixes] 29 commits: Bump time submodule to 1.11.1 Message-ID: <5fc3b693acc58_86cf7c522c8148b9@gitlab.mail> Ben Gamari pushed to branch wip/m32-fixes at Glasgow Haskell Compiler / GHC Commits: 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 085bfdeb by Ben Gamari at 2020-11-29T09:56:17-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/Base.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToCmm/Ticky.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52cf9952776b551a4dbed418c1276df73e7427a2...085bfdebbfc01e1d43d37530bf242571c0c7df1b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/52cf9952776b551a4dbed418c1276df73e7427a2...085bfdebbfc01e1d43d37530bf242571c0c7df1b 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 Sun Nov 29 15:20:09 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 10:20:09 -0500 Subject: [Git][ghc/ghc][wip/gc/nonmoving-pinned] 641 commits: Fix typo in haddock Message-ID: <5fc3bc2937e9a_86c879fa9c81662f@gitlab.mail> Ben Gamari pushed to branch wip/gc/nonmoving-pinned at Glasgow Haskell Compiler / GHC Commits: 318bb17c by Oleg Grenrus at 2020-07-28T20:54:13-04:00 Fix typo in haddock Spotted by `vilpan` on `#haskell` - - - - - 39c89862 by Sergei Trofimovich at 2020-07-28T20:54:50-04:00 ghc/mk: don't build gmp packages for BIGNUM_BACKEND=native Before this change make-based `BIGNUM_BACKEND=native` build was failing as: ``` x86_64-pc-linux-gnu-gcc: error: libraries/ghc-bignum/gmp/objs/*.o: No such file or directory ``` This happens because ghc.mk was pulling in gmp-dependent ghc-bignum library unconditionally. The change avoid building ghc-bignum. Bug: https://gitlab.haskell.org/ghc/ghc/-/issues/18437 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - b9a880fc by Felix Wiemuth at 2020-07-29T15:06:35-04:00 Fix typo - - - - - c59064b0 by Brandon Chinn at 2020-07-29T15:07:11-04:00 Add regression test for #16341 - - - - - a61411ca by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass dit_rep_tc_args to dsm_stock_gen_fn - - - - - a26498da by Brandon Chinn at 2020-07-29T15:07:11-04:00 Pass tc_args to gen_fn - - - - - 44b11bad by Brandon Chinn at 2020-07-29T15:07:11-04:00 Filter out unreachable constructors when deriving stock instances (#16431) - - - - - bbc51916 by Simon Peyton Jones at 2020-07-29T15:07:47-04:00 Kill off sc_mult and as_mult fields They are readily derivable from other fields, so this is more efficient, and less error prone. Fixes #18494 - - - - - e3db4b4c by Peter Trommler at 2020-07-29T15:08:22-04:00 configure: Fix build system on ARM - - - - - 96c31ea1 by Sylvain Henry at 2020-07-29T15:09:02-04:00 Fix bug in Natural multiplication (fix #18509) A bug was lingering in Natural multiplication (inverting two limbs) despite QuickCheck tests used during the development leading to wrong results (independently of the selected backend). - - - - - e1dc3d7b by Krzysztof Gogolewski at 2020-07-29T15:09:39-04:00 Fix validation errors (#18510) Test T2632 is a stage1 test that failed because of the Q => Quote change. The remaining tests did not use quotation and failed when the path contained a space. - - - - - 6c68a842 by John Ericson at 2020-07-30T07:11:02-04:00 For `-fkeep-going` do not duplicate dependency edge code We now compute the deps for `-fkeep-going` the same way that the original graph calculates them, so the edges are correct. Upsweep really ought to take the graph rather than a topological sort so we are never recalculating anything, but at least things are recaluclated consistently now. - - - - - 502de556 by cgibbard at 2020-07-30T07:11:02-04:00 Add haddock comment for unfilteredEdges and move the note about drop_hs_boot_nodes into it. - - - - - 01c948eb by Ryan Scott at 2020-07-30T07:11:37-04:00 Clean up the inferred type variable restriction This patch primarily: * Documents `checkInferredVars` (previously called `check_inferred_vars`) more carefully. This is the function which throws an error message if a user quantifies an inferred type variable in a place where specificity cannot be observed. See `Note [Unobservably inferred type variables]` in `GHC.Rename.HsType`. Note that I now invoke `checkInferredVars` _alongside_ `rnHsSigType`, `rnHsWcSigType`, etc. rather than doing so _inside_ of these functions. This results in slightly more call sites for `checkInferredVars`, but it makes it much easier to enumerate the spots where the inferred type variable restriction comes into effect. * Removes the inferred type variable restriction for default method type signatures, per the discussion in #18432. As a result, this patch fixes #18432. Along the way, I performed some various cleanup: * I moved `no_nested_foralls_contexts_err` into `GHC.Rename.Utils` (under the new name `noNestedForallsContextsErr`), since it now needs to be invoked from multiple modules. I also added a helper function `addNoNestedForallsContextsErr` that throws the error message after producing it, as this is a common idiom. * In order to ensure that users cannot sneak inferred type variables into `SPECIALISE instance` pragmas by way of nested `forall`s, I now invoke `addNoNestedForallsContextsErr` when renaming `SPECIALISE instance` pragmas, much like when we rename normal instance declarations. (This probably should have originally been done as a part of the fix for #18240, but this task was somehow overlooked.) As a result, this patch fixes #18455 as a side effect. - - - - - d47324ce by Ryan Scott at 2020-07-30T07:12:16-04:00 Don't mark closed type family equations as occurrences Previously, `rnFamInstEqn` would mark the name of the type/data family used in an equation as an occurrence, regardless of what sort of family it is. Most of the time, this is the correct thing to do. The exception is closed type families, whose equations constitute its definition and therefore should not be marked as occurrences. Overzealously counting the equations of a closed type family as occurrences can cause certain warnings to not be emitted, as observed in #18470. See `Note [Type family equations and occurrences]` in `GHC.Rename.Module` for the full story. This fixes #18470 with a little bit of extra-casing in `rnFamInstEqn`. To accomplish this, I added an extra `ClosedTyFamInfo` field to the `NonAssocTyFamEqn` constructor of `AssocTyFamInfo` and refactored the relevant call sites accordingly so that this information is propagated to `rnFamInstEqn`. While I was in town, I moved `wrongTyFamName`, which checks that the name of a closed type family matches the name in an equation for that family, from the renamer to the typechecker to avoid the need for an `ASSERT`. As an added bonus, this lets us simplify the details of `ClosedTyFamInfo` a bit. - - - - - ebe2cf45 by Simon Peyton Jones at 2020-07-30T07:12:52-04:00 Remove an incorrect WARN in extendLocalRdrEnv I noticed this warning going off, and discovered that it's really fine. This small patch removes the warning, and docments what is going on. - - - - - 9f71f697 by Simon Peyton Jones at 2020-07-30T07:13:27-04:00 Add two bangs to improve perf of flattening This tiny patch improves the compile time of flatten-heavy programs by 1-2%, by adding two bangs. Addresses (somewhat) #18502 This reduces allocation by T9872b -1.1% T9872d -3.3% T5321Fun -0.2% T5631 -0.2% T5837 +0.1% T6048 +0.1% Metric Decrease: T9872b T9872d - - - - - 7c274cd5 by Sylvain Henry at 2020-07-30T22:54:48-04:00 Fix minimal imports dump for boot files (fix #18497) - - - - - 175cb5b4 by Sylvain Henry at 2020-07-30T22:55:25-04:00 DynFlags: don't use sdocWithDynFlags in datacon ppr We don't need to use `sdocWithDynFlags` to know whether we should display linear types for datacon types, we already have `sdocLinearTypes` field in `SDocContext`. Moreover we want to remove `sdocWithDynFlags` (#10143, #17957)). - - - - - 380638a3 by Sylvain Henry at 2020-07-30T22:56:03-04:00 Bignum: fix powMod for gmp backend (#18515) Also reenable integerPowMod test which had never been reenabled by mistake. - - - - - 56a7c193 by Sylvain Henry at 2020-07-31T19:32:09+02:00 Refactor CLabel pretty-printing Pretty-printing CLabel relies on sdocWithDynFlags that we want to remove (#10143, #17957). It uses it to query the backend and the platform. This patch exposes Clabel ppr functions specialised for each backend so that backend code can directly use them. - - - - - 3b15dc3c by Sylvain Henry at 2020-07-31T19:32:09+02:00 DynFlags: don't use sdocWithDynFlags in GHC.CmmToAsm.Dwarf.Types - - - - - e30fed6c by Vladislav Zavialov at 2020-08-01T04:23:04-04:00 Test case for #17652 The issue was fixed by 19e80b9af252eee760dc047765a9930ef00067ec - - - - - 22641742 by Ryan Scott at 2020-08-02T16:44:11-04:00 Remove ConDeclGADTPrefixPs This removes the `ConDeclGADTPrefixPs` per the discussion in #18517. Most of this patch simply removes code, although the code in the `rnConDecl` case for `ConDeclGADTPrefixPs` had to be moved around a bit: * The nested `forall`s check now lives in the `rnConDecl` case for `ConDeclGADT`. * The `LinearTypes`-specific code that used to live in the `rnConDecl` case for `ConDeclGADTPrefixPs` now lives in `GHC.Parser.PostProcess.mkGadtDecl`, which is now monadic so that it can check if `-XLinearTypes` is enabled. Fixes #18157. - - - - - f2d1accf by Leon Schoorl at 2020-08-02T16:44:47-04:00 Fix GHC_STAGE definition generated by make Fixes #18070 GHC_STAGE is the stage of the compiler we're building, it should be 1,2(,3?). But make was generating 0 and 1. Hadrian does this correctly using a similar `+ 1`: https://gitlab.haskell.org/ghc/ghc/-/blob/eb8115a8c4cbc842b66798480fefc7ab64d31931/hadrian/src/Rules/Generate.hs#L245 - - - - - 947206f4 by Niklas Hambüchen at 2020-08-03T07:52:33+02:00 hadrian: Fix running stage0/bin/ghc with wrong package DB. Fixes #17468. In the invocation of `cabal configure`, `--ghc-pkg-option=--global-package-db` was already given correctly to tell `stage0/bin/ghc-pkg` that it should use the package DB in `stage1/`. However, `ghc` needs to be given this information as well, not only `ghc-pkg`! Until now that was not the case; the package DB in `stage0` was given to `ghc` instead. This was wrong, because there is no binary compatibility guarantee that says that the `stage0` DB's `package.cache` (which is written by the stage0 == system-provided ghc-pkg) can be deserialised by the `ghc-pkg` from the source code tree. As a result, when trying to add fields to `InstalledPackageInfo` that get serialised into / deserialised from the `package.cache`, errors like _build/stage0/lib/package.conf.d/package.cache: GHC.PackageDb.readPackageDb: inappropriate type (Not a valid Unicode code point!) would appear. This was because the `stage0/bin/ghc would try to deserialise the newly added fields from `_build/stage0/lib/package.conf.d/package.cache`, but they were not in there because the system `ghc-pkg` doesn't know about them and thus didn't write them there. It would try to do that because any GHC by default tries to read the global package db in `../lib/package.conf.d/package.cache`. For `stage0/bin/ghc` that *can never work* as explained above, so we must disable this default via `-no-global-package-db` and give it the correct package DB explicitly. This is the same problem as #16534, and the same fix as in MR !780 (but in another context; that one was for developers trying out the `stage0/bin/ghc` == `_build/ghc-stage1` interactively, while this fix is for a `cabal configure` invocation). I also noticed that the fix for #16534 forgot to pass `-no-global-package-db`, and have fixed that in this commit as well. It only worked until now because nobody tried to add a new ghc-pkg `.conf` field since the introduction of Hadrian. - - - - - ef2ae81a by Alex Biehl at 2020-08-03T07:52:33+02:00 Hardcode RTS includes to cope with unregistered builds - - - - - d613ed76 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add backward compat integer-gmp functions Also enhance bigNatCheck# and isValidNatural test - - - - - 3f2f7718 by Sylvain Henry at 2020-08-05T03:59:27-04:00 Bignum: add more BigNat compat functions in integer-gmp - - - - - 5e12cd17 by Krzysztof Gogolewski at 2020-08-05T04:00:04-04:00 Rename Core.Opt.Driver -> Core.Opt.Pipeline Closes #18504. - - - - - 2bff2f87 by Ben Gamari at 2020-08-05T04:00:39-04:00 Revert "iserv: Don't pass --export-dynamic on FreeBSD" This reverts commit 2290eb02cf95e9cfffcb15fc9c593d5ef79c75d9. - - - - - 53ce0db5 by Ben Gamari at 2020-08-05T04:00:39-04:00 Refactor handling of object merging Previously to merge a set of object files we would invoke the linker as usual, adding -r to the command-line. However, this can result in non-sensical command-lines which causes lld to balk (#17962). To avoid this we introduce a new tool setting into GHC, -pgmlm, which is the linker which we use to merge object files. - - - - - eb7013c3 by Hécate at 2020-08-05T04:01:15-04:00 Remove all the unnecessary LANGUAGE pragmas - - - - - fbcb886d by Ryan Scott at 2020-08-05T04:01:51-04:00 Make CodeQ and TExpQ levity polymorphic The patch is quite straightforward. The only tricky part is that `Language.Haskell.TH.Lib.Internal` now must be `Trustworthy` instead of `Safe` due to the `GHC.Exts` import (in order to import `TYPE`). Since `CodeQ` has yet to appear in any released version of `template-haskell`, I didn't bother mentioning the change to `CodeQ` in the `template-haskell` release notes. Fixes #18521. - - - - - 686e06c5 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Grammar for types and data/newtype constructors Before this patch, we parsed types into a reversed sequence of operators and operands. For example, (F x y + G a b * X) would be parsed as [X, *, b, a, G, +, y, x, F], using a simple grammar: tyapps : tyapp | tyapps tyapp tyapp : atype | PREFIX_AT atype | tyop | unpackedness Then we used a hand-written state machine to assemble this either into a type, using 'mergeOps', or into a constructor, using 'mergeDataCon'. This is due to a syntactic ambiguity: data T1 a = MkT1 a data T2 a = Ord a => MkT2 a In T1, what follows after the = sign is a data/newtype constructor declaration. However, in T2, what follows is a type (of kind Constraint). We don't know which of the two we are parsing until we encounter =>, and we cannot check for => without unlimited lookahead. This poses a few issues when it comes to e.g. infix operators: data I1 = Int :+ Bool :+ Char -- bad data I2 = Int :+ Bool :+ Char => MkI2 -- fine By this issue alone we are forced into parsing into an intermediate representation and doing a separate validation pass. However, should that intermediate representation be as low-level as a flat sequence of operators and operands? Before GHC Proposal #229, the answer was Yes, due to some particularly nasty corner cases: data T = ! A :+ ! B -- used to be fine, hard to parse data T = ! A :+ ! B => MkT -- bad However, now the answer is No, as this corner case is gone: data T = ! A :+ ! B -- bad data T = ! A :+ ! B => MkT -- bad This means we can write a proper grammar for types, overloading it in the DisambECP style, see Note [Ambiguous syntactic categories]. With this patch, we introduce a new class, DisambTD. Just like DisambECP is used to disambiguate between expressions, commands, and patterns, DisambTD is used to disambiguate between types and data/newtype constructors. This way, we get a proper, declarative grammar for constructors and types: infixtype : ftype | ftype tyop infixtype | unpackedness infixtype ftype : atype | tyop | ftype tyarg | ftype PREFIX_AT tyarg tyarg : atype | unpackedness atype And having a grammar for types means we are a step closer to using a single grammar for types and expressions. - - - - - 6770e199 by Vladislav Zavialov at 2020-08-06T13:34:05-04:00 Clean up the story around runPV/runECP_P/runECP_PV This patch started as a small documentation change, an attempt to make Note [Parser-Validator] and Note [Ambiguous syntactic categories] more clear and up-to-date. But it turned out that runECP_P/runECP_PV are weakly motivated, and it's easier to remove them than to find a good rationale/explanation for their existence. As the result, there's a bit of refactoring in addition to a documentation update. - - - - - 826d07db by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix debug_ppr_ty ForAllTy (#18522) Before this change, GHC would pretty-print forall k. forall a -> () as forall @k a. () which isn't even valid Haskell. - - - - - 0ddb4384 by Vladislav Zavialov at 2020-08-06T13:34:06-04:00 Fix visible forall in ppr_ty (#18522) Before this patch, this type: T :: forall k -> (k ~ k) => forall j -> k -> j -> Type was printed incorrectly as: T :: forall k j -> (k ~ k) => k -> j -> Type - - - - - d2a43225 by Richard Eisenberg at 2020-08-06T13:34:06-04:00 Fail eagerly on a lev-poly datacon arg Close #18534. See commentary in the patch. - - - - - 63348155 by Sylvain Henry at 2020-08-06T13:34:08-04:00 Use a type alias for Ways - - - - - 9570c212 by Takenobu Tani at 2020-08-06T19:46:46-04:00 users-guide: Rename 8.12 to 9.0 GHC 8.12.1 has been renamed to GHC 9.0.1. See also: https://mail.haskell.org/pipermail/ghc-devs/2020-July/019083.html [skip ci] - - - - - 3907ee01 by Cale Gibbard at 2020-08-07T08:34:46-04:00 A fix to an error message in monad comprehensions, and a move of dsHandleMonadicFailure as suggested by comments on !2330. - - - - - fa9bb70a by Cale Gibbard at 2020-08-07T08:34:46-04:00 Add some tests for fail messages in do-expressions and monad-comprehensions. - - - - - 5f036063 by Ben Gamari at 2020-08-07T08:35:21-04:00 cmm: Clean up Notes a bit - - - - - 6402c124 by Ben Gamari at 2020-08-07T08:35:21-04:00 CmmLint: Check foreign call argument register invariant As mentioned in Note [Register parameter passing] the arguments of foreign calls cannot refer to caller-saved registers. - - - - - 15b36de0 by Ben Gamari at 2020-08-07T08:35:21-04:00 nativeGen: One approach to fix #18527 Previously the code generator could produce corrupt C call sequences due to register overlap between MachOp lowerings and the platform's calling convention. We fix this using a hack described in Note [Evaluate C-call arguments before placing in destination registers]. - - - - - 3847ae0c by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Add test for #18527 - - - - - dd51d53b by Ben Gamari at 2020-08-07T08:35:21-04:00 testsuite: Fix prog001 Previously it failed as the `ghc` package was not visible. - - - - - e4f1b73a by Alan Zimmerman at 2020-08-07T23:58:10-04:00 ApiAnnotations; tweaks for ghc-exactprint update Remove unused ApiAnns, add one for linear arrow. Include API Annotations for trailing comma in export list. - - - - - 8a665db6 by Ben Gamari at 2020-08-07T23:58:45-04:00 configure: Fix double-negation in ld merge-objects check We want to only run the check if ld is gold. Fixes the fix to #17962. - - - - - a11c9678 by Adam Sandberg Ericsson at 2020-08-09T11:32:25+02:00 hadrian: depend on boot compiler version #18001 - - - - - c8873b52 by Alan Zimmerman at 2020-08-09T21:17:54-04:00 Api Annotations : Adjust SrcSpans for prefix bang (!). And prefix ~ (cherry picked from commit 8dbee2c578b1f642d45561be3f416119863e01eb) - - - - - 77398b67 by Sylvain Henry at 2020-08-09T21:18:34-04:00 Avoid allocations in `splitAtList` (#18535) As suspected by @simonpj in #18535, avoiding allocations in `GHC.Utils.Misc.splitAtList` when there are no leftover arguments is beneficial for performance: On CI validate-x86_64-linux-deb9-hadrian: T12227 -7% T12545 -12.3% T5030 -10% T9872a -2% T9872b -2.1% T9872c -2.5% Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c - - - - - 8ba41a0f by Felix Yan at 2020-08-10T20:23:29-04:00 Correct a typo in ghc.mk - - - - - 1c469264 by Felix Yan at 2020-08-10T20:23:29-04:00 Add a closing parenthesis too - - - - - acf537f9 by Sylvain Henry at 2020-08-10T20:24:09-04:00 Make splitAtList strict in its arguments Also fix its slightly wrong comment Metric Decrease: T5030 T12227 T12545 - - - - - ab4d1589 by Ben Gamari at 2020-08-11T22:18:03-04:00 typecheck: Drop SPECIALISE pragmas when there is no unfolding Previously the desugarer would instead fall over when it realized that there was no unfolding for an imported function with a SPECIALISE pragma. We now rather drop the SPECIALISE pragma and throw a warning. Fixes #18118. - - - - - 0ac8c0a5 by Ben Gamari at 2020-08-11T22:18:03-04:00 testsuite: Add test for #18118 - - - - - c43078d7 by Sven Tennie at 2020-08-11T22:18:38-04:00 Add hie.yaml to ghc-heap This enables IDE support by haskell-language-server for ghc-heap. - - - - - f1088b3f by Ben Gamari at 2020-08-11T22:19:15-04:00 testsuite: Specify metrics collected by T17516 Previously it collected everything, including "max bytes used". This is problematic since the test makes no attempt to control for deviations in GC timing, resulting in high variability. Fix this by only collecting "bytes allocated". - - - - - accbc242 by Sylvain Henry at 2020-08-12T03:50:12-04:00 DynFlags: disentangle Outputable - put panic related functions into GHC.Utils.Panic - put trace related functions using DynFlags in GHC.Driver.Ppr One step closer making Outputable fully independent of DynFlags. Bump haddock submodule - - - - - db6dd810 by Ben Gamari at 2020-08-12T03:50:48-04:00 testsuite: Increase tolerance of T16916 T16916 (testing #16916) has been slightly fragile in CI due to its reliance on CPU times. While it's hard to see how to eliminate the time-dependence entirely, we can nevertheless make it more tolerant. Fixes #16966. - - - - - bee43aca by Sylvain Henry at 2020-08-12T20:52:50-04:00 Rewrite and move the monad-state hack note The note has been rewritten by @simonpj in !3851 [skip ci] - - - - - 25fdf25e by Alan Zimmerman at 2020-08-12T20:53:26-04:00 ApiAnnotations: Fix parser for new GHC 9.0 features - - - - - 7831fe05 by Ben Gamari at 2020-08-13T03:44:17-04:00 parser: Suggest ImportQualifiedPost in prepositive import warning As suggested in #18545. - - - - - 55dec4dc by Sebastian Graf at 2020-08-13T03:44:52-04:00 PmCheck: Better long-distance info for where bindings (#18533) Where bindings can see evidence from the pattern match of the `GRHSs` they belong to, but not from anything in any of the guards (which belong to one of possibly many RHSs). Before this patch, we did *not* consider said evidence, causing #18533, where the lack of considering type information from a case pattern match leads to failure to resolve the vanilla COMPLETE set of a data type. Making available that information required a medium amount of refactoring so that `checkMatches` can return a `[(Deltas, NonEmpty Deltas)]`; one `(Deltas, NonEmpty Deltas)` for each `GRHSs` of the match group. The first component of the pair is the covered set of the pattern, the second component is one covered set per RHS. Fixes #18533. Regression test case: T18533 - - - - - cf97889a by Hécate at 2020-08-13T03:45:29-04:00 Re-add BangPatterns to CodePage.hs - - - - - ffc0d578 by Sylvain Henry at 2020-08-13T09:49:56-04:00 Add HomeUnit type Since Backpack the "home unit" is much more involved than what it was before (just an identifier obtained with `-this-unit-id`). Now it is used in conjunction with `-component-id` and `-instantiated-with` to configure module instantiations and to detect if we are type-checking an indefinite unit or compiling a definite one. This patch introduces a new HomeUnit datatype which is much easier to understand. Moreover to make GHC support several packages in the same instances, we will need to handle several HomeUnits so having a dedicated (documented) type is helpful. Finally in #14335 we will also need to handle the case where we have no HomeUnit at all because we are only loading existing interfaces for plugins which live in a different space compared to units used to produce target code. Several functions will have to be refactored to accept "Maybe HomeUnit" parameters instead of implicitly querying the HomeUnit fields in DynFlags. Having a dedicated type will make this easier. Bump haddock submodule - - - - - 8a51b2ab by Sylvain Henry at 2020-08-13T21:09:15-04:00 Make IOEnv monad one-shot (#18202) On CI (x86_64-linux-deb9-hadrian, compile_time/bytes_allocated): T10421 -1.8% (threshold: +/- 1%) T10421a -1.7% (threshold: +/- 1%) T12150 -4.9% (threshold: +/- 2%) T12227 -1.6 (threshold: +/- 1%) T12425 -1.5% (threshold: +/- 1%) T12545 -3.8% (threshold: +/- 1%) T12707 -3.0% (threshold: +/- 1%) T13035 -3.0% (threshold: +/- 1%) T14683 -10.3% (threshold: +/- 2%) T3064 -6.9% (threshold: +/- 2%) T4801 -4.3% (threshold: +/- 2%) T5030 -2.6% (threshold: +/- 2%) T5321FD -3.6% (threshold: +/- 2%) T5321Fun -4.6% (threshold: +/- 2%) T5631 -19.7% (threshold: +/- 2%) T5642 -13.0% (threshold: +/- 2%) T783 -2.7 (threshold: +/- 2%) T9020 -11.1 (threshold: +/- 2%) T9961 -3.4% (threshold: +/- 2%) T1969 (compile_time/bytes_allocated) -2.2% (threshold: +/-1%) T1969 (compile_time/max_bytes_used) +24.4% (threshold: +/-20%) Additionally on other CIs: haddock.Cabal -10.0% (threshold: +/- 5%) haddock.compiler -9.5% (threshold: +/- 5%) haddock.base (max bytes used) +24.6% (threshold: +/- 15%) T10370 (max bytes used, i386) +18.4% (threshold: +/- 15%) Metric Decrease: T10421 T10421a T12150 T12227 T12425 T12545 T12707 T13035 T14683 T3064 T4801 T5030 T5321FD T5321Fun T5631 T5642 T783 T9020 T9961 haddock.Cabal haddock.compiler Metric Decrease 'compile_time/bytes allocated': T1969 Metric Increase 'compile_time/max_bytes_used': T1969 T10370 haddock.base - - - - - 9f66fdf6 by Ben Gamari at 2020-08-14T15:50:34-04:00 testsuite: Drop --io-manager flag from testsuite configuration This is no longer necessary as there are now dedicated testsuite ways which run tests with WinIO. - - - - - 55fd1dc5 by Ben Gamari at 2020-08-14T15:51:10-04:00 llvm-targets: Add i686 targets Addresses #18422. - - - - - f4cc57fa by Ben Gamari at 2020-08-18T15:38:55-04:00 Allow unsaturated runRW# applications Previously we had a very aggressive Core Lint check which caught unsaturated applications of runRW#. However, there is nothing wrong with such applications and they may naturally arise in desugared Core. For instance, the desugared Core of Data.Primitive.Array.runArray# from the `primitive` package contains: case ($) (runRW# @_ @_) (\s -> ...) of ... In this case it's almost certain that ($) will be inlined, turning the application into a saturated application. However, even if this weren't the case there isn't a problem: CorePrep (after deleting an unnecessary case) can simply generate code in its usual way, resulting in a call to the Haskell definition of runRW#. Fixes #18291. - - - - - 3ac6ae7c by Ben Gamari at 2020-08-18T15:38:55-04:00 testsuite: Add test for #18291 - - - - - a87a0b49 by Eli Schwartz at 2020-08-18T15:39:30-04:00 install: do not install sphinx doctrees These files are 100% not needed at install time, and they contain unreproducible info. See https://reproducible-builds.org/ for why this matters. - - - - - 194b25ee by Ben Gamari at 2020-08-18T15:40:05-04:00 testsuite: Allow baseline commit to be set explicitly - - - - - fdcf7645 by Ben Gamari at 2020-08-18T15:40:05-04:00 gitlab-ci: Use MR base commit as performance baseline - - - - - 9ad5cab3 by Fendor at 2020-08-18T15:40:42-04:00 Expose UnitInfoMap as it is part of the public API - - - - - aa4b744d by Ben Gamari at 2020-08-18T22:11:36-04:00 testsuite: Only run llvm ways if llc is available As noted in #18560, we previously would always run the LLVM ways since `configure` would set `SettingsLlcCommand` to something non-null when it otherwise couldn't find the `llc` executable. Now we rather probe for the existence of the `llc` executable in the testsuite driver. Fixes #18560. - - - - - 0c5ed5c7 by Sylvain Henry at 2020-08-18T22:12:13-04:00 DynFlags: refactor GHC.CmmToAsm (#17957, #10143) This patch removes the use of `sdocWithDynFlags` from GHC.CmmToAsm.*.Ppr To do that I've had to make some refactoring: * X86' and PPC's `Instr` are no longer `Outputable` as they require a `Platform` argument * `Instruction` class now exposes `pprInstr :: Platform -> instr -> SDoc` * as a consequence, I've refactored some modules to avoid .hs-boot files * added (derived) functor instances for some datatypes parametric in the instruction type. It's useful for pretty-printing as we just have to map `pprInstr` before pretty-printing the container datatype. - - - - - 731c8d3b by nineonine at 2020-08-19T18:47:39-04:00 Implement -Wredundant-bang-patterns (#17340) Add new flag '-Wredundant-bang-patterns' that enables checks for "dead" bangs. Dead bangs are the ones that under no circumstances can force a thunk that wasn't already forced. Dead bangs are a form of redundant bangs. The new check is performed in Pattern-Match Coverage Checker along with other checks (namely, redundant and inaccessible RHSs). Given f :: Bool -> Int f True = 1 f !x = 2 we can detect dead bang patterns by checking whether @x ~ ⊥@ is satisfiable where the PmBang appears in 'checkGrdTree'. If not, then clearly the bang is dead. Such a dead bang is then indicated in the annotated pattern-match tree by a 'RedundantSrcBang' wrapping. In 'redundantAndInaccessibles', we collect all dead bangs to warn about. Note that we don't want to warn for a dead bang that appears on a redundant clause. That is because in that case, we recommend to delete the clause wholly, including its leading pattern match. Dead bang patterns are redundant. But there are bang patterns which are redundant that aren't dead, for example f !() = 0 the bang still forces the match variable, before we attempt to match on (). But it is redundant with the forcing done by the () match. We currently don't detect redundant bangs that aren't dead. - - - - - eb9bdaef by Simon Peyton Jones at 2020-08-19T18:48:14-04:00 Add right-to-left rule for pattern bindings Fix #18323 by adding a few lines of code to handle non-recursive pattern bindings. see GHC.Tc.Gen.Bind Note [Special case for non-recursive pattern bindings] Alas, this confused the pattern-match overlap checker; see #18323. Note that this patch only affects pattern bindings like that for (x,y) in this program combine :: (forall a . [a] -> a) -> [forall a. a -> a] -> ((forall a . [a] -> a), [forall a. a -> a]) breaks = let (x,y) = combine head ids in x y True We need ImpredicativeTypes for those [forall a. a->a] types to be valid. And with ImpredicativeTypes the old, unprincipled "allow unification variables to unify with a polytype" story actually works quite well. So this test compiles fine (if delicatedly) with old GHCs; but not with QuickLook unless we add this patch - - - - - 293c7fba by Sylvain Henry at 2020-08-21T09:36:38-04:00 Put CFG weights into their own module (#17957) It avoids having to query DynFlags to get them - - - - - 50eb4460 by Sylvain Henry at 2020-08-21T09:36:38-04:00 Don't use DynFlags in CmmToAsm.BlockLayout (#17957) - - - - - 659eb31b by Sylvain Henry at 2020-08-21T09:36:38-04:00 NCG: Dwarf configuration * remove references to DynFlags in GHC.CmmToAsm.Dwarf * add specific Dwarf options in NCGConfig instead of directly querying the debug level - - - - - 2d8ca917 by Sylvain Henry at 2020-08-21T09:37:15-04:00 Fix -ddump-stg flag -ddump-stg was dumping the initial STG (just after Core-to-STG pass) which was misleading because we want the final STG to know if a function allocates or not. Now we have a new flag -ddump-stg-from-core for this and -ddump-stg is deprecated. - - - - - fddddbf4 by Vladislav Zavialov at 2020-08-21T09:37:49-04:00 Import qualified Prelude in Cmm/Parser.y In preparation for the next version of 'happy', c95920 added a qualified import to GHC/Parser.y but for some reason neglected GHC/Cmm/Parser.y This patch adds the missing qualified import to GHC/Cmm/Parser.y and also adds a clarifying comment to explain why this import is needed. - - - - - 989c1c27 by Ben Gamari at 2020-08-21T11:27:53-04:00 gitlab-ci: Test master branch as well While these builds are strictly speaking redundant (since every commit is tested by @marge-bot before making it into `master`), they are nevertheless useful as they are displayed in the branch's commit list in GitLab's web interface. Fixes #18595. - - - - - e67ae884 by Aditya Gupta at 2020-08-22T03:29:00-04:00 mkUnique refactoring (#18362) Move uniqFromMask from Unique.Supply to Unique. Move the the functions that call mkUnique from Unique to Builtin.Uniques - - - - - 03cfcfd4 by Wander Hillen at 2020-08-22T03:29:36-04:00 Add ubuntu 20.04 jobs for nightly and release - - - - - 3f501545 by Craig Ferguson at 2020-08-22T03:30:13-04:00 Utils: clarify docs slightly The previous comment implies `nTimes n f` is either `f^{n+1}` or `f^{2^n}` (when in fact it's `f^n`). - - - - - 8b865092 by Krzysztof Gogolewski at 2020-08-23T14:12:53+02:00 Do not print synonyms in :i (->), :i Type (#18594) This adds a new printing flag `sdocPrintTypeAbbreviations` that is used specifically to avoid ghci printing 'type (->) = (->)' and 'type Type = Type'. - - - - - d8f61182 by Krzysztof Gogolewski at 2020-08-23T14:12:56+02:00 Move pprTyTcApp' inside pprTyTcApp No semantic change - - - - - 364258e0 by Krzysztof Gogolewski at 2020-08-24T00:32:31-04:00 Fix types in silly shifts (#18589) Patch written by Simon. I have only added a testcase. - - - - - b1eb38a0 by Sylvain Henry at 2020-08-24T00:33:13-04:00 Perf: make SDoc monad one-shot (#18202) With validate-x86_64-linux-deb9-hadrian: T1969 -3.4% (threshold: +/-1%) T3294 -3.3% (threshold: +/-1%) T12707 -1.4% (threshold: +/-1%) Additionally with validate-x86_64-linux-deb9-unreg-hadrian: T4801 -2.4% (threshold: +/-2%) T13035 -1.4% (threshold: +/-1%) T13379 -2.4% (threshold: +/-2%) ManyAlternatives -2.5% (threshold: +/-2%) ManyConstructors -3.0% (threshold: +/-2%) Metric Decrease: T12707 T1969 T3294 ManyAlternatives ManyConstructors T13035 T13379 T4801 - - - - - a77b9ec2 by Krzysztof Gogolewski at 2020-08-24T10:04:20-04:00 Add a test for #18397 The bug was fixed by !3421. - - - - - 05550a5a by Sylvain Henry at 2020-08-24T10:04:59-04:00 Avoid roundtrip through SDoc As found by @monoidal on https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3885#note_295126 - - - - - 0a1ecc5f by Ben Gamari at 2020-08-25T07:37:05-04:00 SysTools.Process: Handle exceptions in readCreateProcessWithExitCode' In #18069 we are observing MVar deadlocks from somewhere in ghc.exe. This use of MVar stood out as being one of the more likely culprits. Here we make sure that it is exception-safe. - - - - - db8793ad by Richard Eisenberg at 2020-08-25T07:37:40-04:00 Use tcView, not coreView, in the pure unifier. Addresses a lingering point within #11715. - - - - - fb77207a by Simon Peyton Jones at 2020-08-25T07:38:16-04:00 Use LIdP rather than (XRec p (IdP p)) This patch mainly just replaces use of XRec p (IdP p) with LIdP p One slightly more significant change is to parameterise HsPatSynDetails over the pass rather than the argument type, so that it's uniform with HsConDeclDetails and HsConPatDetails. I also got rid of the dead code GHC.Hs.type.conDetailsArgs But this is all just minor refactoring. No change in functionality. - - - - - 8426a136 by Krzysztof Gogolewski at 2020-08-25T07:38:54-04:00 Add a test for #18585 - - - - - 2d635a50 by Takenobu Tani at 2020-08-26T04:50:21-04:00 linters: Make CPP linter skip image files This patch adds an exclusion rule for `docs/users_guide/images`, to avoid lint errors of PDF files. - - - - - b7d98cb2 by Takenobu Tani at 2020-08-26T04:50:21-04:00 users-guide: Color the logo on the front page of the PDF This patch updates the logo with a recent color scheme. This affects only the PDF version of the user's guide. See also: * https://mail.haskell.org/pipermail/ghc-devs/2020-August/019139.html * https://gitlab.haskell.org/ghc/ghc/-/wikis/logo - - - - - 0b17fa18 by Sylvain Henry at 2020-08-26T04:50:58-04:00 Refactor UnitId pretty-printing When we pretty-print a UnitId for the user, we try to map it back to its origin package name, version and component to print "package-version:component" instead of some hash. The UnitId type doesn't carry these information, so we have to look into a UnitState to find them. This is why the Outputable instance of UnitId used `sdocWithDynFlags` in order to access the `unitState` field of DynFlags. This is wrong for several reasons: 1. The DynFlags are accessed when the message is printed, not when it is generated. So we could imagine that the unitState may have changed in-between. Especially if we want to allow unit unloading. 2. We want GHC to support several independent sessions at once, hence several UnitState. The current approach supposes there is a unique UnitState as a UnitId doesn't indicate which UnitState to use. See the Note [Pretty-printing UnitId] in GHC.Unit for the new approach implemented by this patch. One step closer to remove `sdocDynFlags` field from `SDocContext` (#10143). Fix #18124. Also fix some Backpack code to use SDoc instead of String. - - - - - dc476a50 by Sylvain Henry at 2020-08-26T04:51:35-04:00 Bignum: fix BigNat subtraction (#18604) There was a confusion between the boolean expected by withNewWordArrayTrimedMaybe and the boolean returned by subtracting functions. - - - - - fcb10b6c by Peter Trommler at 2020-08-26T10:42:30-04:00 PPC and X86: Portable printing of IEEE floats GNU as and the AIX assembler support floating point literals. SPARC seems to have support too but I cannot test on SPARC. Curiously, `doubleToBytes` is also used in the LLVM backend. To avoid endianness issues when cross-compiling float and double literals are printed as C-style floating point values. The assembler then takes care of memory layout and endianness. This was brought up in #18431 by @hsyl20. - - - - - 770100e0 by Krzysztof Gogolewski at 2020-08-26T10:43:13-04:00 primops: Remove Monadic and Dyadic categories There were four categories of primops: Monadic, Dyadic, Compare, GenPrimOp. The compiler does not treat Monadic and Dyadic in any special way, we can just replace them with GenPrimOp. Compare is still used in isComparisonPrimOp. - - - - - 01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00 Consolidate imports in getMinimalImports (#18264) - - - - - bacccb73 by Ryan Scott at 2020-08-27T14:20:01-04:00 Make {hsExpr,hsType,pat}NeedsParens aware of boxed 1-tuples `hsExprNeedsParens`, `hsTypeNeedsParens`, and `patNeedsParens` previously assumed that all uses of explicit tuples in the source syntax never need to be parenthesized. This is true save for one exception: boxed one-tuples, which use the `Solo` data type from `GHC.Tuple` instead of special tuple syntax. This patch adds the necessary logic to the three `*NeedsParens` functions to handle `Solo` correctly. Fixes #18612. - - - - - c6f50cea by Krzysztof Gogolewski at 2020-08-28T02:22:36-04:00 Add missing primop documentation (#18454) - Add three pseudoops to primops.txt.pp, so that Haddock renders the documentation - Update comments - Remove special case for "->" - it's no longer exported from GHC.Prim - Remove reference to Note [Compiling GHC.Prim] - the ad-hoc fix is no longer there after updates to levity polymorphism. - Document GHC.Prim - Remove the comment that lazy is levity-polymorphic. As far as I can tell, it never was: in 80e399639, only the unfolding was given an open type variable. - Remove haddock hack in GHC.Magic - no longer neccessary after adding realWorld# to primops.txt.pp. - - - - - f065b6b0 by Tamar Christina at 2020-08-28T02:23:13-04:00 Fix use distro toolchian - - - - - 4517a382 by Tamar Christina at 2020-08-28T02:23:13-04:00 document how build system find toolchains on Windows - - - - - 329f7cb9 by Ben Gamari at 2020-08-31T22:59:14-04:00 base: Better error message on invalid getSystemTimerManager call Previously we would produce a rather unhelpful pattern match failure error in the case where the user called `getSystemTimerManager` in a program which isn't built with `-threaded`. This understandably confused the user in #15616. Fixes #15616. - - - - - f6d70a8f by Roland Senn at 2020-08-31T22:59:50-04:00 Add tests for #15617. Avoid a similar regression in the future. - - - - - e5969fd0 by Roland Senn at 2020-08-31T23:00:27-04:00 Add additional tests for #18172 (Followup MR 3543) There was still one active discussion [thread](https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3543#note_284325) when MR !3543 got merged. This MR adds the requested tests exercising the changes in `compiler/GHC/HsToCore/Match/Literal.hs:warnAboutEmptyEnumerations` and its sub-functions. - - - - - fe18b482 by Ben Gamari at 2020-08-31T23:01:02-04:00 Bump Win32 and process submodules - - - - - 2da93308 by Sylvain Henry at 2020-08-31T23:01:39-04:00 Hadrian: fix slow-validate flavour (#18586) - - - - - 85e13008 by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Update dominator code with fixes from the dom-lt package. Two bugs turned out in the package that have been fixed since. This MR includes this fixes in the GHC port of the code. - - - - - dffb38fa by Andreas Klebinger at 2020-08-31T23:02:15-04:00 Dominators.hs: Use unix line endings - - - - - 6189cc04 by Moritz Angermann at 2020-08-31T23:02:50-04:00 [fixup 3433] move debugBelch into IF_DEBUG(linker) The commit in dff1cb3d9c111808fec60190747272b973547c52 incorrectly left the `debugBelch` function without a comment or IF_DEBUG(linker,) decoration. This rectifies it. Needs at least a 8.10 backport, as it was backported in 6471cc6aff80d5deebbdb1bf7b677b31ed2af3d5 - - - - - bcb68a3f by Sylvain Henry at 2020-08-31T23:03:27-04:00 Don't store HomeUnit in UnitConfig Allow the creation of a UnitConfig (hence of a UnitState) without having a HomeUnit. It's required for #14335. - - - - - 0a372387 by Sylvain Henry at 2020-08-31T23:04:04-04:00 Fix documentation and fix "check" bignum backend (#18604) - - - - - eb85f125 by Moritz Angermann at 2020-08-31T23:04:39-04:00 Set the dynamic-system-linker flag to Manual This flag should be user controllable, hence Manual: True. - - - - - 380ef845 by Sven Tennie at 2020-08-31T23:05:14-04:00 Ignore more files Ignore files from "new style" cabal builds (dist-newstyle folders) and from clangd (C language server). - - - - - 74a7fbff by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.0 and earlier (#18620) This patch adds the upper bound of a happy version for ghc-9.0 and earlier. Currently, we can't use happy-1.20.0 for ghc-9.0. See #18620. - - - - - a4473f02 by Takenobu Tani at 2020-08-31T23:05:51-04:00 Limit upper version of Happy for ghc-9.2 (#18620) This patch adds the upper bound of a happy version for ghc-9.2. Currently, We can use happy-1.19 or happy-1.20 for ghc-9.2. See #18620. - - - - - a8a2568b by Sylvain Henry at 2020-08-31T23:06:28-04:00 Bignum: add BigNat compat functions (#18613) - - - - - 884245dd by Sylvain Henry at 2020-09-01T12:39:36-04:00 Fix FastString lexicographic ordering (fix #18562) - - - - - 4b4fbc58 by Sylvain Henry at 2020-09-01T12:39:36-04:00 Remove "Ord FastString" instance FastStrings can be compared in 2 ways: by Unique or lexically. We don't want to bless one particular way with an "Ord" instance because it leads to bugs (#18562) or to suboptimal code (e.g. using lexical comparison while a Unique comparison would suffice). UTF-8 encoding has the advantage that sorting strings by their encoded bytes also sorts them by their Unicode code points, without having to decode the actual code points. BUT GHC uses Modified UTF-8 which diverges from UTF-8 by encoding \0 as 0xC080 instead of 0x00 (to avoid null bytes in the middle of a String so that the string can still be null-terminated). This patch adds a new `utf8CompareShortByteString` function that performs sorting by bytes but that also takes Modified UTF-8 into account. It is much more performant than decoding the strings into [Char] to perform comparisons (which we did in the previous patch). Bump haddock submodule - - - - - b4edcde7 by Ben Gamari at 2020-09-01T14:53:42-04:00 testsuite: Add broken test for #18302 - - - - - bfab2a30 by Sebastian Graf at 2020-09-02T15:54:55-04:00 Turn on -XMonoLocalBinds by default (#18430) And fix the resulting type errors. Co-authored-by: Krzysztof Gogolewski <krz.gogolewski at gmail.com> Metric Decrease: parsing001 - - - - - c30cc0e9 by David Feuer at 2020-09-02T15:55:31-04:00 Remove potential space leak from Data.List.transpose Previously, `transpose` produced a list of heads and a list of tails independently. This meant that a function using only some heads, and only some tails, could potentially leak space. Use `unzip` to work around the problem by producing pairs and selector thunks instead. Time and allocation behavior will be worse, but there should be no more leak potential. - - - - - ffc3da47 by Sylvain Henry at 2020-09-02T15:56:11-04:00 Remove outdated note - - - - - 85e62123 by Sylvain Henry at 2020-09-02T15:56:48-04:00 Bignum: add missing compat import/export functions - - - - - 397c2b03 by Ben Gamari at 2020-09-03T17:31:47-04:00 configure: Work around Raspbian's silly packaging decisions See #17856. - - - - - 4891c18a by Kathryn Spiers at 2020-09-03T17:32:24-04:00 expected-undocumented-flags remove kill flags It looks like the flags were removed in https://gitlab.haskell.org/ghc/ghc/-/commit/3e27205a66b06a4501d87eb31e285eadbc693eb7 and can safely be removed here - - - - - 1d6d6488 by Sylvain Henry at 2020-09-04T16:24:20-04:00 Don't rely on CLabel's Outputable instance in CmmToC This is in preparation of the removal of sdocWithDynFlags (#10143), hence of the refactoring of CLabel's Outputable instance. - - - - - 89ce7cdf by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: use Platform in foldRegs* - - - - - 220ad8d6 by Sylvain Henry at 2020-09-04T16:24:59-04:00 DynFlags: don't pass DynFlags to cmmImplementSwitchPlans - - - - - c1e54439 by Ryan Scott at 2020-09-04T16:25:35-04:00 Introduce isBoxedTupleDataCon and use it to fix #18644 The code that converts promoted tuple data constructors to `IfaceType`s in `GHC.CoreToIface` was using `isTupleDataCon`, which conflates boxed and unboxed tuple data constructors. To avoid this, this patch introduces `isBoxedTupleDataCon`, which is like `isTupleDataCon` but only works for _boxed_ tuple data constructors. While I was in town, I was horribly confused by the fact that there were separate functions named `isUnboxedTupleCon` and `isUnboxedTupleTyCon` (similarly, `isUnboxedSumCon` and `isUnboxedSumTyCon`). It turns out that the former only works for data constructors, despite its very general name! I opted to rename `isUnboxedTupleCon` to `isUnboxedTupleDataCon` (similarly, I renamed `isUnboxedSumCon` to `isUnboxedSumDataCon`) to avoid this potential confusion, as well as to be more consistent with the naming convention I used for `isBoxedTupleDataCon`. Fixes #18644. - - - - - 07bdcac3 by GHC GitLab CI at 2020-09-04T22:26:25-04:00 configure: Avoid hard-coded ld path on Windows The fix to #17962 ended up regressing on Windows as it failed to replicate the logic responsible for overriding the toolchain paths on Windows. This resulted in a hard-coded path to a directory that likely doesn't exist on the user's system (#18550). - - - - - 0be8e746 by Benjamin Maurer at 2020-09-04T22:27:01-04:00 Documented the as of yet undocumented '--print-*' GHC flags, as well as `-split-objs`, since that is related to `--print-object-splitting-supported`. See #18641 - - - - - 4813486f by Sylvain Henry at 2020-09-04T22:27:44-04:00 Move Hadrian's wiki pages in tree (fix #16165) Only the debugging page contains interesting stuff. Some of this stuff looks old (e.g. recommending "cabal install")... - - - - - 7980ae23 by GHC GitLab CI at 2020-09-05T14:50:52-04:00 rts: Consistently use stgMallocBytes instead of malloc This can help in debugging RTS memory leaks since all allocations go through the same interface. - - - - - 67059893 by Ben Gamari at 2020-09-05T14:51:27-04:00 configure: Fix whitespace - - - - - be2cc0ad by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: More intelligent detection of locale availability Previously ci.sh would unconditionally use C.UTF-8. However, this fails on Centos 7, which appears not to provide this locale. Now we first try C.UTF-8, then try en_US.UTF-8, then fail. Works around #18607. - - - - - 15dca847 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Rename RELEASE variable to RELEASE_JOB This interfered with the autoconf variable of the same name, breaking pre-release builds. - - - - - bec0d170 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Bump Windows toolchain version This should have been done when we bumped the bootstrap compiler to 8.8.4. - - - - - 9fbaee21 by Ben Gamari at 2020-09-05T14:51:27-04:00 gitlab-ci: Drop Windows make job These are a significant burden on our CI resources and end up failing quite often due to #18274. Here I drop the make jobs during validaion; it is now run only during the nightly builds. - - - - - 869f6e19 by Ben Gamari at 2020-09-05T14:51:27-04:00 testsuite: Drop Windows-specific output for parseTree The normalise_slashes normaliser should handle this. - - - - - 2c9f743c by Ben Gamari at 2020-09-05T14:51:28-04:00 testsuite: Mark T5975[ab] as broken on Windows Due to #7305. - - - - - 643785e3 by Ben Gamari at 2020-09-05T14:51:28-04:00 gitlab-ci: Fix typo A small typo in a rule regular expression. - - - - - c5413fc6 by Wander Hillen at 2020-09-07T09:33:54-04:00 Add clarification regarding poll/kqueue flags - - - - - 10434d60 by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Configure bignum backend in Hadrian builds - - - - - d4bc9f0d by Ben Gamari at 2020-09-07T09:34:32-04:00 gitlab-ci: Use hadrian builds for Windows release artifacts - - - - - 4ff93292 by Moritz Angermann at 2020-09-07T21:18:39-04:00 [macOS] improved runpath handling In b592bd98ff25730bbe3c13d6f62a427df8c78e28 we started using -dead_strip_dylib on macOS when lining dynamic libraries and binaries. The underlying reason being the Load Command Size Limit in macOS Sierra (10.14) and later. GHC will produce @rpath/libHS... dependency entries together with a corresponding RPATH entry pointing to the location of the libHS... library. Thus for every library we produce two Load Commands. One to specify the dependent library, and one with the path where to find it. This makes relocating libraries and binaries easier, as we just need to update the RPATH entry with the install_name_tool. The dynamic linker will then subsitute each @rpath with the RPATH entries it finds in the libraries load commands or the environement, when looking up @rpath relative libraries. -dead_strip_dylibs intructs the linker to drop unused libraries. This in turn help us reduce the number of referenced libraries, and subsequently the size of the load commands. This however does not remove the RPATH entries. Subsequently we can end up (in extreme cases) with only a single @rpath/libHS... entry, but 100s or more RPATH entries in the Load Commands. This patch rectifies this (slighly unorthodox) by passing *no* -rpath arguments to the linker at link time, but -headerpad 8000. The headerpad argument is in hexadecimal and the maxium 32k of the load command size. This tells the linker to pad the load command section enough for us to inject the RPATHs later. We then proceed to link the library or binary with -dead_strip_dylibs, and *after* the linking inspect the library to find the left over (non-dead-stripped) dependencies (using otool). We find the corresponding RPATHs for each @rpath relative dependency, and inject them into the library or binary using the install_name_tool. Thus achieving a deadstripped dylib (and rpaths) build product. We can not do this in GHC, without starting to reimplement a dynamic linker as we do not know which symbols and subsequently libraries are necessary. Commissioned-by: Mercury Technologies, Inc. (mercury.com) - - - - - df04b81e by Sylvain Henry at 2020-09-07T21:19:20-04:00 Move DynFlags test into updateModDetailsIdInfos's caller (#17957) - - - - - ea1cbb8f by Ben Gamari at 2020-09-08T15:42:02-04:00 rts: Add stg_copyArray_barrier to RtsSymbols list It's incredible that this wasn't noticed until now. - - - - - d7b2f799 by Daishi Nakajima at 2020-09-08T15:42:41-04:00 testsuite: Output performance test results in tabular format this was suggested in #18417. Change the print format of the values. * Shorten commit hash * Reduce precision of the "Value" field * Shorten metrics name * e.g. runtime/bytes allocated -> run/alloc * Shorten "MetricsChange" * e.g. unchanged -> unch, increased -> incr And, print the baseline environment if there are baselines that were measured in a different environment than the current environment. If all "Baseline commit" are the same, print it once. - - - - - 44472daf by Ryan Scott at 2020-09-08T15:43:16-04:00 Make the forall-or-nothing rule only apply to invisible foralls (#18660) This fixes #18660 by changing `isLHsForAllTy` to `isLHsInvisForAllTy`, which is sufficient to make the `forall`-or-nothing rule only apply to invisible `forall`s. I also updated some related documentation and Notes while I was in the neighborhood. - - - - - 0c61cbff by Ben Gamari at 2020-09-08T15:43:54-04:00 gitlab-ci: Handle distributions without locales Previously we would assume that the `locale` utility exists. However, this is not so on Alpine as musl's locale support is essentially non-existent. (cherry picked from commit 17cdb7ac3b557a245fee1686e066f9f770ddc21e) - - - - - d989c842 by Ben Gamari at 2020-09-08T15:43:55-04:00 gitlab-ci: Accept Centos 7 C.utf8 locale Centos apparently has C.utf8 rather than C.UTF-8. (cherry picked from commit d9f85dd25a26a04d3485470afb3395ee2dec6464) - - - - - e5a2899c by John Ericson at 2020-09-09T00:46:05-04:00 Use "to" instead of "2" in internal names of conversion ops Change the constructors for the primop union, and also names of the literal conversion functions. "2" runs into trouble when we need to do conversions from fixed-width types, and end up with thing like "Int642Word". Only the names internal to GHC are changed, as I don't want to worry about breaking changes ATM. - - - - - 822f1057 by Ryan Scott at 2020-09-09T00:46:41-04:00 Postpone associated tyfam default checks until after typechecking Previously, associated type family defaults were validity-checked during typechecking. Unfortunately, the error messages that these checks produce run the risk of printing knot-tied type constructors, which will cause GHC to diverge. In order to preserve the current error message's descriptiveness, this patch postpones these validity checks until after typechecking, which are now located in the new function `GHC.Tc.Validity.checkValidAssocTyFamDeflt`. Fixes #18648. - - - - - 8c892689 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add OptCoercionOpts Use OptCoercionOpts to avoid threading DynFlags all the way down to GHC.Core.Coercion.Opt - - - - - 3f32a9c0 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add UnfoldingOpts and SimpleOpts Milestone: after this patch, we only use 'unsafeGlobalDynFlags' for the state hack and for debug in Outputable. - - - - - b3df72a6 by Sylvain Henry at 2020-09-09T11:19:24-04:00 DynFlags: add sm_pre_inline field into SimplMode (#17957) It avoids passing and querying DynFlags down in the simplifier. - - - - - ffae5792 by Sylvain Henry at 2020-09-09T11:19:24-04:00 Add comments about sm_dflags and simpleOptExpr - - - - - 7911d0d9 by Alan Zimmerman at 2020-09-09T11:20:03-04:00 Remove GENERATED pragma, as it is not being used @alanz pointed out on ghc-devs that the payload of this pragma does not appear to be used anywhere. I (@bgamari) did some digging and traced the pragma's addition back to d386e0d2 (way back in 2006!). It appears that it was intended to be used by code generators for use in informing the code coveraging checker about generated code provenance. When it was added it used the pragma's "payload" fields as source location information to build an "ExternalBox". However, it looks like this was dropped a year later in 55a5d8d9. At this point it seems like the pragma serves no useful purpose. Given that it also is not documented, I think we should remove it. Updates haddock submodule Closes #18639 - - - - - 5aae5b32 by Ben Gamari at 2020-09-09T18:31:40-04:00 gitlab-ci: Bump Docker images We now generate our Docker images via Dhall definitions, as described in ghc/ci-images!52. Additionally, we are far more careful about where tools come from, using the ALEX, HAPPY, HSCOLOR, and GHC environment variables (set in the Dockerfiles) to find bootstrapping tools. - - - - - 4ce9fe88 by Ben Gamari at 2020-09-09T18:31:40-04:00 hadrian: Fix leakage of GHC in PATH into build Previously hadrian would use GHC on PATH when configuring packages (or fail if there is no such GHC). Fix this. Unfortunately this runs into another bug in Cabal which we workaround. - - - - - 291a15dd by Ben Gamari at 2020-09-09T18:31:40-04:00 utils: Bump cabal-version of hp2ps and unlit - - - - - 4798caa0 by David Himmelstrup at 2020-09-09T18:32:16-04:00 rts comment: RTS_TICKY_SYMBOLS moved from rts/Linker.c to rts/RtsSymbols.c - - - - - 67ce72da by Sebastian Graf at 2020-09-10T10:35:33-04:00 Add long-distance info for pattern bindings (#18572) We didn't consider the RHS of a pattern-binding before, which led to surprising warnings listed in #18572. As can be seen from the regression test T18572, we get the expected output now. - - - - - 1207576a by Sebastian Graf at 2020-09-10T10:35:33-04:00 PmCheck: Big refactor using guard tree variants more closely following source syntax (#18565) Previously, we desugared and coverage checked plain guard trees as described in Lower Your Guards. That caused (in !3849) quite a bit of pain when we need to partially recover tree structure of the input syntax to return covered sets for long-distance information, for example. In this refactor, I introduced a guard tree variant for each relevant source syntax component of a pattern-match (mainly match groups, match, GRHS, empty case, pattern binding). I made sure to share as much coverage checking code as possible, so that the syntax-specific checking functions are just wrappers around the more substantial checking functions for the LYG primitives (`checkSequence`, `checkGrds`). The refactoring payed off in clearer code and elimination of all panics related to assumed guard tree structure and thus fixes #18565. I also took the liberty to rename and re-arrange the order of functions and comments in the module, deleted some dead and irrelevant Notes, wrote some new ones and gave an overview module haddock. - - - - - 95455982 by GHC GitLab CI at 2020-09-10T10:36:09-04:00 hadrian: Don't include -fdiagnostics-color in argument hash Otherwise the input hash will vary with whether colors are requested, which changed with `isatty`. Fixes #18672. - - - - - 6abe4a1c by Sebastian Graf at 2020-09-10T17:02:00+02:00 .gitignore *.hiedb files - - - - - 3777be14 by Sebastian Graf at 2020-09-10T17:03:12+02:00 PmCheck: Handle ⊥ and strict fields correctly (#18341) In #18341, we discovered an incorrect digression from Lower Your Guards. This MR changes what's necessary to support properly fixing #18341. In particular, bottomness constraints are now properly tracked in the oracle/inhabitation testing, as an additional field `vi_bot :: Maybe Bool` in `VarInfo`. That in turn allows us to model newtypes as advertised in the Appendix of LYG and fix #17725. Proper handling of ⊥ also fixes #17977 (once again) and fixes #18670. For some reason I couldn't follow, this also fixes #18273. I also added a couple of regression tests that were missing. Most of them were already fixed before. In summary, this patch fixes #18341, #17725, #18273, #17977 and #18670. Metric Decrease: T12227 - - - - - 1bd28931 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Define TICKY_TICKY when compiling cmm RTS files. - - - - - 15e67801 by David Himmelstrup at 2020-09-11T09:59:43-04:00 Fix typos in TICKY_TICKY symbol names. - - - - - 8a5a91cb by David Himmelstrup at 2020-09-11T09:59:43-04:00 Enable TICKY_TICKY for debug builds when building with makefiles. - - - - - fc965c09 by Sandy Maguire at 2020-09-12T00:31:36-04:00 Add clamp function to Data.Ord - - - - - fb6e29e8 by Sandy Maguire at 2020-09-12T00:31:37-04:00 Add tests - - - - - 2a942285 by Sebastian Graf at 2020-09-12T00:32:13-04:00 PmCheck: Disattach COMPLETE pragma lookup from TyCons By not attaching COMPLETE pragmas with a particular TyCon and instead assume that every COMPLETE pragma is applicable everywhere, we can drastically simplify the logic that tries to initialise available COMPLETE sets of a variable during the pattern-match checking process, as well as fixing a few bugs. Of course, we have to make sure not to report any of the ill-typed/unrelated COMPLETE sets, which came up in a few regression tests. In doing so, we fix #17207, #18277 and #14422. There was a metric decrease in #18478 by ~20%. Metric Decrease: T18478 - - - - - 389a6683 by Ben Gamari at 2020-09-12T00:32:49-04:00 hadrian: Pass input file to makeindex Strangely I find that on Alpine (and apparently only on Alpine) the latex makeindex command expects to be given a filename, lest it reads from stdin. - - - - - 853d121a by Ryan Scott at 2020-09-12T00:33:25-04:00 Don't quote argument to Hadrian's test-env flag (#18656) Doing so causes the name of the test environment to gain an extra set of double quotes, which changes the name entirely. Fixes #18656. - - - - - 8440b5fa by Krzysztof Gogolewski at 2020-09-12T00:33:25-04:00 Make sure we can read past perf notes See #18656. - - - - - 2157be52 by theobat at 2020-09-12T21:27:04-04:00 Avoid iterating twice in `zipTyEnv` (#18535) zipToUFM is a new function to replace `listToUFM (zipEqual ks vs)`. An explicit recursion is preferred due to the sensible nature of fusion. T12227 -6.0% T12545 -12.3% T5030 -9.0% T9872a -1.6% T9872b -1.6% T9872c -2.0% ------------------------- Metric Decrease: T12227 T12545 T5030 T9872a T9872b T9872c ------------------------- - - - - - 69ea2fee by Sebastian Graf at 2020-09-12T21:27:40-04:00 Make `tcCheckSatisfiability` incremental (#18645) By taking and returning an `InertSet`. Every new `TcS` session can then pick up where a prior session left with `setTcSInerts`. Since we don't want to unflatten the Givens (and because it leads to infinite loops, see !3971), we introduced a new variant of `runTcS`, `runTcSInerts`, that takes and returns the `InertSet` and makes sure not to unflatten the Givens after running the `TcS` action. Fixes #18645 and #17836. Metric Decrease: T17977 T18478 - - - - - a77e48d2 by Sebastian Graf at 2020-09-12T21:27:40-04:00 Extract definition of DsM into GHC.HsToCore.Types `DsM` was previously defined in `GHC.Tc.Types`, along with `TcM`. But `GHC.Tc.Types` is in the set of transitive dependencies of `GHC.Parser`, a set which we aim to minimise. Test case `CountParserDeps` checks for that. Having `DsM` in that set means the parser also depends on the innards of the pattern-match checker in `GHC.HsToCore.PmCheck.Types`, which is the reason we have that module in the first place. In the previous commit, we represented the `TyState` by an `InertSet`, but that pulls the constraint solver as well as 250 more modules into the set of dependencies, triggering failure of `CountParserDeps`. Clearly, we want to evolve the pattern-match checker (and the desugarer) without being concerned by this test, so this patch includes a small refactor that puts `DsM` into its own module. - - - - - fd5d622a by Sebastian Graf at 2020-09-12T21:27:40-04:00 Hackily decouple the parser from the desugarer In a hopefully temporary hack, I re-used the idea from !1957 of using a nullary type family to break the dependency from GHC.Driver.Hooks on the definition of DsM ("Abstract Data"). This in turn broke the last dependency from the parser to the desugarer. More details in `Note [The Decoupling Abstract Data Hack]`. In the future, we hope to undo this hack again in favour of breaking the dependency from the parser to DynFlags altogether. - - - - - 35a7b7ec by Adam Sandberg Eriksson at 2020-09-14T17:46:16-04:00 docs: -B rts option sounds the bell on every GC (#18351) - - - - - 5ae8212c by Wander Hillen at 2020-09-14T17:46:54-04:00 Populate gitlab cache after building - - - - - a5ffb39a by Wander Hillen at 2020-09-14T17:46:54-04:00 Move ahead cabal cache restoration to before use of cabal - - - - - e8b37c21 by Wander Hillen at 2020-09-14T17:46:54-04:00 Do the hadrian rebuild multicore - - - - - 07762eb5 by Wander Hillen at 2020-09-14T17:46:54-04:00 Also cache other hadrian builds - - - - - 8610bcbe by DenisFrezzato at 2020-09-15T15:19:08-04:00 Fix rtsopts documentation - - - - - c7182a5c by Simon Peyton Jones at 2020-09-15T15:19:44-04:00 Care with implicit-parameter superclasses Two bugs, #18627 and #18649, had the same cause: we were not account for the fact that a constaint tuple might hide an implicit parameter. The solution is not hard: look for implicit parameters in superclasses. See Note [Local implicit parameters] in GHC.Core.Predicate. Then we use this new function in two places * The "short-cut solver" in GHC.Tc.Solver.Interact.shortCutSolver which simply didn't handle implicit parameters properly at all. This fixes #18627 * The specialiser, which should not specialise on implicit parameters This fixes #18649 There are some lingering worries (see Note [Local implicit parameters]) but things are much better. - - - - - 0f3884b0 by Zubin Duggal at 2020-09-15T15:20:23-04:00 Export enrichHie from GHC.Iface.Ext.Ast This is useful for `ghcide` - - - - - b3143f5a by Sylvain Henry at 2020-09-15T15:21:06-04:00 Enhance metrics output - - - - - 4283feaa by Ryan Scott at 2020-09-15T15:21:43-04:00 Introduce and use DerivClauseTys (#18662) This switches `deriv_clause_tys` so that instead of using a list of `LHsSigType`s to represent the types in a `deriving` clause, it now uses a sum type. `DctSingle` represents a `deriving` clause with no enclosing parentheses, while `DctMulti` represents a clause with enclosing parentheses. This makes pretty-printing easier and avoids confusion between `HsParTy` and the enclosing parentheses in `deriving` clauses, which are different semantically. Fixes #18662. - - - - - 90229c4b by Ryan Scott at 2020-09-16T04:53:22-04:00 Include -f{write,validate}-ide-info in the User's Guide flag reference Previously, these were omitted from the flag reference due to a layout oversight in `docs/users_guide/flags.{rst,py}`. Fixes #18426. - - - - - ce42e187 by Ben Gamari at 2020-09-16T04:53:59-04:00 rts: Fix erroneous usage of vsnprintf As pointed out in #18685, this should be snprintf not vsnprintf. This appears to be due to a cut-and-paste error. Fixes #18658. - - - - - b695e7d7 by Sylvain Henry at 2020-09-16T04:54:38-04:00 Rename ghci flag into internal-interpreter "ghci" as a flag name was confusing because it really enables the internal-interpreter. Even the ghci library had a "ghci" flag... - - - - - 8af954d2 by Sylvain Henry at 2020-09-16T04:55:17-04:00 Make ghc-boot reexport modules from ghc-boot-th Packages don't have to import both ghc-boot and ghc-boot-th. It makes the dependency graph easier to understand and to refactor. - - - - - 6baa67f5 by Adam Sandberg Eriksson at 2020-09-16T07:45:47-04:00 docs: correct haddock reference [skip ci] - - - - - 7cf09ab0 by Simon Peyton Jones at 2020-09-17T01:27:25-04:00 Do absence analysis on stable unfoldings Ticket #18638 showed that Very Bad Things happen if we fail to do absence analysis on stable unfoldings. It's all described in Note [Absence analysis for stable unfoldings and RULES]. I'm a bit surprised this hasn't bitten us before. Fortunately the fix is pretty simple. - - - - - 76d3bcbc by Leif Metcalf at 2020-09-17T01:28:01-04:00 Replace deprecated git --recursive The --recursive flag of git-clone has been replaced by the --recurse-submodules flag since git 1.7.4, released in 2011. - - - - - da8f4ddd by Richard Eisenberg at 2020-09-17T01:28:38-04:00 Document IfaceTupleTy - - - - - 3c94c816 by HaskellMouse at 2020-09-17T08:49:51-04:00 Added explicit fixity to (~). Solves #18252 - - - - - b612e396 by Cary Robbins at 2020-09-17T08:50:30-04:00 Make the 'IsString (Const a b)' instance polykinded on 'b' - - - - - 8d0c26c4 by Ben Gamari at 2020-09-17T08:51:08-04:00 rts/win32: Fix missing #include's These slipped through CI. - - - - - 76009ec8 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump Win32 submodule to 2.9.0.0 Also bumps Cabal, directory - - - - - 147bb598 by Ben Gamari at 2020-09-17T08:51:08-04:00 Bump version to 9.0 Bumps haskeline and haddock submodules. (cherry picked from commit f218cfc92f7b1a1e01190851972bb9a0e0f3c682) - - - - - 5c7387f6 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Make Z-encoding comment into a note - - - - - c12b3041 by Leif Metcalf at 2020-09-17T08:51:43-04:00 Cosmetic - - - - - 4f461e1a by Vladislav Zavialov at 2020-09-17T08:52:19-04:00 Parser.y: clarify treatment of @{-# UNPACK #-} Before this patch, we had this parser production: ftype : ... | ftype PREFIX_AT tyarg { ... } And 'tyarg' is defined as follows: tyarg : atype { ... } | unpackedness atype { ... } So one might get the (false) impression that that parser production is intended to parse things like: F @{-# UNPACK #-} X However, the lexer wouldn't produce PREFIX_AT followed by 'unpackedness', as the '@' operator followed by '{-' is not considered prefix. Thus there's no point using 'tyarg' after PREFIX_AT, and a simple 'atype' will suffice: ftype : ... | ftype PREFIX_AT atype { ... } This change has no user-facing consequences. It just makes the grammar a bit more clear. - - - - - 9dec8600 by Benjamin Maurer at 2020-09-17T08:52:56-04:00 Documented '-m' flags for machine specific instruction extensions. See #18641 'Documenting the Expected Undocumented Flags' - - - - - ca48076a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Introduce OutputableP Some types need a Platform value to be pretty-printed: CLabel, Cmm types, instructions, etc. Before this patch they had an Outputable instance and the Platform value was obtained via sdocWithDynFlags. It meant that the *renderer* of the SDoc was responsible of passing the appropriate Platform value (e.g. via the DynFlags given to showSDoc). It put the burden of passing the Platform value on the renderer while the generator of the SDoc knows the Platform it is generating the SDoc for and there is no point passing a different Platform at rendering time. With this patch, we introduce a new OutputableP class: class OutputableP a where pdoc :: Platform -> a -> SDoc With this class we still have some polymorphism as we have with `ppr` (i.e. we can use `pdoc` on a variety of types instead of having a dedicated `pprXXX` function for each XXX type). One step closer removing `sdocWithDynFlags` (#10143) and supporting several platforms (#14335). - - - - - e45c8544 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Generalize OutputableP Add a type parameter for the environment required by OutputableP. It avoids tying Platform with OutputableP. - - - - - 37aa224a by Sylvain Henry at 2020-09-17T20:04:08-04:00 Add note about OutputableP - - - - - 7f2785f2 by Sylvain Henry at 2020-09-17T20:04:08-04:00 Remove pprPrec from Outputable (unused) - - - - - b689f3db by Sylvain Henry at 2020-09-17T20:04:46-04:00 Bignum: add clamping naturalToWord (fix #18697) - - - - - 0799b3de by Ben Gamari at 2020-09-18T15:55:50-04:00 rts/nonmoving: Add missing STM write barrier When updating a TRec for a TVar already part of a transaction we previously neglected to add the old value to the update remembered set. I suspect this was the cause of #18587. - - - - - c4921349 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor foreign export tracking This avoids calling `libc` in the initializers which are responsible for registering foreign exports. We believe this should avoid the corruption observed in #18548. See Note [Tracking foreign exports] in rts/ForeignExports.c for an overview of the new scheme. - - - - - 40dc9106 by Ben Gamari at 2020-09-18T15:56:25-04:00 rts: Refactor unloading of foreign export StablePtrs Previously we would allocate a linked list cell for each foreign export. Now we can avoid this by taking advantage of the fact that they are already broken into groups. - - - - - 45fa8218 by Simon Jakobi at 2020-09-19T06:57:36-04:00 Deprecate Data.Semigroup.Option Libraries email: https://mail.haskell.org/pipermail/libraries/2018-April/028724.html GHC issue: https://gitlab.haskell.org/ghc/ghc/issues/15028 Corresponding PRs for deepseq: * https://github.com/haskell/deepseq/pull/55 * https://github.com/haskell/deepseq/pull/57 Bumps the deepseq submodule. - - - - - 2229d570 by Vladislav Zavialov at 2020-09-19T15:47:24-04:00 Require happy >=1.20 - - - - - a89c2fba by Ben Gamari at 2020-09-19T15:47:24-04:00 ci.sh: Enforce minimum happy/alex versions Also, always invoke cabal-install to ensure that happy/alex symlinks are up-to-date. - - - - - 2f7ef2fb by Ben Gamari at 2020-09-19T15:47:24-04:00 gitlab-ci: Ensure that cabal-install overwrites existing executables Previously cabal-install wouldn't overwrite toolchain executables if they already existed (as they likely would due to caching). - - - - - ac213d26 by Ryan Scott at 2020-09-19T15:48:01-04:00 Wire in constraint tuples This wires in the definitions of the constraint tuple classes. The key changes are in: * `GHC.Builtin.Types`, where the `mk_ctuple` function is used to define constraint tuple type constructors, data constructors, and superclass selector functions, and * `GHC.Builtin.Uniques`. In addition to wiring in the `Unique`s for constraint tuple type and data constructors, we now must wire in the superclass selector functions. Luckily, this proves to be not that challenging. See the newly added comments. Historical note: constraint tuples used to be wired-in until about five years ago, when commit 130e93aab220bdf14d08028771f83df210da340b turned them into known-key names. This was done as part of a larger refactor to reduce the number of special cases for constraint tuples, but the commit message notes that the main reason that constraint tuples were made known-key (as opposed to boxed/unboxed tuples, which are wired in) is because it was awkward to wire in the superclass selectors. This commit solves the problem of wiring in superclass selectors. Fixes #18635. ------------------------- Metric Decrease: T10421 T12150 T12227 T12234 T12425 T13056 T13253-spj T18282 T18304 T5321FD T5321Fun T5837 T9961 Metric Decrease (test_env='x86_64-linux-deb9-unreg-hadrian'): T12707 Metric Decrease (test_env='x86_64-darwin'): T4029 ------------------------- - - - - - e195dae6 by Wander Hillen at 2020-09-19T15:48:41-04:00 Export singleton function from Data.List Data.OldList exports a monomorphized singleton function but it is not re-exported by Data.List. Adding the export to Data.List causes a conflict with a 14-year old function of the same name and type by SPJ in GHC.Utils.Misc. We can't just remove this function because that leads to a problems when building GHC with a stage0 compiler that does not have singleton in Data.List yet. We also can't hide the function in GHC.Utils.Misc since it is not possible to hide a function from a module if the module does not export the function. To work around this, all places where the Utils.Misc singleton was used now use a qualified version like Utils.singleton and in GHC.Utils.Misc we are very specific about which version we export. - - - - - 9c1b8ad9 by Sylvain Henry at 2020-09-19T15:49:19-04:00 Bump Stack resolver - - - - - d05d13ce by John Ericson at 2020-09-19T15:49:57-04:00 Cinch -fno-warn-name-shadowing down to specific GHCi module - - - - - f1accd00 by Sylvain Henry at 2020-09-19T15:49:57-04:00 Add quick-validate Hadrian flavour (quick + -Werror) - - - - - 8f8d51f1 by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix docs who misstated how the RTS treats size suffixes. They are parsed as multiples of 1024. Not 1000. The docs used to imply otherwise. See decodeSize in rts/RtsFlags.c for the logic for this. - - - - - 2ae0edbd by Andreas Klebinger at 2020-09-19T15:50:33-04:00 Fix a codeblock in ghci.rst - - - - - 4df3aa95 by Ben Gamari at 2020-09-19T15:51:07-04:00 users guide: Fix various documentation issues - - - - - 885ecd18 by Ben Gamari at 2020-09-19T15:51:07-04:00 hadrian: Fail on Sphinx syntax errors Specifically the "Inline literal start-string without end-string" warning, which typically means that the user neglected to separate an inline code block from suffix text with a backslash. - - - - - b26cd867 by David Feuer at 2020-09-19T15:51:44-04:00 Unpack the MVar in Compact The `MVar` lock in `Compact` was unnecessarily lazy, creating an extra indirection and wasting two words. Make it strict. - - - - - 760307cf by Artyom Kuznetsov at 2020-09-19T15:52:21-04:00 Remove GADT self-reference check (#11554, #12081, #12174, fixes #15942) Reverts 430f5c84dac1eab550110d543831a70516b5cac8 - - - - - 057db94c by Ben Gamari at 2020-09-19T15:52:56-04:00 rts: Drop field initializer on thread_basic_info_data_t This struct has a number of fields and we only care that the value is initialized with zeros. This eliminates the warnings noted in #17905. - - - - - 87e2e2b1 by Vladislav Zavialov at 2020-09-19T23:55:30+03:00 Resolve shift/reduce conflicts with %shift (#17232) - - - - - 66cba46e by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T12971 as broken on Windows It's unclear why, but this no longer seems to fail. Closes #17945. - - - - - 816811d4 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Unmark T5975[ab] as broken on Windows Sadly it's unclear *why* they have suddenly started working. Closes #7305. - - - - - 43a43d39 by Ben Gamari at 2020-09-20T20:30:57-04:00 base/testsuite: Add missing LANGUAGE pragma in ThreadDelay001 Only affected the Windows codepath. - - - - - ced8f113 by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Update expected output for outofmem on Windows The error originates from osCommitMemory rather than getMBlocks. - - - - - ea08aead by Ben Gamari at 2020-09-20T20:30:57-04:00 testsuite: Mark some GHCi/Makefile tests as broken on Windows See #18718. - - - - - caf6a5a3 by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Fix WinIO error message normalization This wasn't being applied to stderr. - - - - - 93ab3e8d by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark tempfiles as broken on Win32 without WinIO The old POSIX emulation appears to ignore the user-requested prefix. - - - - - 9df77fed by GHC GitLab CI at 2020-09-20T20:30:57-04:00 testsuite: Mark TH_spliceE5_prof as broken on Windows Due to #18721. - - - - - 1a0f8243 by Ryan Scott at 2020-09-21T16:45:47-04:00 Remove unused ThBrackCtxt and ResSigCtxt Fixes #18715. - - - - - 2f222b12 by Ryan Scott at 2020-09-21T16:45:47-04:00 Disallow constraints in KindSigCtxt This patch cleans up how `GHC.Tc.Validity` classifies `UserTypeCtxt`s that can only refer to kind-level positions, which is important for rejecting certain classes of programs. In particular, this patch: * Introduces a new `TypeOrKindCtxt` data type and `typeOrKindCtxt :: UserTypeCtxt -> TypeOrKindCtxt` function, which determines whether a `UserTypeCtxt` can refer to type-level contexts, kind-level contexts, or both. * Defines the existing `allConstraintsAllowed` and `vdqAllowed` functions in terms of `typeOrKindCtxt`, which avoids code duplication and ensures that they stay in sync in the future. The net effect of this patch is that it fixes #18714, in which it was discovered that `allConstraintsAllowed` incorrectly returned `True` for `KindSigCtxt`. Because `typeOrKindCtxt` now correctly classifies `KindSigCtxt` as a kind-level context, this bug no longer occurs. - - - - - aaa51dcf by Ben Gamari at 2020-09-21T16:46:22-04:00 hadrian: Add extra-deps: happy-1.20 to stack.yaml GHC now requires happy-1.20, which isn't available in LTS-16.14. Fixes #18726. - - - - - 6de40f83 by Simon Peyton Jones at 2020-09-22T05:37:24-04:00 Better eta-expansion (again) and don't specilise DFuns This patch fixes #18223, which made GHC generate an exponential amount of code. There are three quite separate changes in here 1. Re-engineer eta-expansion (again). The eta-expander was generating lots of intermediate stuff, which could be optimised away, but which choked the simplifier meanwhile. Relatively easy to kill it off at source. See Note [The EtaInfo mechanism] in GHC.Core.Opt.Arity. The main new thing is the use of pushCoArg in getArg_maybe. 2. Stop Specialise specalising DFuns. This is the cause of a huge (and utterly unnecessary) blowup in program size in #18223. See Note [Do not specialise DFuns] in GHC.Core.Opt.Specialise. I also refactored the Specialise monad a bit... it was silly, because it passed on unchanging values as if they were mutable state. 3. Do an extra Simplifer run, after SpecConstra and before late-Specialise. I found (investigating perf/compiler/T16473) that failing to do this was crippling *both* SpecConstr *and* Specialise. See Note [Simplify after SpecConstr] in GHC.Core.Opt.Pipeline. This change does mean an extra run of the Simplifier, but only with -O2, and I think that's acceptable. T16473 allocates *three* times less with this change. (I changed it to check runtime rather than compile time.) Some smaller consequences * I moved pushCoercion, pushCoArg and friends from SimpleOpt to Arity, because it was needed by the new etaInfoApp. And pushCoValArg now returns a MCoercion rather than Coercion for the argument Coercion. * A minor, incidental improvement to Core pretty-printing This does fix #18223, (which was otherwise uncompilable. Hooray. But there is still a big intermediate because there are some very deeply nested types in that program. Modest reductions in compile-time allocation on a couple of benchmarks T12425 -2.0% T13253 -10.3% Metric increase with -O2, due to extra simplifier run T9233 +5.8% T12227 +1.8% T15630 +5.0% There is a spurious apparent increase on heap residency on T9630, on some architectures at least. I tried it with -G1 and the residency is essentially unchanged. Metric Increase T9233 T12227 T9630 Metric Decrease T12425 T13253 - - - - - 416bd50e by Simon Peyton Jones at 2020-09-22T05:37:59-04:00 Fix the occurrence analyser Ticket #18603 demonstrated that the occurrence analyser's handling of local RULES for imported Ids (which I now call IMP-RULES) was inadequate. It led the simplifier into an infnite loop by failing to label a binder as a loop breaker. The main change in this commit is to treat IMP-RULES in a simple and uniform way: as extra rules for the local binder. See Note [IMP-RULES: local rules for imported functions] This led to quite a bit of refactoring. The result is still tricky, but it's much better than before, and better documented I think. Oh, and it fixes the bug. - - - - - 6fe8a0c7 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck - Comments only: Replace /~ by ≁ - - - - - e9501547 by Sebastian Graf at 2020-09-22T05:38:35-04:00 PmCheck: Rewrite inhabitation test We used to produce inhabitants of a pattern-match refinement type Nabla in the checker in at least two different and mostly redundant ways: 1. There was `provideEvidence` (now called `generateInhabitingPatterns`) which is used by `GHC.HsToCore.PmCheck` to produce non-exhaustive patterns, which produces inhabitants of a Nabla as a sub-refinement type where all match variables are instantiated. 2. There also was `ensure{,All}Inhabited` (now called `inhabitationTest`) which worked slightly different, but was whenever new type constraints or negative term constraints were added. See below why `provideEvidence` and `ensureAllInhabited` can't be the same function, the main reason being performance. 3. And last but not least there was the `nonVoid` test, which tested that a given type was inhabited. We did use this for strict fields and -XEmptyCase in the past. The overlap of (3) with (2) was always a major pet peeve of mine. The latter was quite efficient and proven to work for recursive data types, etc, but could not handle negative constraints well (e.g. we often want to know if a *refined* type is empty, such as `{ x:[a] | x /= [] }`). Lower Your Guards suggested that we could get by with just one, by replacing both functions with `inhabitationTest` in this patch. That was only possible by implementing the structure of φ constraints as in the paper, namely the semantics of φ constructor constraints. This has a number of benefits: a. Proper handling of unlifted types and strict fields, fixing #18249, without any code duplication between `GHC.HsToCore.PmCheck.Oracle.instCon` (was `mkOneConFull`) and `GHC.HsToCore.PmCheck.checkGrd`. b. `instCon` can perform the `nonVoid` test (3) simply by emitting unliftedness constraints for strict fields. c. `nonVoid` (3) is thus simply expressed by a call to `inhabitationTest`. d. Similarly, `ensureAllInhabited` (2), which we called after adding type info, now can similarly be expressed as the fuel-based `inhabitationTest`. See the new `Note [Why inhabitationTest doesn't call generateInhabitingPatterns]` why we still have tests (1) and (2). Fixes #18249 and brings nice metric decreases for `T17836` (-76%) and `T17836b` (-46%), as well as `T18478` (-8%) at the cost of a few very minor regressions (< +2%), potentially due to the fact that `generateInhabitingPatterns` does more work to suggest the minimal COMPLETE set. Metric Decrease: T17836 T17836b - - - - - 086ef018 by Hécate at 2020-09-23T06:52:08-04:00 Remove the list of loaded modules from the ghci prompt - - - - - d7385f70 by Ben Gamari at 2020-09-23T06:52:44-04:00 Bump submodules * Bump bytestring to 0.10.12.0 * Bump Cabal to 3.4.0.0-rc3 * Bump Win32 to 2.10.0.0 - - - - - 667d6355 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Refactor CLabel pretty-printing * Don't depend on the selected backend to know if we print Asm or C labels: we already have PprStyle to determine this. Moreover even when a native backend is used (NCG, LLVM) we may want to C headers containing pretty-printed labels, so it wasn't a good predicate anyway. * Make pretty-printing code clearer and avoid partiality - - - - - a584366b by Sylvain Henry at 2020-09-23T20:43:48-04:00 Remove sdocWithDynFlags (fix #10143) - - - - - a997fa01 by Sylvain Henry at 2020-09-23T20:43:48-04:00 Preliminary work towards removing DynFlags -> Driver.Ppr dependency - - - - - 31fea307 by Hécate at 2020-09-23T20:44:24-04:00 Remove redundant "do", "return" and language extensions from base - - - - - 04d64331 by syd at cs-syd.eu at 2020-09-24T13:15:54-04:00 Update Lock.hs with more documentation to make sure that the Boolean return value is clear. [skip ci] - - - - - 97cff919 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Implement Quick Look impredicativity This patch implements Quick Look impredicativity (#18126), sticking very closely to the design in A quick look at impredicativity, Serrano et al, ICFP 2020 The main change is that a big chunk of GHC.Tc.Gen.Expr has been extracted to two new modules GHC.Tc.Gen.App GHC.Tc.Gen.Head which deal with typechecking n-ary applications, and the head of such applications, respectively. Both contain a good deal of documentation. Three other loosely-related changes are in this patch: * I implemented (partly by accident) points (2,3)) of the accepted GHC proposal "Clean up printing of foralls", namely https://github.com/ghc-proposals/ghc-proposals/blob/ master/proposals/0179-printing-foralls.rst (see #16320). In particular, see Note [TcRnExprMode] in GHC.Tc.Module - :type instantiates /inferred/, but not /specified/, quantifiers - :type +d instantiates /all/ quantifiers - :type +v is killed off That completes the implementation of the proposal, since point (1) was done in commit df08468113ab46832b7ac0a7311b608d1b418c4d Author: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Date: Mon Feb 3 21:17:11 2020 +0100 Always display inferred variables using braces * HsRecFld (which the renamer introduces for record field selectors), is now preserved by the typechecker, rather than being rewritten back to HsVar. This is more uniform, and turned out to be more convenient in the new scheme of things. * The GHCi debugger uses a non-standard unification that allows the unification variables to unify with polytypes. We used to hack this by using ImpredicativeTypes, but that doesn't work anymore so I introduces RuntimeUnkTv. See Note [RuntimeUnkTv] in GHC.Runtime.Heap.Inspect Updates haddock submodule. WARNING: this patch won't validate on its own. It was too hard to fully disentangle it from the following patch, on type errors and kind generalisation. Changes to tests * Fixes #9730 (test added) * Fixes #7026 (test added) * Fixes most of #8808, except function `g2'` which uses a section (which doesn't play with QL yet -- see #18126) Test added * Fixes #1330. NB Church1.hs subsumes Church2.hs, which is now deleted * Fixes #17332 (test added) * Fixes #4295 * This patch makes typecheck/should_run/T7861 fail. But that turns out to be a pre-existing bug: #18467. So I have just made T7861 into expect_broken(18467) - - - - - 9fa26aa1 by Simon Peyton Jones at 2020-09-24T13:16:32-04:00 Improve kind generalisation, error messages This patch does two things: * It refactors GHC.Tc.Errors a bit. In debugging Quick Look I was forced to look in detail at error messages, and ended up doing a bit of refactoring, esp in mkTyVarEqErr'. It's still quite a mess, but a bit better, I think. * It makes a significant improvement to the kind checking of type and class declarations. Specifically, we now ensure that if kind checking fails with an unsolved constraint, all the skolems are in scope. That wasn't the case before, which led to some obscure error messages; and occasional failures with "no skolem info" (eg #16245). Both of these, and the main Quick Look patch itself, affect a /lot/ of error messages, as you can see from the number of files changed. I've checked them all; I think they are as good or better than before. Smaller things * I documented the various instances of VarBndr better. See Note [The VarBndr tyep and its uses] in GHC.Types.Var * Renamed GHC.Tc.Solver.simpl_top to simplifyTopWanteds * A bit of refactoring in bindExplicitTKTele, to avoid the footwork with Either. Simpler now. * Move promoteTyVar from GHC.Tc.Solver to GHC.Tc.Utils.TcMType Fixes #16245 (comment 211369), memorialised as typecheck/polykinds/T16245a Also fixes the three bugs in #18640 - - - - - 6d0ce0eb by Sebastian Graf at 2020-09-24T13:17:07-04:00 PmCheck: Desugar string literal patterns with -XRebindableSyntax correctly (#18708) Fixes #18708. - - - - - 007940d2 by Hécate at 2020-09-24T13:17:44-04:00 Namespace the Hadrian linting rule for base - - - - - 5b727189 by Andreas Klebinger at 2020-09-25T21:10:20-04:00 Make sizeExpr strict in the size threshold to facilitate WW. - - - - - dd664031 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci.sh: Factor out common utilities - - - - - 5b78e865 by Ben Gamari at 2020-09-25T21:10:56-04:00 ci: Add ad-hoc performance testing rule - - - - - 29885f07 by Zubin Duggal at 2020-09-25T21:11:32-04:00 Stop removing definitions of record fields in GHC.Iface.Ext.Ast - - - - - 0d6519d9 by Ben Gamari at 2020-09-25T21:12:08-04:00 gitlab-ci: Drop Darwin cleanup job We now have a proper periodic clean-up script installed on the runners. - - - - - 277d20af by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add regression tests for #18371 They have been fixed by !3959, I believe. Fixes #18371. - - - - - 8edf6056 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Add a regression test for #18609 The egregious performance hits are gone since !4050. So we fix #18609. - - - - - 4a1b89a4 by Sebastian Graf at 2020-09-25T21:12:44-04:00 Accept new test output for #17218 The expected test output was plain wrong. It has been fixed for a long time. Thus we can close #17218. - - - - - 51606236 by Sven Tennie at 2020-09-25T21:13:19-04:00 Print RET_BIG stack closures A RET_BIG closure has a large bitmap that describes it's payload and can be printed with printLargeBitmap(). Additionally, the output for payload closures of small and big bitmaps is changed: printObj() is used to print a bit more information about what's on the stack. - - - - - 2707c4ea by Arnaud Spiwack at 2020-09-25T21:13:58-04:00 Pattern guards BindStmt always use multiplicity Many Fixes #18439 . The rhs of the pattern guard was consumed with multiplicity one, while the pattern assumed it was Many. We use Many everywhere instead. This is behaviour consistent with that of `case` expression. See #18738. - - - - - 92daad24 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: refactor backend modules * move backends into GHC.Num.Backend.* * split backend selection into GHC.Num.Backend and GHC.Num.Backend.Selected to avoid duplication with the Check backend - - - - - 04bc50b3 by Sylvain Henry at 2020-09-25T21:14:36-04:00 Bignum: implement extended GCD (#18427) - - - - - 6a7dae4b by Krzysztof Gogolewski at 2020-09-25T21:15:14-04:00 Fix typed holes causing linearity errors (#18491) - - - - - 83407ffc by Krzysztof Gogolewski at 2020-09-25T21:15:53-04:00 Various documentation fixes * Remove UnliftedFFITypes from conf. Some time ago, this extension was undocumented and we had to silence a warning. This is no longer needed. * Use r'' in conf.py. This fixes a Sphinx warning: WARNING: Support for evaluating Python 2 syntax is deprecated and will be removed in Sphinx 4.0. Convert docs/users_guide/conf.py to Python 3 syntax. * Mark GHCForeignImportPrim as documented * Fix formatting in template_haskell.rst * Remove 'recursive do' from the list of unsupported items in TH - - - - - af1e84e7 by Sebastian Graf at 2020-09-26T05:36:46-04:00 PmCheck: Big refactor of module structure * Move everything from `GHC.HsToCore.PmCheck.*` to `GHC.HsToCore.Pmc.*` in analogy to `GHC.Tc`, rename exported `covCheck*` functions to `pmc*` * Rename `Pmc.Oracle` to `Pmc.Solver` * Split off the LYG desugaring and checking steps into their own modules (`Pmc.Desugar` and `Pmc.Check` respectively) * Split off a `Pmc.Utils` module with stuff shared by `Pmc.{,Desugar,Check,Solver}` * Move `Pmc.Types` to `Pmc.Solver.Types`, add a new `Pmc.Types` module with all the LYG types, which form the interfaces between `Pmc.{Desugar,Check,Solver,}`. - - - - - f08f98e8 by Sebastian Graf at 2020-09-26T05:36:46-04:00 Extract SharedIdEnv into its own module It's now named `GHC.Types.Unique.SDFM.UniqSDFM`. The implementation is more clear about its stated goals and supported operations. - - - - - 1cde295c by Sylvain Henry at 2020-09-26T05:37:23-04:00 Bignum: add bigNatFromWordArray Reimplementation of integer-gmp's byteArrayToBigNat# - - - - - bda55fa0 by Krzysztof Gogolewski at 2020-09-26T13:18:22-04:00 Make 'undefined x' linear in 'x' (#18731) - - - - - 160fba4a by Krzysztof Gogolewski at 2020-09-26T13:19:00-04:00 Disallow linear types in FFI (#18472) - - - - - e124f2a7 by Krzysztof Gogolewski at 2020-09-26T13:19:36-04:00 Fix handling of function coercions (#18747) This was broken when we added multiplicity to the function type. - - - - - 7ff43382 by Vladislav Zavialov at 2020-09-27T03:01:31+03:00 Comments: change outdated reference to mergeOps As of 686e06c59c3aa6b66895e8a501c7afb019b09e36, GHC.Parser.PostProcess.mergeOps no longer exists. [ci skip] - - - - - 4edf5527 by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Don't rearrange (->) in the renamer The parser produces an AST where the (->) is already associated correctly: 1. (->) has the least possible precedence 2. (->) is right-associative Thus we don't need to handle it in mkHsOpTyRn. - - - - - a9ce159b by Vladislav Zavialov at 2020-09-27T10:04:12-04:00 Remove outdated comment in rnHsTyKi This comment dates back to 3df40b7b78044206bbcffe3e2c0a57d901baf5e8 and does not seem relevant anymore. - - - - - 583a2070 by Richard Eisenberg at 2020-09-29T00:31:27-04:00 Optimize NthCo (FunCo ...) in coercion opt We were missing this case previously. Close #18528. Metric Decrease: T18223 T5321Fun - - - - - b31a3360 by Krzysztof Gogolewski at 2020-09-29T00:32:05-04:00 Linear types: fix kind inference when checking datacons - - - - - 5830a12c by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 New linear types syntax: a %p -> b (#18459) Implements GHC Proposal #356 Updates the haddock submodule. - - - - - bca4d36d by Vladislav Zavialov at 2020-09-29T00:32:05-04:00 Improve error messages for (a %m) without LinearTypes Detect when the user forgets to enable the LinearTypes extension and produce a better error message. Steals the (a %m) syntax from TypeOperators, the workaround is to write (a % m) instead. - - - - - b9635d0a by Benjamin Maurer at 2020-09-29T00:32:43-04:00 Description of flag `-H` was in 'verbosity options', moved to 'misc'. Fixes #18699 - - - - - 74c797f6 by Benjamin Maurer at 2020-09-29T00:33:20-04:00 Workaround for #18623: GHC crashes bc. under rlimit for vmem it will reserve _all_ of it, leaving nothing for, e.g., thread stacks. Fix will only allocate 2/3rds and check whether remainder is at least large enough for minimum amount of thread stacks. - - - - - 4365d77a by Ryan Scott at 2020-09-29T00:33:57-04:00 Add regression test #18501 ghc/ghc!3220 ended up fixing #18501. This patch adds a regression test for #18501 to ensure that it stays fixed. - - - - - 8e3f00dd by Sylvain Henry at 2020-09-29T17:24:03+02:00 Make the parser module less dependent on DynFlags Bump haddock submodule - - - - - 3ab0d8f7 by Sebastian Graf at 2020-09-30T02:48:27-04:00 PmCheck: Long-distance information for LocalBinds (#18626) Now `desugarLocalBind` (formerly `desugarLet`) reasons about * `FunBind`s that * Have no pattern matches (so which aren't functions) * Have a singleton match group with a single GRHS * (which may have guards) * and looks through trivial post-typechecking `AbsBinds` in doing so to pick up the introduced renamings. And desugars to `PmLet` LYG-style guards. Since GRHSs are no longer denoted simply by `NonEmpty PmGRHS`, but also need to carry a `[PmGrd]` for the `PmLet`s from `LocalBind`s, I added `PmGRHSs` to capture that. Since we call out to the desugarer more often, I found that there were superfluous warnings emitted when desugaring e.g. case expressions. Thus, I made sure that we deactivate any warnings in the LYG desugaring steps by the new wrapper function `noCheckDs`. There's a regression test in `T18626`. Fixes #18626. - - - - - f8f60efc by Ben Gamari at 2020-09-30T02:49:03-04:00 testsuite: Mark T12971 as broken on Windows Due to #17945. - - - - - 6527fc57 by Ben Gamari at 2020-09-30T02:49:03-04:00 Bump Cabal, hsc2hs, directory, process submodules Necessary for recent Win32 bump. - - - - - df3f5880 by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unsafeGlobalDynFlags (#17957, #14597) There are still global variables but only 3 booleans instead of a single DynFlags. - - - - - 9befd94d by Sylvain Henry at 2020-09-30T02:49:41-04:00 Remove unused global variables Some removed globals variables were still declared in the RTS. They were removed in the following commits: * 4fc6524a2a4a0003495a96c8b84783286f65c198 * 0dc7985663efa1739aafb480759e2e2e7fca2a36 * bbd3c399939311ec3e308721ab87ca6b9443f358 - - - - - 7c98699f by Richard Eisenberg at 2020-09-30T02:50:17-04:00 Omit redundant kind equality check in solver See updated Note [Use loose types in inert set] in GHC.Tc.Solver.Monad. Close #18753. - - - - - 39549826 by Sebastian Graf at 2020-09-30T02:50:54-04:00 Pmc: Don't call exprType on type arguments (#18767) Fixes #18767. - - - - - 235e410f by Richard Eisenberg at 2020-09-30T02:51:29-04:00 Regression test for #10709. Close #10709 - - - - - 5c32655f by Ben Gamari at 2020-09-30T22:31:55-04:00 hadrian/doc: Clarify documentation of key-value configuration - - - - - 0bb02873 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Add test for T18574 - - - - - e393f213 by Sylvain Henry at 2020-10-01T18:34:53-04:00 Allow fusion with catMaybes (#18574) Metric Decrease: T18574 - - - - - d2cfad96 by Fendor at 2020-10-01T18:35:33-04:00 Add mainModuleNameIs and demote mainModIs Add `mainModuleNameIs` to DynFlags and demote `mainModIs` to function which uses the homeUnit from DynFlags it is created from. - - - - - fc351ab8 by Fendor at 2020-10-01T18:35:33-04:00 Use HomeUnit for main module without module declaration - - - - - dca1cb22 by Fendor at 2020-10-01T18:35:33-04:00 Remove mAIN completely - - - - - a5aaceec by Sylvain Henry at 2020-10-01T18:36:11-04:00 Use ADTs for parser errors/warnings Haskell and Cmm parsers/lexers now report errors and warnings using ADTs defined in GHC.Parser.Errors. They can be printed using functions in GHC.Parser.Errors.Ppr. Some of the errors provide hints with a separate ADT (e.g. to suggest to turn on some extension). For now, however, hints are not consistent across all messages. For example some errors contain the hints in the main message. I didn't want to change any message with this patch. I expect these changes to be discussed and implemented later. Surprisingly, this patch enhances performance. On CI (x86_64/deb9/hadrian, ghc/alloc): parsing001 -11.5% T13719 -2.7% MultiLayerModules -3.5% Naperian -3.1% Bump haddock submodule Metric Decrease: MultiLayerModules Naperian T13719 parsing001 - - - - - a946c7ef by Sylvain Henry at 2020-10-01T18:36:11-04:00 Less DynFlags in Header parsing - - - - - dafe7943 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Parser: remove some unused imports These are not reported by GHC because Happy adds {-# OPTIONS_GHC -w #-} - - - - - 93d5de16 by Sylvain Henry at 2020-10-01T18:36:11-04:00 Don't import GHC.Unit to reduce the number of dependencies - - - - - e3655f81 by Sebastian Graf at 2020-10-01T18:36:47-04:00 Don't attach CPR signatures to NOINLINE data structures (#18154) Because the generated `KindRep`s don't have an unfolding, !3230 did not actually stop to compute, attach and serialise unnecessary CPR signatures for them. As already said in `Note [CPR for data structures]`, that leads to bloated interface files which is ultimately quadratic for Nested CPR. So we don't attach any CPR signature to bindings that * Are not thunks (because thunks are not in WHNF) * Have arity 0 (which means the top-level constructor is not a lambda) If the data structure has an unfolding, we continue to look through it. If not (as is the case for `KindRep`s), we look at the unchanged CPR signature and see `topCprType`, as expected. - - - - - ba5965eb by Richard Eisenberg at 2020-10-01T18:37:23-04:00 Add regression test for #18755. Close #18755 - - - - - a8018c17 by Vladislav Zavialov at 2020-10-01T18:37:58-04:00 Fix pretty-printing of the mult-polymorphic arrow A follow-up to !4020 (5830a12c46e7227c276a8a71213057595ee4fc04) - - - - - e5523324 by Sylvain Henry at 2020-10-01T18:38:35-04:00 Bignum: add integerNegate RULE - - - - - 1edd6d21 by Vladislav Zavialov at 2020-10-01T18:39:10-04:00 Refactor: remove rnHsDoc It did not do any useful work. - - - - - a9ae83af by Krzysztof Gogolewski at 2020-10-02T08:00:25-04:00 Fix typos in comments [skip ci] - - - - - b81350bb by Icelandjack at 2020-10-02T08:01:01-04:00 Replaced MkT1 with T1 in type signatures. - - - - - 3c9beab7 by Vladislav Zavialov at 2020-10-02T13:51:58-04:00 Minor TTG clean-up: comments, unused families, bottom 1. Fix and update section headers in GHC/Hs/Extension.hs 2. Delete the unused 'XCoreAnn' and 'XTickPragma' families 3. Avoid calls to 'panic' in 'pprStmt' - - - - - 12c06927 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerRecipMod (#18427) - - - - - 8dd4f405 by Sylvain Henry at 2020-10-02T13:52:38-04:00 Bignum: implement integerPowMod (#18427) Incidentally fix powModInteger which was crashing in integer-gmp for negative exponents when the modular multiplicative inverse for the base didn't exist. Now we compute it explicitly with integerRecipMod so that every backend returns the same result without crashing. - - - - - 1033a720 by Krzysztof Gogolewski at 2020-10-02T13:53:23-04:00 Reject linearity in kinds in checkValidType (#18780) Patch taken from https://gitlab.haskell.org/ghc/ghc/-/issues/18624#note_300673 - - - - - b0ccba66 by Krzysztof Gogolewski at 2020-10-03T19:33:02-04:00 Small documentation fixes - Fix formatting of code blocks and a few sphinx warnings - Move the Void# change to 9.2, it was done right after the branch was cut - Fix typo in linear types documentation - Note that -Wincomplete-uni-patterns affects lazy patterns [skip ci] - - - - - 70dc2f09 by Karel Gardas at 2020-10-03T19:33:06-04:00 fix rts.cabal to use real arch names and not aliasses (fixes #18654) - - - - - bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 1b9d2ab1 by Ben Gamari at 2020-11-29T10:19:44-05:00 nonmoving: Teach allocatePinned() to allocate into nonmoving heap The allocatePinned() function is used to allocate pinned memory (e.g. for newPinnedByteArray#) - - - - - 20 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh - .gitlab/linters/check-cpp.py - README.md - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Uniques.hs - compiler/GHC/Builtin/Uniques.hs-boot - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d8a0cb88f45f9c9a3490472e77cf8e6071e7693a...1b9d2ab1996ac2d9ae9bc430276a63be639ed8d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d8a0cb88f45f9c9a3490472e77cf8e6071e7693a...1b9d2ab1996ac2d9ae9bc430276a63be639ed8d0 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 Sun Nov 29 15:28:00 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 10:28:00 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] gitlab-ci: Add VERBOSE environment variable Message-ID: <5fc3be00dac11_86c879fa9c81843c@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: d3458ac8 by Ben Gamari at 2020-11-29T10:27:15-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. (cherry picked from commit 802e9180dd9a9a88c4e8869f0de1048e1edd6343) - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -348,6 +348,11 @@ function build_make() { if [[ -z "$BIN_DIST_PREP_TAR_COMP" ]]; then fail "BIN_DIST_PREP_TAR_COMP is not set" fi + if [[ -n "$VERBOSE" ]]; then + MAKE_ARGS="$MAKE_ARGS V=1" + else + MAKE_ARGS="$MAKE_ARGS V=0" + fi echo "include mk/flavours/${BUILD_FLAVOUR}.mk" > mk/build.mk echo 'GhcLibHcOpts+=-haddock' >> mk/build.mk @@ -402,6 +407,7 @@ function clean() { } function run_hadrian() { + if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi run hadrian/build.cabal.sh \ --flavour="$FLAVOUR" \ -j"$cores" \ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d3458ac8e1a4cae1cacf25309072bebb7bac70f1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d3458ac8e1a4cae1cacf25309072bebb7bac70f1 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 Sun Nov 29 17:02:30 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 12:02:30 -0500 Subject: [Git][ghc/ghc][wip/no-fptr] 5 commits: GHC.Utils.Binary: Eliminate allocating withForeignPtr uses Message-ID: <5fc3d42696c06_86c157b6ce48278fa@gitlab.mail> Ben Gamari pushed to branch wip/no-fptr at Glasgow Haskell Compiler / GHC Commits: a20e6c8c by Ben Gamari at 2020-11-27T14:33:51-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - 6ca6b8e7 by Ben Gamari at 2020-11-27T14:33:51-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 7d79edbd by Ben Gamari at 2020-11-28T13:12:29-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - fa6edd4d by Ben Gamari at 2020-11-28T13:12:29-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - f40b662b by Ben Gamari at 2020-11-28T13:12:43-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - 4 changed files: - compiler/GHC/Utils/Binary.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/IO/Buffer.hs - libraries/bytestring Changes: ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised @@ -84,6 +85,7 @@ import Data.Array import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import GHC.ForeignPtr import Data.IORef import Data.Char ( ord, chr ) import Data.Time @@ -96,7 +98,10 @@ import GHC.Real ( Ratio(..) ) type BinArray = ForeignPtr Word8 - +#if !MIN_VERSION_base(4,15,0) +unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b +unsafeWithForeignPtr = withForeignPtr +#endif --------------------------------------------------------------- -- BinData @@ -111,14 +116,14 @@ instance Binary BinData where put_ bh (BinData sz dat) = do put_ bh sz putPrim bh sz $ \dest -> - withForeignPtr dat $ \orig -> + unsafeWithForeignPtr dat $ \orig -> copyBytes dest orig sz -- get bh = do sz <- get bh dat <- mallocForeignPtrBytes sz getPrim bh sz $ \orig -> - withForeignPtr dat $ \dest -> + unsafeWithForeignPtr dat $ \dest -> copyBytes dest orig sz return (BinData sz dat) @@ -226,7 +231,7 @@ writeBinMem (BinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode arr <- readIORef arr_r ix <- readFastMutInt ix_r - withForeignPtr arr $ \p -> hPutBuf h p ix + unsafeWithForeignPtr arr $ \p -> hPutBuf h p ix hClose h readBinMem :: FilePath -> IO BinHandle @@ -236,7 +241,7 @@ readBinMem filename = do filesize' <- hFileSize h let filesize = fromIntegral filesize' arr <- mallocForeignPtrBytes filesize - count <- withForeignPtr arr $ \p -> hGetBuf h p filesize + count <- unsafeWithForeignPtr arr $ \p -> hGetBuf h p filesize when (count /= filesize) $ error ("Binary.readBinMem: only read " ++ show count ++ " bytes") hClose h @@ -280,7 +285,7 @@ putPrim h@(BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ expandBin h (ix + size) arr <- readIORef arr_r - withForeignPtr arr $ \op -> f (op `plusPtr` ix) + unsafeWithForeignPtr arr $ \op -> f (op `plusPtr` ix) writeFastMutInt ix_r (ix + size) -- -- | Similar to putPrim but advances the index by the actual number of @@ -302,7 +307,10 @@ getPrim (BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing) arr <- readIORef arr_r - w <- withForeignPtr arr $ \op -> f (op `plusPtr` ix) + w <- f (unsafeForeignPtrToPtr arr `plusPtr` ix) + touchForeignPtr arr + -- This is safe WRT #17760 as we we guarantee that the above line doesn't + -- diverge writeFastMutInt ix_r (ix + size) return w ===================================== libraries/base/GHC/Event/Array.hs ===================================== @@ -33,7 +33,7 @@ import Foreign.ForeignPtr (ForeignPtr, withForeignPtr) import Foreign.Ptr (Ptr, nullPtr, plusPtr) import Foreign.Storable (Storable(..)) import GHC.Base hiding (empty) -import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_) +import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_, unsafeWithForeignPtr) import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (show) @@ -78,9 +78,9 @@ reallocArray p newSize oldSize = reallocHack undefined p reallocHack dummy src = do let size = sizeOf dummy dst <- mallocPlainForeignPtrBytes (newSize * size) - withForeignPtr src $ \s -> + unsafeWithForeignPtr src $ \s -> when (s /= nullPtr && oldSize > 0) . - withForeignPtr dst $ \d -> do + unsafeWithForeignPtr dst $ \d -> do _ <- memcpy d s (fromIntegral (oldSize * size)) return () return dst @@ -99,8 +99,8 @@ duplicate a = dupHack undefined a dupHack dummy (Array ref) = do AC es len cap <- readIORef ref ary <- allocArray cap - withForeignPtr ary $ \dest -> - withForeignPtr es $ \src -> do + unsafeWithForeignPtr ary $ \dest -> + unsafeWithForeignPtr es $ \src -> do _ <- memcpy dest src (fromIntegral (len * sizeOf dummy)) return () Array `fmap` newIORef (AC ary len cap) @@ -119,8 +119,8 @@ unsafeRead :: Storable a => Array a -> Int -> IO a unsafeRead (Array ref) ix = do AC es _ cap <- readIORef ref CHECK_BOUNDS("unsafeRead",cap,ix) - withForeignPtr es $ \p -> - peekElemOff p ix + unsafeWithForeignPtr es $ \ptr -> peekElemOff ptr ix + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge unsafeWrite :: Storable a => Array a -> Int -> a -> IO () unsafeWrite (Array ref) ix a = do @@ -130,13 +130,15 @@ unsafeWrite (Array ref) ix a = do unsafeWrite' :: Storable a => AC a -> Int -> a -> IO () unsafeWrite' (AC es _ cap) ix a = CHECK_BOUNDS("unsafeWrite'",cap,ix) - withForeignPtr es $ \p -> - pokeElemOff p ix a + unsafeWithForeignPtr es $ \ptr -> pokeElemOff ptr ix a + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge +-- | Precondition: continuation must not diverge due to use of +-- 'unsafeWithForeignPtr'. unsafeLoad :: Array a -> (Ptr a -> Int -> IO Int) -> IO Int unsafeLoad (Array ref) load = do AC es _ cap <- readIORef ref - len' <- withForeignPtr es $ \p -> load p cap + len' <- unsafeWithForeignPtr es $ \p -> load p cap writeIORef ref (AC es len' cap) return len' @@ -146,7 +148,7 @@ unsafeCopyFromBuffer :: Storable a => Array a -> Ptr a -> Int -> IO () unsafeCopyFromBuffer (Array ref) sptr n = readIORef ref >>= \(AC es _ cap) -> CHECK_BOUNDS("unsafeCopyFromBuffer", cap, n) - withForeignPtr es $ \pdest -> do + unsafeWithForeignPtr es $ \pdest -> do let size = sizeOfPtr sptr undefined _ <- memcpy pdest sptr (fromIntegral $ n * size) writeIORef ref (AC es n cap) @@ -198,7 +200,7 @@ forM_ ary g = forHack ary g undefined AC es len _ <- readIORef ref let size = sizeOf dummy offset = len * size - withForeignPtr es $ \p -> do + unsafeWithForeignPtr es $ \p -> do let go n | n >= offset = return () | otherwise = do f =<< peek (p `plusPtr` n) @@ -269,8 +271,8 @@ copy' d dstart s sstart maxCount = copyHack d s undefined then return dac else do AC dst dlen dcap <- ensureCapacity' dac (dstart + count) - withForeignPtr dst $ \dptr -> - withForeignPtr src $ \sptr -> do + unsafeWithForeignPtr dst $ \dptr -> + unsafeWithForeignPtr src $ \sptr -> do _ <- memcpy (dptr `plusPtr` (dstart * size)) (sptr `plusPtr` (sstart * size)) (fromIntegral (count * size)) @@ -286,7 +288,7 @@ removeAt a i = removeHack a undefined let size = sizeOf dummy newLen = oldLen - 1 when (newLen > 0 && i < newLen) . - withForeignPtr fp $ \ptr -> do + unsafeWithForeignPtr fp $ \ptr -> do _ <- memmove (ptr `plusPtr` (size * i)) (ptr `plusPtr` (size * (i+1))) (fromIntegral (size * (newLen-i))) ===================================== libraries/base/GHC/IO/Buffer.hs ===================================== @@ -73,6 +73,7 @@ import GHC.Show import GHC.Real import GHC.List import GHC.ForeignPtr.Ops +import GHC.ForeignPtr (unsafeWithForeignPtr) import Foreign.C.Types import Foreign.ForeignPtr import Foreign.Storable @@ -118,17 +119,17 @@ type CharBufElem = Char type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char -peekCharBuf arr ix = withForeignPtr arr $ \p -> do +peekCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> do (c,_) <- readCharBufPtr p ix return c {-# INLINE readCharBuf #-} readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) -readCharBuf arr ix = withForeignPtr arr $ \p -> readCharBufPtr p ix +readCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> readCharBufPtr p ix {-# INLINE writeCharBuf #-} writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int -writeCharBuf arr ix c = withForeignPtr arr $ \p -> writeCharBufPtr p ix c +writeCharBuf arr ix c = unsafeWithForeignPtr arr $ \p -> writeCharBufPtr p ix c {-# INLINE readCharBufPtr #-} readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit e043aacfc4202a59ccae8b8c8cf0e1ad83a3f209 +Subproject commit 8d5d8bd463f10244e3754dd03e4bf020a0ea03e3 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0f4327d893252acf6a7e7d4914a8168b2f16944e...f40b662b9ea555bab6e9729f4165eaca7021d322 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0f4327d893252acf6a7e7d4914a8168b2f16944e...f40b662b9ea555bab6e9729f4165eaca7021d322 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 Sun Nov 29 17:04:02 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 12:04:02 -0500 Subject: [Git][ghc/ghc][wip/keepAlive-the-return-of-the-primop] 13 commits: GHC.Utils.Binary: Eliminate allocating withForeignPtr uses Message-ID: <5fc3d48277009_86cf5745688287d8@gitlab.mail> Ben Gamari pushed to branch wip/keepAlive-the-return-of-the-primop at Glasgow Haskell Compiler / GHC Commits: a20e6c8c by Ben Gamari at 2020-11-27T14:33:51-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - 6ca6b8e7 by Ben Gamari at 2020-11-27T14:33:51-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 7d79edbd by Ben Gamari at 2020-11-28T13:12:29-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - fa6edd4d by Ben Gamari at 2020-11-28T13:12:29-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - f40b662b by Ben Gamari at 2020-11-28T13:12:43-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - 6aad2ebe by Ben Gamari at 2020-11-29T12:03:51-05:00 genprimopcode: Add a second levity-polymorphic tyvar This will be needed shortly. - - - - - effa1308 by GHC GitLab CI at 2020-11-29T12:03:51-05:00 Introduce keepAlive primop - - - - - 4b8b9241 by Ben Gamari at 2020-11-29T12:03:51-05:00 base: Use keepAlive# in withForeignPtr - - - - - d11752ef by Ben Gamari at 2020-11-29T12:03:51-05:00 Implement withByteArrayContents in terms of keepAlive# - - - - - 94f3ac80 by Ben Gamari at 2020-11-29T12:03:51-05:00 base: Implement GHC.ForeignPtr.Ops in terms of keepAlive# - - - - - 8f7df80b by Ben Gamari at 2020-11-29T12:03:51-05:00 base: Use keepAlive# in Foreign.Marshal.Alloc - - - - - 7c7506bf by Ben Gamari at 2020-11-29T12:03:51-05:00 ghc-compact: Use keepAlive# in GHC.Compact.Serialized - - - - - b7910e3f by Ben Gamari at 2020-11-29T12:03:51-05:00 testsuite: Accept - - - - - 18 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToStg/Prep.hs - compiler/GHC/Data/ByteArray.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Utils/Binary.hs - libraries/base/Foreign/Marshal/Alloc.hs - libraries/base/GHC/Event/Array.hs - libraries/base/GHC/ForeignPtr.hs - libraries/base/GHC/ForeignPtr/Ops.hs - libraries/base/GHC/IO/Buffer.hs - libraries/bytestring - libraries/ghc-compact/GHC/Compact/Serialized.hs - testsuite/tests/ghci/should_fail/T15055.stderr - testsuite/tests/package/package06e.stderr - testsuite/tests/package/package07e.stderr - testsuite/tests/package/package08e.stderr - utils/genprimopcode/Main.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -2963,6 +2963,20 @@ primop NumSparks "numSparks#" GenPrimOp has_side_effects = True out_of_line = True + +------------------------------------------------------------------------ +section "Controlling object lifetime" + {Ensuring that objects don't die a premature death.} +------------------------------------------------------------------------ + +-- See Note [keepAlive# magic] in GHC.CoreToStg.Prep. +primop KeepAliveOp "keepAlive#" GenPrimOp + o -> State# RealWorld -> (State# RealWorld -> p) -> p + { TODO. } + with + strictness = { \ _arity -> mkClosedStrictSig [topDmd, topDmd, strictOnceApply1Dmd] topDiv } + + ------------------------------------------------------------------------ section "Tag to enum stuff" {Convert back and forth between values of enumerated types ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -1642,6 +1642,8 @@ app_ok primop_ok fun args -> False -- for the special cases for SeqOp and DataToTagOp | DataToTagOp <- op -> False + | KeepAliveOp <- op + -> False | otherwise -> primop_ok op -- Check the primop itself ===================================== compiler/GHC/CoreToStg/Prep.hs ===================================== @@ -32,7 +32,10 @@ import GHC.Tc.Utils.Env import GHC.Unit import GHC.Builtin.Names +import GHC.Builtin.PrimOps import GHC.Builtin.Types +import GHC.Builtin.Types.Prim ( realWorldStatePrimTy ) +import GHC.Types.Id.Make ( realWorldPrimId, mkPrimOpId ) import GHC.Core.Utils import GHC.Core.Opt.Arity @@ -47,6 +50,7 @@ import GHC.Core.TyCon import GHC.Core.DataCon import GHC.Core.Opt.OccurAnal + import GHC.Data.Maybe import GHC.Data.OrdList import GHC.Data.FastString @@ -63,7 +67,6 @@ import GHC.Types.Var.Set import GHC.Types.Var.Env import GHC.Types.Id import GHC.Types.Id.Info -import GHC.Types.Id.Make ( realWorldPrimId ) import GHC.Types.Basic import GHC.Types.Name ( NamedThing(..), nameSrcSpan, isInternalName ) import GHC.Types.SrcLoc ( SrcSpan(..), realSrcLocSpan, mkRealSrcLoc ) @@ -784,6 +787,38 @@ cpeApp top_env expr -- rather than the far superior "f x y". Test case is par01. = let (terminal, args', depth') = collect_args arg in cpe_app env terminal (args' ++ args) (depth + depth' - 1) + + cpe_app env + (Var f) + args + n + | Just KeepAliveOp <- isPrimOpId_maybe f + , CpeApp (Type arg_rep) + : CpeApp (Type arg_ty) + : CpeApp (Type _result_rep) + : CpeApp (Type result_ty) + : CpeApp arg + : CpeApp s0 + : CpeApp k + : rest <- pprTrace "cpe_app keepAlive#" (ppr args) args + = do { pprTraceM "cpe_app(keepAlive#)" (ppr n) + ; y <- newVar result_ty + ; s2 <- newVar realWorldStatePrimTy + ; -- beta reduce if possible + ; (floats, k') <- case k of + Lam s body -> cpe_app (extendCorePrepEnvExpr env s s0) body rest (n-2) + _ -> cpe_app env k (CpeApp s0 : rest) (n-1) + ; let touchId = mkPrimOpId TouchOp + expr = Case k' y result_ty [(DEFAULT, [], rhs)] + rhs = let scrut = mkApps (Var touchId) [Type arg_rep, Type arg_ty, arg, Var realWorldPrimId] + in Case scrut s2 result_ty [(DEFAULT, [], Var y)] + ; pprTraceM "cpe_app(keepAlive)" (ppr expr) + ; (floats', expr') <- cpeBody env expr + ; return (floats `appendFloats` floats', expr') + } + | Just KeepAliveOp <- isPrimOpId_maybe f + = panic "invalid keepAlive# application" + cpe_app env (Var f) (CpeApp _runtimeRep at Type{} : CpeApp _type at Type{} : CpeApp arg : rest) n | f `hasKey` runRWKey -- N.B. While it may appear that n == 1 in the case of runRW# ===================================== compiler/GHC/Data/ByteArray.hs ===================================== @@ -77,10 +77,15 @@ unsafeMutableByteArrayContents :: MutableByteArray -> Ptr a unsafeMutableByteArrayContents = unsafeByteArrayContents . unsafeCoerce withByteArrayContents :: ByteArray -> (Ptr a -> IO b) -> IO b +#if MIN_VERSION_base(4,15,0) +withByteArrayContents (ByteArray ba) f = + IO $ \s -> keepAlive# ba s (unIO (f (Ptr (byteArrayContents# ba)))) +#else withByteArrayContents (ByteArray ba) f = do r <- f $ Ptr (byteArrayContents# ba) IO $ \s -> case touch# ba s of s' -> (# s', () #) return r +#endif newMutableByteArray :: Int -> IO MutableByteArray newMutableByteArray (I# size) = IO $ \s -> ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1541,6 +1541,8 @@ emitPrimOp dflags primop = case primop of TraceMarkerOp -> alwaysExternal SetThreadAllocationCounter -> alwaysExternal + KeepAliveOp -> panic "keepAlive# should have been eliminated in CorePrep" + where profile = targetProfile dflags platform = profilePlatform profile ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised @@ -84,6 +85,7 @@ import Data.Array import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import GHC.ForeignPtr import Data.IORef import Data.Char ( ord, chr ) import Data.Time @@ -96,7 +98,10 @@ import GHC.Real ( Ratio(..) ) type BinArray = ForeignPtr Word8 - +#if !MIN_VERSION_base(4,15,0) +unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b +unsafeWithForeignPtr = withForeignPtr +#endif --------------------------------------------------------------- -- BinData @@ -111,14 +116,14 @@ instance Binary BinData where put_ bh (BinData sz dat) = do put_ bh sz putPrim bh sz $ \dest -> - withForeignPtr dat $ \orig -> + unsafeWithForeignPtr dat $ \orig -> copyBytes dest orig sz -- get bh = do sz <- get bh dat <- mallocForeignPtrBytes sz getPrim bh sz $ \orig -> - withForeignPtr dat $ \dest -> + unsafeWithForeignPtr dat $ \dest -> copyBytes dest orig sz return (BinData sz dat) @@ -226,7 +231,7 @@ writeBinMem (BinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode arr <- readIORef arr_r ix <- readFastMutInt ix_r - withForeignPtr arr $ \p -> hPutBuf h p ix + unsafeWithForeignPtr arr $ \p -> hPutBuf h p ix hClose h readBinMem :: FilePath -> IO BinHandle @@ -236,7 +241,7 @@ readBinMem filename = do filesize' <- hFileSize h let filesize = fromIntegral filesize' arr <- mallocForeignPtrBytes filesize - count <- withForeignPtr arr $ \p -> hGetBuf h p filesize + count <- unsafeWithForeignPtr arr $ \p -> hGetBuf h p filesize when (count /= filesize) $ error ("Binary.readBinMem: only read " ++ show count ++ " bytes") hClose h @@ -280,7 +285,7 @@ putPrim h@(BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ expandBin h (ix + size) arr <- readIORef arr_r - withForeignPtr arr $ \op -> f (op `plusPtr` ix) + unsafeWithForeignPtr arr $ \op -> f (op `plusPtr` ix) writeFastMutInt ix_r (ix + size) -- -- | Similar to putPrim but advances the index by the actual number of @@ -302,7 +307,10 @@ getPrim (BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing) arr <- readIORef arr_r - w <- withForeignPtr arr $ \op -> f (op `plusPtr` ix) + w <- f (unsafeForeignPtrToPtr arr `plusPtr` ix) + touchForeignPtr arr + -- This is safe WRT #17760 as we we guarantee that the above line doesn't + -- diverge writeFastMutInt ix_r (ix + size) return w ===================================== libraries/base/Foreign/Marshal/Alloc.hs ===================================== @@ -116,19 +116,6 @@ alloca :: forall a b . Storable a => (Ptr a -> IO b) -> IO b alloca = allocaBytesAligned (sizeOf (undefined :: a)) (alignment (undefined :: a)) --- Note [NOINLINE for touch#] --- ~~~~~~~~~~~~~~~~~~~~~~~~~~ --- Both allocaBytes and allocaBytesAligned use the touch#, which is notoriously --- fragile in the presence of simplification (see #14346). In particular, the --- simplifier may drop the continuation containing the touch# if it can prove --- that the action passed to allocaBytes will not return. The hack introduced to --- fix this for 8.2.2 is to mark allocaBytes as NOINLINE, ensuring that the --- simplifier can't see the divergence. --- --- These can be removed once #14375 is fixed, which suggests that we instead do --- away with touch# in favor of a primitive that will capture the scoping left --- implicit in the case of touch#. - -- |@'allocaBytes' n f@ executes the computation @f@, passing as argument -- a pointer to a temporarily allocated block of memory of @n@ bytes. -- The block of memory is sufficiently aligned for any of the basic @@ -143,12 +130,8 @@ allocaBytes (I# size) action = IO $ \ s0 -> case unsafeFreezeByteArray# mbarr# s1 of { (# s2, barr# #) -> let addr = Ptr (byteArrayContents# barr#) in case action addr of { IO action' -> - case action' s2 of { (# s3, r #) -> - case touch# barr# s3 of { s4 -> - (# s4, r #) - }}}}} --- See Note [NOINLINE for touch#] -{-# NOINLINE allocaBytes #-} + keepAlive# barr# s2 action' + }}} allocaBytesAligned :: Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> @@ -156,12 +139,8 @@ allocaBytesAligned (I# size) (I# align) action = IO $ \ s0 -> case unsafeFreezeByteArray# mbarr# s1 of { (# s2, barr# #) -> let addr = Ptr (byteArrayContents# barr#) in case action addr of { IO action' -> - case action' s2 of { (# s3, r #) -> - case touch# barr# s3 of { s4 -> - (# s4, r #) - }}}}} --- See Note [NOINLINE for touch#] -{-# NOINLINE allocaBytesAligned #-} + keepAlive# barr# s2 action' + }}} -- |Resize a memory area that was allocated with 'malloc' or 'mallocBytes' -- to the size needed to store values of type @b at . The returned pointer ===================================== libraries/base/GHC/Event/Array.hs ===================================== @@ -33,7 +33,7 @@ import Foreign.ForeignPtr (ForeignPtr, withForeignPtr) import Foreign.Ptr (Ptr, nullPtr, plusPtr) import Foreign.Storable (Storable(..)) import GHC.Base hiding (empty) -import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_) +import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_, unsafeWithForeignPtr) import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (show) @@ -78,9 +78,9 @@ reallocArray p newSize oldSize = reallocHack undefined p reallocHack dummy src = do let size = sizeOf dummy dst <- mallocPlainForeignPtrBytes (newSize * size) - withForeignPtr src $ \s -> + unsafeWithForeignPtr src $ \s -> when (s /= nullPtr && oldSize > 0) . - withForeignPtr dst $ \d -> do + unsafeWithForeignPtr dst $ \d -> do _ <- memcpy d s (fromIntegral (oldSize * size)) return () return dst @@ -99,8 +99,8 @@ duplicate a = dupHack undefined a dupHack dummy (Array ref) = do AC es len cap <- readIORef ref ary <- allocArray cap - withForeignPtr ary $ \dest -> - withForeignPtr es $ \src -> do + unsafeWithForeignPtr ary $ \dest -> + unsafeWithForeignPtr es $ \src -> do _ <- memcpy dest src (fromIntegral (len * sizeOf dummy)) return () Array `fmap` newIORef (AC ary len cap) @@ -119,8 +119,8 @@ unsafeRead :: Storable a => Array a -> Int -> IO a unsafeRead (Array ref) ix = do AC es _ cap <- readIORef ref CHECK_BOUNDS("unsafeRead",cap,ix) - withForeignPtr es $ \p -> - peekElemOff p ix + unsafeWithForeignPtr es $ \ptr -> peekElemOff ptr ix + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge unsafeWrite :: Storable a => Array a -> Int -> a -> IO () unsafeWrite (Array ref) ix a = do @@ -130,13 +130,15 @@ unsafeWrite (Array ref) ix a = do unsafeWrite' :: Storable a => AC a -> Int -> a -> IO () unsafeWrite' (AC es _ cap) ix a = CHECK_BOUNDS("unsafeWrite'",cap,ix) - withForeignPtr es $ \p -> - pokeElemOff p ix a + unsafeWithForeignPtr es $ \ptr -> pokeElemOff ptr ix a + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge +-- | Precondition: continuation must not diverge due to use of +-- 'unsafeWithForeignPtr'. unsafeLoad :: Array a -> (Ptr a -> Int -> IO Int) -> IO Int unsafeLoad (Array ref) load = do AC es _ cap <- readIORef ref - len' <- withForeignPtr es $ \p -> load p cap + len' <- unsafeWithForeignPtr es $ \p -> load p cap writeIORef ref (AC es len' cap) return len' @@ -146,7 +148,7 @@ unsafeCopyFromBuffer :: Storable a => Array a -> Ptr a -> Int -> IO () unsafeCopyFromBuffer (Array ref) sptr n = readIORef ref >>= \(AC es _ cap) -> CHECK_BOUNDS("unsafeCopyFromBuffer", cap, n) - withForeignPtr es $ \pdest -> do + unsafeWithForeignPtr es $ \pdest -> do let size = sizeOfPtr sptr undefined _ <- memcpy pdest sptr (fromIntegral $ n * size) writeIORef ref (AC es n cap) @@ -198,7 +200,7 @@ forM_ ary g = forHack ary g undefined AC es len _ <- readIORef ref let size = sizeOf dummy offset = len * size - withForeignPtr es $ \p -> do + unsafeWithForeignPtr es $ \p -> do let go n | n >= offset = return () | otherwise = do f =<< peek (p `plusPtr` n) @@ -269,8 +271,8 @@ copy' d dstart s sstart maxCount = copyHack d s undefined then return dac else do AC dst dlen dcap <- ensureCapacity' dac (dstart + count) - withForeignPtr dst $ \dptr -> - withForeignPtr src $ \sptr -> do + unsafeWithForeignPtr dst $ \dptr -> + unsafeWithForeignPtr src $ \sptr -> do _ <- memcpy (dptr `plusPtr` (dstart * size)) (sptr `plusPtr` (sstart * size)) (fromIntegral (count * size)) @@ -286,7 +288,7 @@ removeAt a i = removeHack a undefined let size = sizeOf dummy newLen = oldLen - 1 when (newLen > 0 && i < newLen) . - withForeignPtr fp $ \ptr -> do + unsafeWithForeignPtr fp $ \ptr -> do _ <- memmove (ptr `plusPtr` (size * i)) (ptr `plusPtr` (size * (i+1))) (fromIntegral (size * (newLen-i))) ===================================== libraries/base/GHC/ForeignPtr.hs ===================================== @@ -526,7 +526,9 @@ withForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b -- or from the object pointed to by the -- 'ForeignPtr', using the operations from the -- 'Storable' class. -withForeignPtr = unsafeWithForeignPtr +withForeignPtr fo@(ForeignPtr _ r) f = IO $ \s -> + case f (unsafeForeignPtrToPtr fo) of + IO action# -> keepAlive# r s action# -- | This is similar to 'withForeignPtr' but comes with an important caveat: -- the user must guarantee that the continuation does not diverge (e.g. loop or ===================================== libraries/base/GHC/ForeignPtr/Ops.hs ===================================== @@ -51,121 +51,114 @@ import GHC.Word import GHC.Int import GHC.Base import GHC.ForeignPtr -import GHC.Ptr - -withFP :: ForeignPtr a - -> (Addr# -> State# RealWorld -> (# State# RealWorld, b #)) - -> IO b -withFP fp f = - withForeignPtr fp (\(Ptr addr) -> IO (f addr)) peekWord8ForeignPtr :: ForeignPtr ty -> Int -> IO Word8 -peekWord8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord8OffAddr# addr d s0 of +peekWord8ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord8OffAddr# addr d) of (# s1, r #) -> (# s1, W8# r #) peekWord16ForeignPtr :: ForeignPtr ty -> Int -> IO Word16 -peekWord16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord16OffAddr# addr d s0 of +peekWord16ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord16OffAddr# addr d) of (# s1, r #) -> (# s1, W16# r #) peekWord32ForeignPtr :: ForeignPtr ty -> Int -> IO Word32 -peekWord32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord32OffAddr# addr d s0 of +peekWord32ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord32OffAddr# addr d) of (# s1, r #) -> (# s1, W32# r #) peekWord64ForeignPtr :: ForeignPtr ty -> Int -> IO Word64 -peekWord64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord64OffAddr# addr d s0 of +peekWord64ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord64OffAddr# addr d) of (# s1, r #) -> (# s1, W64# r #) peekWordForeignPtr :: ForeignPtr ty -> Int -> IO Word -peekWordForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readWord64OffAddr# addr d s0 of +peekWordForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readWord64OffAddr# addr d) of (# s1, r #) -> (# s1, W# r #) peekInt8ForeignPtr :: ForeignPtr ty -> Int -> IO Int8 -peekInt8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt8ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I8# r #) peekInt16ForeignPtr :: ForeignPtr ty -> Int -> IO Int16 -peekInt16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt16ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I16# r #) peekInt32ForeignPtr :: ForeignPtr ty -> Int -> IO Int32 -peekInt32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt32ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I32# r #) peekInt64ForeignPtr :: ForeignPtr ty -> Int -> IO Int64 -peekInt64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekInt64ForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I64# r #) peekIntForeignPtr :: ForeignPtr ty -> Int -> IO Int -peekIntForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readInt64OffAddr# addr d s0 of +peekIntForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readInt64OffAddr# addr d) of (# s1, r #) -> (# s1, I# r #) peekCharForeignPtr :: ForeignPtr ty -> Int -> IO Char -peekCharForeignPtr fp (I# d) = withFP fp $ \addr s0 -> - case readCharOffAddr# addr d s0 of +peekCharForeignPtr (ForeignPtr addr c) (I# d) = IO $ \s0 -> + case keepAlive# c s0 (readCharOffAddr# addr d) of (# s1, r #) -> (# s1, C# r #) pokeWord8ForeignPtr :: ForeignPtr ty -> Int -> Word8 -> IO () -pokeWord8ForeignPtr fp (I# d) (W8# n) = withFP fp $ \addr s0 -> - case writeWord8OffAddr# addr d n s0 of +pokeWord8ForeignPtr (ForeignPtr addr c) (I# d) (W8# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord8OffAddr# addr d n) of s1 -> (# s1, () #) pokeWord16ForeignPtr :: ForeignPtr ty -> Int -> Word16 -> IO () -pokeWord16ForeignPtr fp (I# d) (W16# n) = withFP fp $ \addr s0 -> - case writeWord16OffAddr# addr d n s0 of +pokeWord16ForeignPtr (ForeignPtr addr c) (I# d) (W16# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord16OffAddr# addr d n) of s1 -> (# s1, () #) pokeWord32ForeignPtr :: ForeignPtr ty -> Int -> Word32 -> IO () -pokeWord32ForeignPtr fp (I# d) (W32# n) = withFP fp $ \addr s0 -> - case writeWord32OffAddr# addr d n s0 of +pokeWord32ForeignPtr (ForeignPtr addr c) (I# d) (W32# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord32OffAddr# addr d n) of s1 -> (# s1, () #) pokeWord64ForeignPtr :: ForeignPtr ty -> Int -> Word64 -> IO () -pokeWord64ForeignPtr fp (I# d) (W64# n) = withFP fp $ \addr s0 -> - case writeWord64OffAddr# addr d n s0 of +pokeWord64ForeignPtr (ForeignPtr addr c) (I# d) (W64# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord64OffAddr# addr d n) of s1 -> (# s1, () #) pokeWordForeignPtr :: ForeignPtr ty -> Int -> Word -> IO () -pokeWordForeignPtr fp (I# d) (W# n) = withFP fp $ \addr s0 -> - case writeWord64OffAddr# addr d n s0 of +pokeWordForeignPtr (ForeignPtr addr c) (I# d) (W# n) = IO $ \s0 -> + case keepAlive# c s0 (writeWord64OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt8ForeignPtr :: ForeignPtr ty -> Int -> Int8 -> IO () -pokeInt8ForeignPtr fp (I# d) (I8# n) = withFP fp $ \addr s0 -> - case writeInt8OffAddr# addr d n s0 of +pokeInt8ForeignPtr (ForeignPtr addr c) (I# d) (I8# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt8OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt16ForeignPtr :: ForeignPtr ty -> Int -> Int16 -> IO () -pokeInt16ForeignPtr fp (I# d) (I16# n) = withFP fp $ \addr s0 -> - case writeInt16OffAddr# addr d n s0 of +pokeInt16ForeignPtr (ForeignPtr addr c) (I# d) (I16# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt16OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt32ForeignPtr :: ForeignPtr ty -> Int -> Int32 -> IO () -pokeInt32ForeignPtr fp (I# d) (I32# n) = withFP fp $ \addr s0 -> - case writeInt32OffAddr# addr d n s0 of +pokeInt32ForeignPtr (ForeignPtr addr c) (I# d) (I32# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt32OffAddr# addr d n) of s1 -> (# s1, () #) pokeInt64ForeignPtr :: ForeignPtr ty -> Int -> Int64 -> IO () -pokeInt64ForeignPtr fp (I# d) (I64# n) = withFP fp $ \addr s0 -> - case writeInt64OffAddr# addr d n s0 of +pokeInt64ForeignPtr (ForeignPtr addr c) (I# d) (I64# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt64OffAddr# addr d n) of s1 -> (# s1, () #) pokeIntForeignPtr :: ForeignPtr ty -> Int -> Int -> IO () -pokeIntForeignPtr fp (I# d) (I# n) = withFP fp $ \addr s0 -> - case writeInt64OffAddr# addr d n s0 of +pokeIntForeignPtr (ForeignPtr addr c) (I# d) (I# n) = IO $ \s0 -> + case keepAlive# c s0 (writeInt64OffAddr# addr d n) of s1 -> (# s1, () #) pokeCharForeignPtr :: ForeignPtr ty -> Int -> Char -> IO () -pokeCharForeignPtr fp (I# d) (C# n) = withFP fp $ \addr s0 -> - case writeCharOffAddr# addr d n s0 of +pokeCharForeignPtr (ForeignPtr addr c) (I# d) (C# n) = IO $ \s0 -> + case keepAlive# c s0 (writeCharOffAddr# addr d n) of s1 -> (# s1, () #) ===================================== libraries/base/GHC/IO/Buffer.hs ===================================== @@ -73,6 +73,7 @@ import GHC.Show import GHC.Real import GHC.List import GHC.ForeignPtr.Ops +import GHC.ForeignPtr (unsafeWithForeignPtr) import Foreign.C.Types import Foreign.ForeignPtr import Foreign.Storable @@ -118,17 +119,17 @@ type CharBufElem = Char type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char -peekCharBuf arr ix = withForeignPtr arr $ \p -> do +peekCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> do (c,_) <- readCharBufPtr p ix return c {-# INLINE readCharBuf #-} readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) -readCharBuf arr ix = withForeignPtr arr $ \p -> readCharBufPtr p ix +readCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> readCharBufPtr p ix {-# INLINE writeCharBuf #-} writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int -writeCharBuf arr ix c = withForeignPtr arr $ \p -> writeCharBufPtr p ix c +writeCharBuf arr ix c = unsafeWithForeignPtr arr $ \p -> writeCharBufPtr p ix c {-# INLINE readCharBufPtr #-} readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit e043aacfc4202a59ccae8b8c8cf0e1ad83a3f209 +Subproject commit 8d5d8bd463f10244e3754dd03e4bf020a0ea03e3 ===================================== libraries/ghc-compact/GHC/Compact/Serialized.hs ===================================== @@ -29,6 +29,7 @@ module GHC.Compact.Serialized( import GHC.Prim import GHC.Types import GHC.Word (Word8) +import GHC.IO (unIO) import GHC.Ptr (Ptr(..), plusPtr) @@ -74,12 +75,6 @@ mkBlockList buffer = compactGetFirstBlock buffer >>= go rest <- go next return $ item : rest --- We MUST mark withSerializedCompact as NOINLINE --- Otherwise the compiler will eliminate the call to touch# --- causing the Compact# to be potentially GCed too eagerly, --- before func had a chance to copy everything into its own --- buffers/sockets/whatever - -- | Serialize the 'Compact', and call the provided function with -- with the 'Compact' serialized representation. It is not safe -- to return the pointer from the action and use it after @@ -89,7 +84,6 @@ mkBlockList buffer = compactGetFirstBlock buffer >>= go -- unsound to use 'unsafeInterleaveIO' to lazily construct -- a lazy bytestring from the 'Ptr'. -- -{-# NOINLINE withSerializedCompact #-} withSerializedCompact :: Compact a -> (SerializedCompact a -> IO c) -> IO c withSerializedCompact (Compact buffer root lock) func = withMVar lock $ \_ -> do @@ -97,9 +91,7 @@ withSerializedCompact (Compact buffer root lock) func = withMVar lock $ \_ -> do (# s', rootAddr #) -> (# s', Ptr rootAddr #) ) blockList <- mkBlockList buffer let serialized = SerializedCompact blockList rootPtr - r <- func serialized - IO (\s -> case touch# buffer s of - s' -> (# s', r #) ) + IO $ \s -> keepAlive# buffer s (unIO $ func serialized) fixupPointers :: Addr# -> Addr# -> State# RealWorld -> (# State# RealWorld, Maybe (Compact a) #) ===================================== testsuite/tests/ghci/should_fail/T15055.stderr ===================================== @@ -1,6 +1,9 @@ : error: Could not load module ‘GHC’ - It is a member of the hidden package ‘ghc-8.5’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) ===================================== testsuite/tests/package/package06e.stderr ===================================== @@ -1,14 +1,20 @@ package06e.hs:2:1: error: Could not load module ‘GHC.Hs.Type’ - It is a member of the hidden package ‘ghc-8.7’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package06e.hs:3:1: error: Could not load module ‘GHC.Types.Unique.FM’ - It is a member of the hidden package ‘ghc-8.7’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. ===================================== testsuite/tests/package/package07e.stderr ===================================== @@ -2,27 +2,37 @@ package07e.hs:2:1: error: Could not find module ‘GHC.Hs.MyTypes’ Perhaps you meant - GHC.Hs.Type (needs flag -package-id ghc-8.11.0.20200401) - GHC.Tc.Types (needs flag -package-id ghc-8.11.0.20200401) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201120) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201022) + GHC.Tc.Types (needs flag -package-id ghc-9.1.0.20201120) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:3:1: error: Could not load module ‘GHC.Hs.Type’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:4:1: error: Could not load module ‘GHC.Hs.Utils’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package07e.hs:5:1: error: Could not load module ‘GHC.Types.Unique.FM’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. ===================================== testsuite/tests/package/package08e.stderr ===================================== @@ -2,27 +2,37 @@ package08e.hs:2:1: error: Could not find module ‘GHC.Hs.MyTypes’ Perhaps you meant - GHC.Hs.Type (needs flag -package-id ghc-8.11.0.20200401) - GHC.Tc.Types (needs flag -package-id ghc-8.11.0.20200401) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201120) + GHC.Hs.Type (needs flag -package-id ghc-9.1.0.20201022) + GHC.Tc.Types (needs flag -package-id ghc-9.1.0.20201120) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:3:1: error: Could not load module ‘GHC.Hs.Type’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:4:1: error: Could not load module ‘GHC.Hs.Utils’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. package08e.hs:5:1: error: Could not load module ‘GHC.Types.Unique.FM’ - It is a member of the hidden package ‘ghc-8.11.0.20200401’. + It is a member of the hidden package ‘ghc-9.1.0.20201022’. + You can run ‘:set -package ghc’ to expose it. + (Note: this unloads all the modules in the current scope.) + It is a member of the hidden package ‘ghc-9.1.0.20201120’. You can run ‘:set -package ghc’ to expose it. (Note: this unloads all the modules in the current scope.) Use -v (or `:set -v` in ghci) to see a list of the files searched for. ===================================== utils/genprimopcode/Main.hs ===================================== @@ -503,6 +503,7 @@ gen_latex_doc (Info defaults entries) tvars = tvars_of typ tbinds [] = ". " tbinds ("o":tbs) = "(o::?) " ++ (tbinds tbs) + tbinds ("p":tbs) = "(p::?) " ++ (tbinds tbs) tbinds (tv:tbs) = tv ++ " " ++ (tbinds tbs) tvars_of (TyF t1 t2) = tvars_of t1 `union` tvars_of t2 tvars_of (TyC t1 t2) = tvars_of t1 `union` tvars_of t2 @@ -852,6 +853,7 @@ ppTyVar "b" = "betaTyVar" ppTyVar "c" = "gammaTyVar" ppTyVar "s" = "deltaTyVar" ppTyVar "o" = "runtimeRep1TyVar, openAlphaTyVar" +ppTyVar "p" = "runtimeRep2TyVar, openBetaTyVar" ppTyVar _ = error "Unknown type var" ppType :: Ty -> String @@ -885,6 +887,7 @@ ppType (TyVar "b") = "betaTy" ppType (TyVar "c") = "gammaTy" ppType (TyVar "s") = "deltaTy" ppType (TyVar "o") = "openAlphaTy" +ppType (TyVar "p") = "openBetaTy" ppType (TyApp (TyCon "State#") [x]) = "mkStatePrimTy " ++ ppType x ppType (TyApp (TyCon "MutVar#") [x,y]) = "mkMutVarPrimTy " ++ ppType x View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c80bd7791960c8cc28021aa89726996d524bbb9f...b7910e3fa09c1e9c0ce42bb600dd007bd1e79297 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c80bd7791960c8cc28021aa89726996d524bbb9f...b7910e3fa09c1e9c0ce42bb600dd007bd1e79297 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 Sun Nov 29 19:20:34 2020 From: gitlab at gitlab.haskell.org (Andrew Martin) Date: Sun, 29 Nov 2020 14:20:34 -0500 Subject: [Git][ghc/ghc][wip/boxed-rep] 4 commits: Add tests for levity polymorphism Message-ID: <5fc3f482d73d6_86c111d4a00833055@gitlab.mail> Andrew Martin pushed to branch wip/boxed-rep at Glasgow Haskell Compiler / GHC Commits: b5bd116b by Andrew Martin at 2020-11-18T09:28:28-05:00 Add tests for levity polymorphism - - - - - fd251750 by Andrew Martin at 2020-11-18T10:02:03-05:00 Add table documenting built-in types - - - - - c7d210f5 by Andrew Martin at 2020-11-18T10:17:58-05:00 Fix test T13963 - - - - - 0dace92a by Andrew Martin at 2020-11-18T10:19:53-05:00 Update the user manual - - - - - 14 changed files: - compiler/GHC/Builtin/Types.hs - docs/users_guide/9.2.1-notes.rst - docs/users_guide/exts/levity_polymorphism.rst - docs/users_guide/exts/typed_holes.rst - testsuite/tests/ghci/scripts/T13963.script - testsuite/tests/ghci/scripts/T13963.stdout - + testsuite/tests/typecheck/should_compile/LevPolyResult.hs - testsuite/tests/typecheck/should_compile/all.T - + testsuite/tests/typecheck/should_fail/LevPolyLet.hs - + testsuite/tests/typecheck/should_fail/LevPolyLet.stderr - testsuite/tests/typecheck/should_fail/all.T - + testsuite/tests/typecheck/should_run/LevPolyResultInst.hs - + testsuite/tests/typecheck/should_run/LevPolyResultInst.stdout - testsuite/tests/typecheck/should_run/all.T Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -215,6 +215,41 @@ to this Note, so a search for this Note's name should find all the lists. See also Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType. + +Note [Wired-in Types and Type Constructors] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +This module include a lot of wired-in types and type constructors. Here, +these are presented in a tabular format to make it easier to find the +wired-in type identifier corresponding to a known Haskell type. Data +constructors are nested under their corresponding types with two spaces +of indentation. + +Identifier Type Haskell name Notes +---------------------------------------------------------------------------- +liftedTypeKindTyCon TyCon GHC.Types.Type Synonym for: TYPE LiftedRep +liftedRepTyCon TyCon GHC.Types.LiftedRep Synonym for: 'BoxedRep 'Lifted +levityTyCon TyCon GHC.Types.Levity Data type + liftedDataConTyCon TyCon GHC.Types.Lifted Data constructor + unliftedDataConTyCon TyCon GHC.Types.Unlifted Data constructor +vecCountTyCon TyCon GHC.Types.VecCount Data type + vec2DataConTy Type GHC.Types.Vec2 Data constructor + vec4DataConTy Type GHC.Types.Vec4 Data constructor + vec8DataConTy Type GHC.Types.Vec8 Data constructor + vec16DataConTy Type GHC.Types.Vec16 Data constructor + vec32DataConTy Type GHC.Types.Vec32 Data constructor + vec64DataConTy Type GHC.Types.Vec64 Data constructor +runtimeRepTyCon TyCon GHC.Types.RuntimeRep Data type + boxedRepDataConTyCon TyCon GHC.Types.BoxedRep Data constructor + intRepDataConTy Type GHC.Types.IntRep Data constructor + doubleRepDataConTy Type GHC.Types.DoubleRep Data constructor + floatRepDataConTy Type GHC.Types.FloatRep Data constructor +boolTyCon TyCon GHC.Types.Bool Data type + trueDataCon DataCon GHC.Types.True Data constructor + falseDataCon DataCon GHC.Types.False Data constructor + promotedTrueDataCon TyCon GHC.Types.True Data constructor + promotedFalseDataCon TyCon GHC.Types.False Data constructor + ************************************************************************ * * \subsection{Wired in type constructors} @@ -223,8 +258,10 @@ See also Note [Getting from RuntimeRep to PrimRep] in GHC.Types.RepType. If you change which things are wired in, make sure you change their names in GHC.Builtin.Names, so they use wTcQual, wDataQual, etc + -} + -- This list is used only to define GHC.Builtin.Utils.wiredInThings. That in turn -- is used to initialise the name environment carried around by the renamer. -- This means that if we look up the name of a TyCon (or its implicit binders) ===================================== docs/users_guide/9.2.1-notes.rst ===================================== @@ -13,6 +13,12 @@ Language `__ (Serrano et al, ICFP 2020). More information here: :ref:`impredicative-polymorphism`. This replaces the old (undefined, flaky) behaviour of the :extension:`ImpredicativeTypes` extension. +* The first stage of the `Pointer Rep Proposal`_ has been implemented. All + boxed types, both lifted and unlifted, now have representation kinds of + the shape ``BoxedRep r``. Code that references ``LiftedRep`` and ``UnliftedRep`` + will need to be updated. + +.. _Pointer Rep Proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0203-pointer-rep.rst Compiler ~~~~~~~~ ===================================== docs/users_guide/exts/levity_polymorphism.rst ===================================== @@ -13,21 +13,25 @@ Here are the key definitions, all available from ``GHC.Exts``: :: TYPE :: RuntimeRep -> Type -- highly magical, built into GHC - data RuntimeRep = LiftedRep -- for things like `Int` - | UnliftedRep -- for things like `Array#` - | IntRep -- for `Int#` + data Levity = Lifted -- for things like `Int` + | Unlifted -- for things like `Array#` + + data RuntimeRep = BoxedRep Levity -- for anything represented by a GC-managed pointer + | IntRep -- for `Int#` | TupleRep [RuntimeRep] -- unboxed tuples, indexed by the representations of the elements | SumRep [RuntimeRep] -- unboxed sums, indexed by the representations of the disjuncts | ... + type LiftedRep = BoxedRep Lifted + type Type = TYPE LiftedRep -- Type is just an ordinary type synonym The idea is that we have a new fundamental type constant ``TYPE``, which is parameterised by a ``RuntimeRep``. We thus get ``Int# :: TYPE 'IntRep`` -and ``Bool :: TYPE 'LiftedRep``. Anything with a type of the form +and ``Bool :: TYPE LiftedRep``. Anything with a type of the form ``TYPE x`` can appear to either side of a function arrow ``->``. We can thus say that ``->`` has type -``TYPE r1 -> TYPE r2 -> TYPE 'LiftedRep``. The result is always lifted +``TYPE r1 -> TYPE r2 -> TYPE LiftedRep``. The result is always lifted because all functions are lifted in GHC. .. _levity-polymorphic-restrictions: @@ -102,13 +106,13 @@ Printing levity-polymorphic types :category: verbosity Print ``RuntimeRep`` parameters as they appear; otherwise, they are - defaulted to ``'LiftedRep``. + defaulted to ``LiftedRep``. Most GHC users will not need to worry about levity polymorphism or unboxed types. For these users, seeing the levity polymorphism in the type of ``$`` is unhelpful. And thus, by default, it is suppressed, -by supposing all type variables of type ``RuntimeRep`` to be ``'LiftedRep`` -when printing, and printing ``TYPE 'LiftedRep`` as ``Type`` (or ``*`` when +by supposing all type variables of type ``RuntimeRep`` to be ``LiftedRep`` +when printing, and printing ``TYPE LiftedRep`` as ``Type`` (or ``*`` when :extension:`StarIsType` is on). Should you wish to see levity polymorphism in your types, enable ===================================== docs/users_guide/exts/typed_holes.rst ===================================== @@ -443,7 +443,7 @@ it will additionally offer up a list of refinement hole fits, in this case: :: with const @Integer @[Integer] where const :: forall a b. a -> b -> a ($) (_ :: [Integer] -> Integer) - with ($) @'GHC.Types.LiftedRep @[Integer] @Integer + with ($) @GHC.Types.LiftedRep @[Integer] @Integer where ($) :: forall a b. (a -> b) -> a -> b fail (_ :: String) with fail @((->) [Integer]) @Integer ===================================== testsuite/tests/ghci/scripts/T13963.script ===================================== @@ -1,13 +1,13 @@ :set -XPolyKinds -XDataKinds -XRankNTypes -import GHC.Exts (TYPE, RuntimeRep(BoxedRep), Levity(Lifted)) +import GHC.Exts (TYPE, RuntimeRep, LiftedRep) type Pair (a :: TYPE rep) (b :: TYPE rep') rep'' = forall (r :: TYPE rep''). (a -> b -> r) :kind Pair :kind Pair Int :kind Pair Int Float -:kind Pair Int Float ('BoxedRep 'Lifted) +:kind Pair Int Float LiftedRep :set -fprint-explicit-runtime-reps :kind Pair :kind Pair Int :kind Pair Int Float -:kind Pair Int Float ('BoxedRep 'Lifted) +:kind Pair Int Float LiftedRep ===================================== testsuite/tests/ghci/scripts/T13963.stdout ===================================== @@ -1,8 +1,8 @@ Pair :: * -> * -> RuntimeRep -> * Pair Int :: * -> RuntimeRep -> * Pair Int Float :: RuntimeRep -> * -Pair Int Float ('BoxedRep 'Lifted) :: * +Pair Int Float LiftedRep :: * Pair :: TYPE rep -> TYPE rep' -> RuntimeRep -> * Pair Int :: * -> RuntimeRep -> * Pair Int Float :: RuntimeRep -> * -Pair Int Float ('BoxedRep 'Lifted) :: * +Pair Int Float LiftedRep :: * ===================================== testsuite/tests/typecheck/should_compile/LevPolyResult.hs ===================================== @@ -0,0 +1,11 @@ +{-# language DataKinds #-} +{-# language KindSignatures #-} +{-# language PolyKinds #-} +{-# language RankNTypes #-} + +module LevPolyResult (example) where + +import GHC.Exts + +example :: forall (v :: Levity) (a :: TYPE ('BoxedRep v)). (Int -> a) -> a +example f = f 42 ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -688,6 +688,7 @@ test('UnliftedNewtypesForall', normal, compile, ['']) test('UnlifNewUnify', normal, compile, ['']) test('UnliftedNewtypesLPFamily', normal, compile, ['']) test('UnliftedNewtypesDifficultUnification', normal, compile, ['']) +test('LevPolyResult', normal, compile, ['']) test('T16832', normal, ghci_script, ['T16832.script']) test('T16995', normal, compile, ['']) test('T17007', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/LevPolyLet.hs ===================================== @@ -0,0 +1,19 @@ +{-# language DataKinds #-} +{-# language KindSignatures #-} +{-# language PolyKinds #-} +{-# language RankNTypes #-} + +module LevPolyLet + ( example + ) where + +import GHC.Exts + +-- This should be rejected because of the let binding. +example :: forall (v :: Levity) (a :: TYPE ('BoxedRep v)). + (Int -> a) + -> (a -> Bool) + -> Bool +example f g = + let x = f 42 + in g x ===================================== testsuite/tests/typecheck/should_fail/LevPolyLet.stderr ===================================== @@ -0,0 +1,5 @@ +LevPolyLet.hs:18:7: + A levity-polymorphic type is not allowed here: + Type: a + Kind: TYPE ('BoxedRep v) + In the type of binder ‘x’ ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -440,6 +440,7 @@ test('T13068', [extra_files(['T13068.hs', 'T13068a.hs', 'T13068.hs-boot', 'T1306 test('T13075', normal, compile_fail, ['']) test('T13105', normal, compile_fail, ['']) test('LevPolyBounded', normal, compile_fail, ['']) +test('LevPolyLet', normal, compile_fail, ['']) test('T13487', normal, compile, ['']) test('T13292', normal, multimod_compile, ['T13292', '-v0 -fdefer-type-errors']) test('T13300', normal, compile_fail, ['']) ===================================== testsuite/tests/typecheck/should_run/LevPolyResultInst.hs ===================================== @@ -0,0 +1,27 @@ +{-# language BangPatterns #-} +{-# language DataKinds #-} +{-# language MagicHash #-} +{-# language PolyKinds #-} +{-# language RankNTypes #-} +{-# language UnboxedTuples #-} + +import GHC.Exts + +main :: IO () +main = do + print (example (\x -> I# x > 7)) + case indexArray# (example replicateFalse) 0# of + (# r #) -> print r + +-- Combines base:runST, primitive:newArray, and primitive:unsafeFreezeArray +replicateFalse :: Int# -> Array# Bool +replicateFalse n = + let !(# _, r #) = runRW# + (\s -> case newArray# n False s of + (# s', arr #) -> unsafeFreezeArray# arr s' + ) + in r + +example :: forall (v :: Levity) (a :: TYPE ('BoxedRep v)). (Int# -> a) -> a +{-# noinline example #-} +example f = f 8# ===================================== testsuite/tests/typecheck/should_run/LevPolyResultInst.stdout ===================================== @@ -0,0 +1,2 @@ +True +False ===================================== testsuite/tests/typecheck/should_run/all.T ===================================== @@ -145,5 +145,6 @@ test('UnliftedNewtypesFamilyRun', normal, compile_and_run, ['']) test('UnliftedNewtypesDependentFamilyRun', normal, compile_and_run, ['']) test('UnliftedNewtypesIdentityRun', normal, compile_and_run, ['']) test('UnliftedNewtypesCoerceRun', normal, compile_and_run, ['']) +test('LevPolyResultInst', normal, compile_and_run, ['']) test('T17104', normal, compile_and_run, ['']) test('T18627', normal, compile_and_run, ['-O']) # Optimisation shows up the bug View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/39caf4f1edde204edd323596ba2b2b2890dce093...0dace92a5867ced6f979b4543c49865165d4c49a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/39caf4f1edde204edd323596ba2b2b2890dce093...0dace92a5867ced6f979b4543c49865165d4c49a 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 Sun Nov 29 20:33:26 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 29 Nov 2020 15:33:26 -0500 Subject: [Git][ghc/ghc][master] withTimings: Emit allocations counter Message-ID: <5fc40596e1b3e_86cf574568841485@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1bc104b0 by Ben Gamari at 2020-11-29T15:33:18-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - 1 changed file: - compiler/GHC/Utils/Error.hs Changes: ===================================== compiler/GHC/Utils/Error.hs ===================================== @@ -536,14 +536,16 @@ withTiming' dflags what force_result prtimings action logInfo dflags $ withPprStyle defaultUserStyle $ text "***" <+> what <> colon let ctx = initDefaultSDocContext dflags - eventBegins ctx what alloc0 <- liftIO getAllocationCounter start <- liftIO getCPUTime + eventBegins ctx what + recordAllocs alloc0 !r <- action () <- pure $ force_result r eventEnds ctx what end <- liftIO getCPUTime alloc1 <- liftIO getAllocationCounter + recordAllocs alloc1 -- recall that allocation counter counts down let alloc = alloc0 - alloc1 time = realToFrac (end - start) * 1e-9 @@ -569,12 +571,19 @@ withTiming' dflags what force_result prtimings action else action where whenPrintTimings = liftIO . when (prtimings == PrintTimings) + + recordAllocs alloc = do + liftIO $ traceMarkerIO $ "GHC:allocs:" ++ show alloc + eventBegins ctx w = do - whenPrintTimings $ traceMarkerIO (eventBeginsDoc ctx w) - liftIO $ traceEventIO (eventBeginsDoc ctx w) + let doc = eventBeginsDoc ctx w + whenPrintTimings $ traceMarkerIO doc + liftIO $ traceEventIO doc + eventEnds ctx w = do - whenPrintTimings $ traceMarkerIO (eventEndsDoc ctx w) - liftIO $ traceEventIO (eventEndsDoc ctx w) + let doc = eventEndsDoc ctx w + whenPrintTimings $ traceMarkerIO doc + liftIO $ traceEventIO doc eventBeginsDoc ctx w = showSDocOneLine ctx $ text "GHC:started:" <+> w eventEndsDoc ctx w = showSDocOneLine ctx $ text "GHC:finished:" <+> w View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bc104b029b4f043cac42253ee2387f4d574abca -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1bc104b029b4f043cac42253ee2387f4d574abca 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 Sun Nov 29 20:34:02 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 29 Nov 2020 15:34:02 -0500 Subject: [Git][ghc/ghc][master] 9 commits: ThreadPaused: Don't zero slop until free vars are pushed Message-ID: <5fc405bab5d5f_86cfd752bc8473e0@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e992ea84 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - e82cd140 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 35a5207e by GHC GitLab CI at 2020-11-29T15:33:54-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 0120829f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 8a4d8fb6 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 2793cfdc by GHC GitLab CI at 2020-11-29T15:33:54-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - e391a16f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 60d088ab by Ben Gamari at 2020-11-29T15:33:54-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 3aa60362 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 11 changed files: - includes/rts/storage/ClosureMacros.h - rts/Messages.c - rts/Messages.h - rts/PrimOps.cmm - rts/RaiseAsync.c - rts/ThreadPaused.c - rts/Updates.h - rts/posix/OSThreads.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/NonMoving.c Changes: ===================================== includes/rts/storage/ClosureMacros.h ===================================== @@ -520,11 +520,15 @@ INLINE_HEADER StgWord8 *mutArrPtrsCard (StgMutArrPtrs *a, W_ n) #if defined(PROFILING) || defined(DEBUG) #define OVERWRITING_CLOSURE(c) \ overwritingClosure(c) +#define OVERWRITING_CLOSURE_SIZE(c, size) \ + overwritingClosureSize(c, size) #define OVERWRITING_CLOSURE_MUTABLE(c, off) \ overwritingMutableClosureOfs(c, off) #else #define OVERWRITING_CLOSURE(c) \ do { (void) sizeof(c); } while(0) +#define OVERWRITING_CLOSURE_SIZE(c, size) \ + do { (void) sizeof(c); (void) sizeof(size); } while(0) #define OVERWRITING_CLOSURE_MUTABLE(c, off) \ do { (void) sizeof(c); (void) sizeof(off); } while(0) #endif ===================================== rts/Messages.c ===================================== @@ -97,7 +97,7 @@ loop: case THROWTO_SUCCESS: { // this message is done StgTSO *source = t->source; - doneWithMsgThrowTo(t); + doneWithMsgThrowTo(cap, t); tryWakeupThread(cap, source); break; } ===================================== rts/Messages.h ===================================== @@ -23,8 +23,16 @@ void sendMessage (Capability *from_cap, Capability *to_cap, Message *msg); #include "SMPClosureOps.h" INLINE_HEADER void -doneWithMsgThrowTo (MessageThrowTo *m) +doneWithMsgThrowTo (Capability *cap, MessageThrowTo *m) { + // The message better be locked + ASSERT(m->header.info == &stg_WHITEHOLE_info); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + updateRemembSetPushClosure(cap, (StgClosure *) m->link); + updateRemembSetPushClosure(cap, (StgClosure *) m->source); + updateRemembSetPushClosure(cap, (StgClosure *) m->target); + updateRemembSetPushClosure(cap, (StgClosure *) m->exception); + } OVERWRITING_CLOSURE((StgClosure*)m); unlockClosure((StgClosure*)m, &stg_MSG_NULL_info); LDV_RECORD_CREATE(m); ===================================== rts/PrimOps.cmm ===================================== @@ -227,6 +227,21 @@ stg_shrinkSmallMutableArrayzh ( gcptr mba, W_ new_size ) { ASSERT(new_size <= StgSmallMutArrPtrs_ptrs(mba)); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + // Ensure that the elements we are about to shrink out of existence + // remain visible to the non-moving collector. + W_ p, end; + p = mba + SIZEOF_StgSmallMutArrPtrs + WDS(new_size); + end = mba + SIZEOF_StgSmallMutArrPtrs + WDS(StgSmallMutArrPtrs_ptrs(mba)); +again: + ccall updateRemembSetPushClosure_(BaseReg "ptr", + W_[p] "ptr"); + if (p < end) { + p = p + SIZEOF_W; + goto again; + } + } + OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) + new_size)); StgSmallMutArrPtrs_ptrs(mba) = new_size; ===================================== rts/RaiseAsync.c ===================================== @@ -336,7 +336,7 @@ check_target: } // nobody else can wake up this TSO after we claim the message - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); raiseAsync(cap, target, msg->exception, false, NULL); return THROWTO_SUCCESS; @@ -580,7 +580,7 @@ maybePerformBlockedException (Capability *cap, StgTSO *tso) throwToSingleThreaded(cap, msg->target, msg->exception); source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); return 1; } @@ -602,7 +602,7 @@ awakenBlockedExceptionQueue (Capability *cap, StgTSO *tso) i = lockClosure((StgClosure *)msg); if (i != &stg_MSG_NULL_info) { source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); } else { unlockClosure((StgClosure *)msg,i); @@ -700,7 +700,7 @@ removeFromQueues(Capability *cap, StgTSO *tso) // ASSERT(m->header.info == &stg_WHITEHOLE_info); // unlock and revoke it at the same time - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); break; } ===================================== rts/ThreadPaused.c ===================================== @@ -314,10 +314,6 @@ threadPaused(Capability *cap, StgTSO *tso) continue; } - // zero out the slop so that the sanity checker can tell - // where the next closure is. - OVERWRITING_CLOSURE(bh); - // an EAGER_BLACKHOLE or CAF_BLACKHOLE gets turned into a // BLACKHOLE here. #if defined(THREADED_RTS) @@ -345,11 +341,16 @@ threadPaused(Capability *cap, StgTSO *tso) // overwrite to the update remembered set. // N.B. We caught the WHITEHOLE case above. updateRemembSetPushThunkEager(cap, - THUNK_INFO_PTR_TO_STRUCT(bh_info), - (StgThunk *) bh); + THUNK_INFO_PTR_TO_STRUCT(bh_info), + (StgThunk *) bh); } } + // zero out the slop so that the sanity checker can tell + // where the next closure is. N.B. We mustn't do this until we have + // pushed the free variables to the update remembered set above. + OVERWRITING_CLOSURE_SIZE(bh, closure_sizeW_(bh, INFO_PTR_TO_STRUCT(bh_info))); + // The payload of the BLACKHOLE points to the TSO RELAXED_STORE(&((StgInd *)bh)->indirectee, (StgClosure *)tso); SET_INFO_RELEASE(bh,&stg_BLACKHOLE_info); ===================================== rts/Updates.h ===================================== @@ -49,7 +49,6 @@ W_ bd; \ \ prim_write_barrier; \ - OVERWRITING_CLOSURE(p1); \ bd = Bdescr(p1); \ if (bdescr_gen_no(bd) != 0 :: bits16) { \ IF_NONMOVING_WRITE_BARRIER_ENABLED { \ @@ -60,6 +59,7 @@ } else { \ TICK_UPD_NEW_IND(); \ } \ + OVERWRITING_CLOSURE(p1); \ StgInd_indirectee(p1) = p2; \ prim_write_barrier; \ SET_INFO(p1, stg_BLACKHOLE_info); \ ===================================== rts/posix/OSThreads.c ===================================== @@ -401,8 +401,9 @@ interruptOSThread (OSThreadId id) void joinOSThread (OSThreadId id) { - if (pthread_join(id, NULL) != 0) { - sysErrorBelch("joinOSThread: error %d", errno); + int ret = pthread_join(id, NULL); + if (ret != 0) { + sysErrorBelch("joinOSThread: error %d", ret); } } ===================================== rts/sm/Evac.c ===================================== @@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) // // However, if we are in a deadlock detection GC then we disable aging // so there is no need. + // + // See Note [Non-moving GC: Marking evacuated objects]. if (major_gc && !deadlock_detect_gc) markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to); return to; @@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ +/* + * Note [Non-moving GC: Marking evacuated objects] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * When the non-moving collector is in use we must be careful to ensure that any + * references to objects in the non-moving generation from younger generations + * are pushed to the mark queue. + * + * In particular we need to ensure that we handle newly-promoted objects are + * correctly marked. For instance, consider this case: + * + * generation 0 generation 1 + * ────────────── ────────────── + * + * ┌───────┐ + * ┌───────┐ │ A │ + * │ B │ ◁────────────────────────── │ │ + * │ │ ──┬─────────────────┐ └───────┘ + * └───────┘ ┆ after GC │ + * ┆ │ + * ┌───────┐ ┆ before GC │ ┌───────┐ + * │ C │ ◁┄┘ └─────▷ │ C' │ + * │ │ │ │ + * └───────┘ └───────┘ + * + * + * In this case object C started off in generation 0 and was evacuated into + * generation 1 during the preparatory GC. However, the only reference to C' + * is from B, which lives in the generation 0 (via aging); this reference will + * not be visible to the concurrent non-moving collector (which can only + * traverse the generation 1 heap). Consequently, upon evacuating C we need to + * ensure that C' is added to the update remembered set as we know that it will + * continue to be reachable via B (which is assumed to be reachable as it lives + * in a younger generation). + * + * Where this happens depends upon the type of the object (e.g. C'): + * + * - In the case of "normal" small heap-allocated objects this happens in + * alloc_for_copy. + * - In the case of compact region this happens in evacuate_compact. + * - In the case of large objects this happens in evacuate_large. + * + * See also Note [Aging under the non-moving collector] in NonMoving.c. + * + */ + /* size is in words We want to *always* inline this as often the size of the closure is static, @@ -356,6 +404,9 @@ evacuate_large(StgPtr p) __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL); if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) p); } initBdescr(bd, new_gen, new_gen->to); @@ -510,6 +561,9 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -695,13 +749,6 @@ loop: */ if (flags & BF_LARGE) { evacuate_large((P_)q); - - // We may have evacuated the block to the nonmoving generation. If so - // we need to make sure it is added to the mark queue since the only - // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { - markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); - } return; } ===================================== rts/sm/GC.c ===================================== @@ -1701,13 +1701,8 @@ collect_gct_blocks (void) static void collect_pinned_object_blocks (void) { - generation *gen; const bool use_nonmoving = RtsFlags.GcFlags.useNonmoving; - if (use_nonmoving && major_gc) { - gen = oldest_gen; - } else { - gen = g0; - } + generation *const gen = (use_nonmoving && major_gc) ? oldest_gen : g0; for (uint32_t n = 0; n < n_capabilities; n++) { bdescr *last = NULL; @@ -1732,7 +1727,7 @@ collect_pinned_object_blocks (void) if (gen->large_objects != NULL) { gen->large_objects->u.back = last; } - g0->large_objects = RELAXED_LOAD(&capabilities[n]->pinned_object_blocks); + gen->large_objects = RELAXED_LOAD(&capabilities[n]->pinned_object_blocks); RELAXED_STORE(&capabilities[n]->pinned_object_blocks, NULL); } } ===================================== rts/sm/NonMoving.c ===================================== @@ -191,8 +191,8 @@ Mutex concurrent_coll_finished_lock; * === Other references === * * Apart from the design document in docs/storage/nonmoving-gc and the Ueno - * 2016 paper (TODO citation) from which it drew inspiration, there are a - * variety of other relevant Notes scattered throughout the tree: + * 2016 paper [ueno 2016] from which it drew inspiration, there are a variety + * of other relevant Notes scattered throughout the tree: * * - Note [Concurrent non-moving collection] (NonMoving.c) describes * concurrency control of the nonmoving collector @@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock; * - Note [Aging under the non-moving collector] (NonMoving.c) describes how * we accommodate aging * + * - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how + * non-moving objects reached by evacuate() are marked, which is necessary + * due to aging. + * * - Note [Large objects in the non-moving collector] (NonMovingMark.c) * describes how we track large objects. * @@ -232,6 +236,11 @@ Mutex concurrent_coll_finished_lock; * how we use the DIRTY flags associated with MUT_VARs and TVARs to improve * barrier efficiency. * + * [ueno 2016]: + * Katsuhiro Ueno and Atsushi Ohori. 2016. A fully concurrent garbage + * collector for functional programs on multicore processors. SIGPLAN Not. 51, + * 9 (September 2016), 421–433. DOI:https://doi.org/10.1145/3022670.2951944 + * * * Note [Concurrent non-moving collection] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -312,6 +321,8 @@ Mutex concurrent_coll_finished_lock; * * The non-moving collector will come to C in the mark queue and mark it. * + * The implementation details of this are described in Note [Non-moving GC: + * Marking evacuated objects] in Evac.c. * * Note [Deadlock detection under the non-moving collector] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -726,7 +737,6 @@ void nonmovingStop(void) "waiting for nonmoving collector thread to terminate"); ACQUIRE_LOCK(&concurrent_coll_finished_lock); waitCondition(&concurrent_coll_finished, &concurrent_coll_finished_lock); - joinOSThread(mark_thread); } #endif } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1bc104b029b4f043cac42253ee2387f4d574abca...3aa603620ef5a6aae1778278aa9914f344ab526e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1bc104b029b4f043cac42253ee2387f4d574abca...3aa603620ef5a6aae1778278aa9914f344ab526e 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 Sun Nov 29 21:05:00 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Sun, 29 Nov 2020 16:05:00 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: withTimings: Emit allocations counter Message-ID: <5fc40cfcaf5a4_86c111d4a008590ae@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 1bc104b0 by Ben Gamari at 2020-11-29T15:33:18-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - e992ea84 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - e82cd140 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 35a5207e by GHC GitLab CI at 2020-11-29T15:33:54-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 0120829f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 8a4d8fb6 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 2793cfdc by GHC GitLab CI at 2020-11-29T15:33:54-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - e391a16f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 60d088ab by Ben Gamari at 2020-11-29T15:33:54-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 3aa60362 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - a1efdf34 by Ben Gamari at 2020-11-29T16:04:48-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 6c2d941c by Ben Gamari at 2020-11-29T16:04:49-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 706c924b by Ryan Scott at 2020-11-29T16:04:49-05:00 Allow deploy:pages job to fail See #18973. - - - - - 20 changed files: - .gitlab-ci.yml - compiler/GHC/Utils/Error.hs - includes/rts/storage/ClosureMacros.h - rts/Linker.c - rts/Messages.c - rts/Messages.h - rts/PrimOps.cmm - rts/RaiseAsync.c - rts/ThreadPaused.c - rts/Updates.h - rts/linker/Elf.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/linker/elf_reloc_aarch64.c - rts/posix/OSThreads.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/NonMoving.c - rts/win32/veh_excn.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1237,6 +1237,8 @@ pages: dependencies: - doc-tarball image: ghcci/x86_64-linux-deb9:0.2 + # See #18973 + allow_failure: true tags: - x86_64-linux script: ===================================== compiler/GHC/Utils/Error.hs ===================================== @@ -536,14 +536,16 @@ withTiming' dflags what force_result prtimings action logInfo dflags $ withPprStyle defaultUserStyle $ text "***" <+> what <> colon let ctx = initDefaultSDocContext dflags - eventBegins ctx what alloc0 <- liftIO getAllocationCounter start <- liftIO getCPUTime + eventBegins ctx what + recordAllocs alloc0 !r <- action () <- pure $ force_result r eventEnds ctx what end <- liftIO getCPUTime alloc1 <- liftIO getAllocationCounter + recordAllocs alloc1 -- recall that allocation counter counts down let alloc = alloc0 - alloc1 time = realToFrac (end - start) * 1e-9 @@ -569,12 +571,19 @@ withTiming' dflags what force_result prtimings action else action where whenPrintTimings = liftIO . when (prtimings == PrintTimings) + + recordAllocs alloc = do + liftIO $ traceMarkerIO $ "GHC:allocs:" ++ show alloc + eventBegins ctx w = do - whenPrintTimings $ traceMarkerIO (eventBeginsDoc ctx w) - liftIO $ traceEventIO (eventBeginsDoc ctx w) + let doc = eventBeginsDoc ctx w + whenPrintTimings $ traceMarkerIO doc + liftIO $ traceEventIO doc + eventEnds ctx w = do - whenPrintTimings $ traceMarkerIO (eventEndsDoc ctx w) - liftIO $ traceEventIO (eventEndsDoc ctx w) + let doc = eventEndsDoc ctx w + whenPrintTimings $ traceMarkerIO doc + liftIO $ traceEventIO doc eventBeginsDoc ctx w = showSDocOneLine ctx $ text "GHC:started:" <+> w eventEndsDoc ctx w = showSDocOneLine ctx $ text "GHC:finished:" <+> w ===================================== includes/rts/storage/ClosureMacros.h ===================================== @@ -520,11 +520,15 @@ INLINE_HEADER StgWord8 *mutArrPtrsCard (StgMutArrPtrs *a, W_ n) #if defined(PROFILING) || defined(DEBUG) #define OVERWRITING_CLOSURE(c) \ overwritingClosure(c) +#define OVERWRITING_CLOSURE_SIZE(c, size) \ + overwritingClosureSize(c, size) #define OVERWRITING_CLOSURE_MUTABLE(c, off) \ overwritingMutableClosureOfs(c, off) #else #define OVERWRITING_CLOSURE(c) \ do { (void) sizeof(c); } while(0) +#define OVERWRITING_CLOSURE_SIZE(c, size) \ + do { (void) sizeof(c); (void) sizeof(size); } while(0) #define OVERWRITING_CLOSURE_MUTABLE(c, off) \ do { (void) sizeof(c); (void) sizeof(off); } while(0) #endif ===================================== rts/Linker.c ===================================== @@ -49,7 +49,6 @@ #include #include #include -#include #include #if defined(HAVE_SYS_STAT_H) @@ -885,12 +884,11 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) */ IF_DEBUG(linker, debugBelch("lookupSymbol: looking up %s with dlsym\n", lbl)); - ASSERT(lbl[0] == '_'); + CHECK(lbl[0] == '_'); return internal_dlsym(lbl + 1); # else - ASSERT(false); - return NULL; +# error No OBJFORMAT_* macro set # endif } else { if (dependent) { @@ -2112,7 +2110,7 @@ HsInt unloadNativeObj (void *handle) n_unloaded_objects += 1; // dynamic objects have no symbols - ASSERT(nc->symbols == NULL); + CHECK(nc->symbols == NULL); freeOcStablePtrs(nc); // Remove object code from root set ===================================== rts/Messages.c ===================================== @@ -97,7 +97,7 @@ loop: case THROWTO_SUCCESS: { // this message is done StgTSO *source = t->source; - doneWithMsgThrowTo(t); + doneWithMsgThrowTo(cap, t); tryWakeupThread(cap, source); break; } ===================================== rts/Messages.h ===================================== @@ -23,8 +23,16 @@ void sendMessage (Capability *from_cap, Capability *to_cap, Message *msg); #include "SMPClosureOps.h" INLINE_HEADER void -doneWithMsgThrowTo (MessageThrowTo *m) +doneWithMsgThrowTo (Capability *cap, MessageThrowTo *m) { + // The message better be locked + ASSERT(m->header.info == &stg_WHITEHOLE_info); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + updateRemembSetPushClosure(cap, (StgClosure *) m->link); + updateRemembSetPushClosure(cap, (StgClosure *) m->source); + updateRemembSetPushClosure(cap, (StgClosure *) m->target); + updateRemembSetPushClosure(cap, (StgClosure *) m->exception); + } OVERWRITING_CLOSURE((StgClosure*)m); unlockClosure((StgClosure*)m, &stg_MSG_NULL_info); LDV_RECORD_CREATE(m); ===================================== rts/PrimOps.cmm ===================================== @@ -227,6 +227,21 @@ stg_shrinkSmallMutableArrayzh ( gcptr mba, W_ new_size ) { ASSERT(new_size <= StgSmallMutArrPtrs_ptrs(mba)); + IF_NONMOVING_WRITE_BARRIER_ENABLED { + // Ensure that the elements we are about to shrink out of existence + // remain visible to the non-moving collector. + W_ p, end; + p = mba + SIZEOF_StgSmallMutArrPtrs + WDS(new_size); + end = mba + SIZEOF_StgSmallMutArrPtrs + WDS(StgSmallMutArrPtrs_ptrs(mba)); +again: + ccall updateRemembSetPushClosure_(BaseReg "ptr", + W_[p] "ptr"); + if (p < end) { + p = p + SIZEOF_W; + goto again; + } + } + OVERWRITING_CLOSURE_MUTABLE(mba, (BYTES_TO_WDS(SIZEOF_StgSmallMutArrPtrs) + new_size)); StgSmallMutArrPtrs_ptrs(mba) = new_size; ===================================== rts/RaiseAsync.c ===================================== @@ -336,7 +336,7 @@ check_target: } // nobody else can wake up this TSO after we claim the message - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); raiseAsync(cap, target, msg->exception, false, NULL); return THROWTO_SUCCESS; @@ -580,7 +580,7 @@ maybePerformBlockedException (Capability *cap, StgTSO *tso) throwToSingleThreaded(cap, msg->target, msg->exception); source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); return 1; } @@ -602,7 +602,7 @@ awakenBlockedExceptionQueue (Capability *cap, StgTSO *tso) i = lockClosure((StgClosure *)msg); if (i != &stg_MSG_NULL_info) { source = msg->source; - doneWithMsgThrowTo(msg); + doneWithMsgThrowTo(cap, msg); tryWakeupThread(cap, source); } else { unlockClosure((StgClosure *)msg,i); @@ -700,7 +700,7 @@ removeFromQueues(Capability *cap, StgTSO *tso) // ASSERT(m->header.info == &stg_WHITEHOLE_info); // unlock and revoke it at the same time - doneWithMsgThrowTo(m); + doneWithMsgThrowTo(cap, m); break; } ===================================== rts/ThreadPaused.c ===================================== @@ -314,10 +314,6 @@ threadPaused(Capability *cap, StgTSO *tso) continue; } - // zero out the slop so that the sanity checker can tell - // where the next closure is. - OVERWRITING_CLOSURE(bh); - // an EAGER_BLACKHOLE or CAF_BLACKHOLE gets turned into a // BLACKHOLE here. #if defined(THREADED_RTS) @@ -345,11 +341,16 @@ threadPaused(Capability *cap, StgTSO *tso) // overwrite to the update remembered set. // N.B. We caught the WHITEHOLE case above. updateRemembSetPushThunkEager(cap, - THUNK_INFO_PTR_TO_STRUCT(bh_info), - (StgThunk *) bh); + THUNK_INFO_PTR_TO_STRUCT(bh_info), + (StgThunk *) bh); } } + // zero out the slop so that the sanity checker can tell + // where the next closure is. N.B. We mustn't do this until we have + // pushed the free variables to the update remembered set above. + OVERWRITING_CLOSURE_SIZE(bh, closure_sizeW_(bh, INFO_PTR_TO_STRUCT(bh_info))); + // The payload of the BLACKHOLE points to the TSO RELAXED_STORE(&((StgInd *)bh)->indirectee, (StgClosure *)tso); SET_INFO_RELEASE(bh,&stg_BLACKHOLE_info); ===================================== rts/Updates.h ===================================== @@ -49,7 +49,6 @@ W_ bd; \ \ prim_write_barrier; \ - OVERWRITING_CLOSURE(p1); \ bd = Bdescr(p1); \ if (bdescr_gen_no(bd) != 0 :: bits16) { \ IF_NONMOVING_WRITE_BARRIER_ENABLED { \ @@ -60,6 +59,7 @@ } else { \ TICK_UPD_NEW_IND(); \ } \ + OVERWRITING_CLOSURE(p1); \ StgInd_indirectee(p1) = p2; \ prim_write_barrier; \ SET_INFO(p1, stg_BLACKHOLE_info); \ ===================================== rts/linker/Elf.c ===================================== @@ -416,7 +416,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) "\nSection header table: start %ld, n_entries %d, ent_size %d\n", (long)ehdr->e_shoff, shnum, ehdr->e_shentsize )); - ASSERT(ehdr->e_shentsize == sizeof(Elf_Shdr)); + CHECK(ehdr->e_shentsize == sizeof(Elf_Shdr)); shdr = (Elf_Shdr*) (ehdrC + ehdr->e_shoff); @@ -537,7 +537,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) #if defined(SHN_XINDEX) /* See Note [Many ELF Sections] */ if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -864,7 +864,7 @@ ocGetNames_ELF ( ObjectCode* oc ) PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); - ASSERT(common_mem != NULL); + CHECK(common_mem != NULL); } //TODO: we ignore local symbols anyway right? So we can use the @@ -893,7 +893,7 @@ ocGetNames_ELF ( ObjectCode* oc ) secno = shndx; #if defined(SHN_XINDEX) if (shndx == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -902,11 +902,11 @@ ocGetNames_ELF ( ObjectCode* oc ) if (shndx == SHN_COMMON) { isLocal = false; - ASSERT(common_used < common_size); - ASSERT(common_mem); + CHECK(common_used < common_size); + CHECK(common_mem); symbol->addr = (void*)((uintptr_t)common_mem + common_used); common_used += symbol->elf_sym->st_size; - ASSERT(common_used <= common_size); + CHECK(common_used <= common_size); IF_DEBUG(linker, debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", @@ -935,7 +935,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ) ) { /* Section 0 is the undefined section, hence > and not >=. */ - ASSERT(secno > 0 && secno < shnum); + CHECK(secno > 0 && secno < shnum); /* if (shdr[secno].sh_type == SHT_NOBITS) { debugBelch(" BSS symbol, size %d off %d name %s\n", @@ -945,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - ASSERT(symbol->addr != 0x0); + CHECK(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -962,7 +962,7 @@ ocGetNames_ELF ( ObjectCode* oc ) /* And the decision is ... */ if (symbol->addr != NULL) { - ASSERT(nm != NULL); + CHECK(nm != NULL); /* Acquire! */ if (!isLocal) { @@ -1045,7 +1045,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, break; } } - ASSERT(stab != NULL); + CHECK(stab != NULL); targ = (Elf_Word*)oc->sections[target_shndx].start; IF_DEBUG(linker,debugBelch( @@ -1251,7 +1251,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, result = ((S + A) | T) - P; result &= ~1; // Clear thumb indicator bit - ASSERT(isInt(26, result)); /* X in range */ + CHECK(isInt(26, result)); /* X in range */ } // Update the branch target @@ -1426,7 +1426,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, case COMPAT_R_ARM_GOT_PREL: { int32_t A = *pP; void* GOT_S = symbol->got_addr; - ASSERT(GOT_S); + CHECK(GOT_S); *(uint32_t *)P = (uint32_t) GOT_S + A - P; break; } @@ -1552,21 +1552,21 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, case R_SPARC_WDISP30: w1 = *pP & 0xC0000000; w2 = (Elf_Word)((value - P) >> 2); - ASSERT((w2 & 0xC0000000) == 0); + CHECK((w2 & 0xC0000000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_HI22: w1 = *pP & 0xFFC00000; w2 = (Elf_Word)(value >> 10); - ASSERT((w2 & 0xFFC00000) == 0); + CHECK((w2 & 0xFFC00000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_LO10: w1 = *pP & ~0x3FF; w2 = (Elf_Word)(value & 0x3FF); - ASSERT((w2 & ~0x3FF) == 0); + CHECK((w2 & ~0x3FF) == 0); w1 |= w2; *pP = w1; break; @@ -1866,13 +1866,13 @@ ocResolve_ELF ( ObjectCode* oc ) Elf_Word secno = symbol->elf_sym->st_shndx; #if defined(SHN_XINDEX) if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[i]; } #endif - ASSERT(symbol->elf_sym->st_name == 0); - ASSERT(symbol->elf_sym->st_value == 0); - ASSERT(0x0 != oc->sections[ secno ].start); + CHECK(symbol->elf_sym->st_name == 0); + CHECK(symbol->elf_sym->st_value == 0); + CHECK(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1946,7 +1946,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { - ASSERT(0x0 != *init); + CHECK(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/MachO.c ===================================== @@ -252,7 +252,6 @@ resolveImports( "%s: unknown symbol `%s'", oc->fileName, symbol->name); return 0; } - ASSERT(addr); checkProddableBlock(oc, ((void**)(oc->image + sect->offset)) + i, @@ -847,7 +846,7 @@ relocateSection(ObjectCode* oc, int curSection) IF_DEBUG(linker, debugBelch(" : value = %p\n", (void *)symbol->nlist->n_value)); if ((symbol->nlist->n_type & N_TYPE) == N_SECT) { - ASSERT(symbol->addr != NULL); + CHECK(symbol->addr != NULL); value = (uint64_t) symbol->addr; IF_DEBUG(linker, debugBelch("relocateSection, defined external symbol %s, relocated address %p\n", nm, (void *)value)); @@ -949,29 +948,29 @@ relocateSection(ObjectCode* oc, int curSection) { if((int32_t)(value - baseValue) != (int64_t)(value - baseValue)) { - ASSERT(reloc->r_extern); + CHECK(reloc->r_extern); value = (uint64_t) &makeSymbolExtra(oc, reloc->r_symbolnum, value) -> jumpIsland; } - ASSERT((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); + CHECK((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); type = X86_64_RELOC_SIGNED; } switch(type) { case X86_64_RELOC_UNSIGNED: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing += value; break; case X86_64_RELOC_SIGNED: case X86_64_RELOC_SIGNED_1: case X86_64_RELOC_SIGNED_2: case X86_64_RELOC_SIGNED_4: - ASSERT(reloc->r_pcrel); + CHECK(reloc->r_pcrel); thing += value - baseValue; break; case X86_64_RELOC_SUBTRACTOR: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing -= value; break; default: ===================================== rts/linker/PEi386.c ===================================== @@ -1594,7 +1594,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) barf ("Could not allocate any heap memory from private heap."); } - ASSERT(section.size == 0 || section.info->virtualSize == 0); + CHECK(section.size == 0 || section.info->virtualSize == 0); sz = section.size; if (sz < section.info->virtualSize) sz = section.info->virtualSize; @@ -2032,7 +2032,7 @@ ocRunInit_PEi386 ( ObjectCode *oc ) getProgEnvv(&envc, &envv); Section section = *oc->info->init; - ASSERT(SECTIONKIND_INIT_ARRAY == section.kind); + CHECK(SECTIONKIND_INIT_ARRAY == section.kind); uint8_t *init_startC = section.start; init_t *init_start = (init_t*)init_startC; ===================================== rts/linker/elf_got.c ===================================== @@ -136,10 +136,10 @@ verifyGot(ObjectCode * oc) { for(size_t i=0; i < symTab->n_symbols; i++) { ElfSymbol * symbol = &symTab->symbols[i]; if(symbol->got_addr) { - ASSERT((void*)(*(void**)symbol->got_addr) - == (void*)symbol->addr); + CHECK((void*)(*(void**)symbol->got_addr) + == (void*)symbol->addr); } - ASSERT(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); + CHECK(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); } } return EXIT_SUCCESS; ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -6,7 +6,6 @@ #include "elf_plt.h" #include -#include #if defined(aarch64_HOST_ARCH) @@ -71,15 +70,15 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { *(uint64_t*)P = (uint64_t)addend; break; case COMPAT_R_AARCH64_ABS32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); case COMPAT_R_AARCH64_PREL32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); *(uint32_t*)P = (uint32_t)addend; break; case COMPAT_R_AARCH64_ABS16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); case COMPAT_R_AARCH64_PREL16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); *(uint16_t*)P = (uint16_t)addend; break; /* static aarch64 relocations */ @@ -95,8 +94,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { // imm64 = SignExtend(hi:lo:0x000,64) // Range is 21 bits + the 12 page relative bits // known to be 0. -2^32 <= X < 2^32 - assert(isInt64(21+12, addend)); - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t) (((uint64_t) addend << 17) & 0x60000000) @@ -106,7 +105,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { /* - control flow relocations */ case COMPAT_R_AARCH64_JUMP26: /* relocate b ... */ case COMPAT_R_AARCH64_CALL26: { /* relocate bl ... */ - assert(isInt64(26+2, addend)); /* X in range */ + CHECK(isInt64(26+2, addend)); /* X in range */ *(inst_t *)P = (*(inst_t *)P & 0xfc000000) /* keep upper 6 (32-6) * bits */ | ((uint32_t)(addend >> 2) & 0x03ffffff); @@ -114,8 +113,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { } case COMPAT_R_AARCH64_ADR_GOT_PAGE: { /* range is -2^32 <= X < 2^32 */ - assert(isInt64(21+12, addend)); /* X in range */ - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); /* X in range */ + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t)(((uint64_t)addend << 17) & 0x60000000) // lo @@ -149,10 +148,10 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { FALLTHROUGH; case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { if(exp_shift == -1) { - assert( (addend & 7) == 0 ); + CHECK( (addend & 7) == 0 ); exp_shift = 3; } - assert((addend & 0xfff) == addend); + CHECK((addend & 0xfff) == addend); int shift = 0; if(isLoadStore(P)) { /* bits 31, 30 encode the size. */ @@ -161,7 +160,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { shift = 4; } } - assert(addend == 0 || exp_shift == shift); + CHECK(addend == 0 || exp_shift == shift); *(inst_t *)P = (*(inst_t *)P & 0xffc003ff) | ((inst_t)(addend >> shift << 10) & 0x003ffc00); break; @@ -188,12 +187,12 @@ computeAddend(Section * section, Elf_Rel * rel, /* Position where something is relocated */ addr_t P = (addr_t)((uint8_t*)section->start + rel->r_offset); - assert(0x0 != P); - assert((uint64_t)section->start <= P); - assert(P <= (uint64_t)section->start + section->size); + CHECK(0x0 != P); + CHECK((uint64_t)section->start <= P); + CHECK(P <= (uint64_t)section->start + section->size); /* Address of the symbol */ addr_t S = (addr_t) symbol->addr; - assert(0x0 != S); + CHECK(0x0 != S); /* GOT slot for the symbol */ addr_t GOT_S = (addr_t) symbol->got_addr; @@ -243,16 +242,16 @@ computeAddend(Section * section, Elf_Rel * rel, } } - assert(0 == (0xffff000000000000 & S)); + CHECK(0 == (0xffff000000000000 & S)); V = S + A - P; - assert(isInt64(26+2, V)); /* X in range */ + CHECK(isInt64(26+2, V)); /* X in range */ } return V; } - case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: assert(0 == ((S+A) & 0x0f)); - case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: assert(0 == ((S+A) & 0x07)); - case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: assert(0 == ((S+A) & 0x03)); - case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: assert(0 == ((S+A) & 0x01)); + case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x0f)); + case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x07)); + case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x03)); + case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x01)); case COMPAT_R_AARCH64_LDST8_ABS_LO12_NC: /* type: static, class: aarch64, op: S + A */ return (S + A) & 0xfff; @@ -266,12 +265,12 @@ computeAddend(Section * section, Elf_Rel * rel, // TODO: fix this story proper, so that the transformation // makes sense without resorting to: everyone else // does it like this as well. - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return Page(GOT_S+A) - Page(P); } case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { // G(GDAT(S+A)) - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return (GOT_S + A) & 0xfff; } default: @@ -297,7 +296,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); + CHECK(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -323,8 +322,8 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relaTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); - assert(0x0 != symbol->addr); + CHECK(0x0 != symbol); + CHECK(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== rts/posix/OSThreads.c ===================================== @@ -401,8 +401,9 @@ interruptOSThread (OSThreadId id) void joinOSThread (OSThreadId id) { - if (pthread_join(id, NULL) != 0) { - sysErrorBelch("joinOSThread: error %d", errno); + int ret = pthread_join(id, NULL); + if (ret != 0) { + sysErrorBelch("joinOSThread: error %d", ret); } } ===================================== rts/sm/Evac.c ===================================== @@ -109,6 +109,8 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) // // However, if we are in a deadlock detection GC then we disable aging // so there is no need. + // + // See Note [Non-moving GC: Marking evacuated objects]. if (major_gc && !deadlock_detect_gc) markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) to); return to; @@ -134,6 +136,52 @@ alloc_for_copy (uint32_t size, uint32_t gen_no) The evacuate() code -------------------------------------------------------------------------- */ +/* + * Note [Non-moving GC: Marking evacuated objects] + * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ + * + * When the non-moving collector is in use we must be careful to ensure that any + * references to objects in the non-moving generation from younger generations + * are pushed to the mark queue. + * + * In particular we need to ensure that we handle newly-promoted objects are + * correctly marked. For instance, consider this case: + * + * generation 0 generation 1 + * ────────────── ────────────── + * + * ┌───────┐ + * ┌───────┐ │ A │ + * │ B │ ◁────────────────────────── │ │ + * │ │ ──┬─────────────────┐ └───────┘ + * └───────┘ ┆ after GC │ + * ┆ │ + * ┌───────┐ ┆ before GC │ ┌───────┐ + * │ C │ ◁┄┘ └─────▷ │ C' │ + * │ │ │ │ + * └───────┘ └───────┘ + * + * + * In this case object C started off in generation 0 and was evacuated into + * generation 1 during the preparatory GC. However, the only reference to C' + * is from B, which lives in the generation 0 (via aging); this reference will + * not be visible to the concurrent non-moving collector (which can only + * traverse the generation 1 heap). Consequently, upon evacuating C we need to + * ensure that C' is added to the update remembered set as we know that it will + * continue to be reachable via B (which is assumed to be reachable as it lives + * in a younger generation). + * + * Where this happens depends upon the type of the object (e.g. C'): + * + * - In the case of "normal" small heap-allocated objects this happens in + * alloc_for_copy. + * - In the case of compact region this happens in evacuate_compact. + * - In the case of large objects this happens in evacuate_large. + * + * See also Note [Aging under the non-moving collector] in NonMoving.c. + * + */ + /* size is in words We want to *always* inline this as often the size of the closure is static, @@ -356,6 +404,9 @@ evacuate_large(StgPtr p) __atomic_fetch_or(&bd->flags, BF_EVACUATED, __ATOMIC_ACQ_REL); if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_ACQ_REL); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) p); } initBdescr(bd, new_gen, new_gen->to); @@ -510,6 +561,9 @@ evacuate_compact (StgPtr p) bd->flags |= BF_EVACUATED; if (RTS_UNLIKELY(RtsFlags.GcFlags.useNonmoving && new_gen == oldest_gen)) { __atomic_fetch_or(&bd->flags, BF_NONMOVING, __ATOMIC_RELAXED); + + // See Note [Non-moving GC: Marking evacuated objects]. + markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, (StgClosure *) str); } initBdescr(bd, new_gen, new_gen->to); @@ -695,13 +749,6 @@ loop: */ if (flags & BF_LARGE) { evacuate_large((P_)q); - - // We may have evacuated the block to the nonmoving generation. If so - // we need to make sure it is added to the mark queue since the only - // reference to it may be from the moving heap. - if (major_gc && flags & BF_NONMOVING && !deadlock_detect_gc) { - markQueuePushClosureGC(&gct->cap->upd_rem_set.queue, q); - } return; } ===================================== rts/sm/GC.c ===================================== @@ -1701,13 +1701,8 @@ collect_gct_blocks (void) static void collect_pinned_object_blocks (void) { - generation *gen; const bool use_nonmoving = RtsFlags.GcFlags.useNonmoving; - if (use_nonmoving && major_gc) { - gen = oldest_gen; - } else { - gen = g0; - } + generation *const gen = (use_nonmoving && major_gc) ? oldest_gen : g0; for (uint32_t n = 0; n < n_capabilities; n++) { bdescr *last = NULL; @@ -1732,7 +1727,7 @@ collect_pinned_object_blocks (void) if (gen->large_objects != NULL) { gen->large_objects->u.back = last; } - g0->large_objects = RELAXED_LOAD(&capabilities[n]->pinned_object_blocks); + gen->large_objects = RELAXED_LOAD(&capabilities[n]->pinned_object_blocks); RELAXED_STORE(&capabilities[n]->pinned_object_blocks, NULL); } } ===================================== rts/sm/NonMoving.c ===================================== @@ -191,8 +191,8 @@ Mutex concurrent_coll_finished_lock; * === Other references === * * Apart from the design document in docs/storage/nonmoving-gc and the Ueno - * 2016 paper (TODO citation) from which it drew inspiration, there are a - * variety of other relevant Notes scattered throughout the tree: + * 2016 paper [ueno 2016] from which it drew inspiration, there are a variety + * of other relevant Notes scattered throughout the tree: * * - Note [Concurrent non-moving collection] (NonMoving.c) describes * concurrency control of the nonmoving collector @@ -204,6 +204,10 @@ Mutex concurrent_coll_finished_lock; * - Note [Aging under the non-moving collector] (NonMoving.c) describes how * we accommodate aging * + * - Note [Non-moving GC: Marking evacuated objects] (Evac.c) describes how + * non-moving objects reached by evacuate() are marked, which is necessary + * due to aging. + * * - Note [Large objects in the non-moving collector] (NonMovingMark.c) * describes how we track large objects. * @@ -232,6 +236,11 @@ Mutex concurrent_coll_finished_lock; * how we use the DIRTY flags associated with MUT_VARs and TVARs to improve * barrier efficiency. * + * [ueno 2016]: + * Katsuhiro Ueno and Atsushi Ohori. 2016. A fully concurrent garbage + * collector for functional programs on multicore processors. SIGPLAN Not. 51, + * 9 (September 2016), 421–433. DOI:https://doi.org/10.1145/3022670.2951944 + * * * Note [Concurrent non-moving collection] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -312,6 +321,8 @@ Mutex concurrent_coll_finished_lock; * * The non-moving collector will come to C in the mark queue and mark it. * + * The implementation details of this are described in Note [Non-moving GC: + * Marking evacuated objects] in Evac.c. * * Note [Deadlock detection under the non-moving collector] * ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -726,7 +737,6 @@ void nonmovingStop(void) "waiting for nonmoving collector thread to terminate"); ACQUIRE_LOCK(&concurrent_coll_finished_lock); waitCondition(&concurrent_coll_finished, &concurrent_coll_finished_lock); - joinOSThread(mark_thread); } #endif } ===================================== rts/win32/veh_excn.c ===================================== @@ -10,7 +10,6 @@ #include "ghcconfig.h" #include "veh_excn.h" #include "LinkerInternals.h" -#include #include #include #include @@ -195,7 +194,7 @@ void __register_hs_exception_handler( void ) __hs_handle = AddVectoredContinueHandler(CALL_LAST, __hs_exception_handler); // should the handler not be registered this will return a null. - assert(__hs_handle); + CHECK(__hs_handle); // Register for an exception filter to ensure the continue handler gets // hit if no one handled the exception. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d18e37b595c91f6fd4ab8b50fdd6f747b5fa235...706c924bc15979f349c9cc6671910972b04b251c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d18e37b595c91f6fd4ab8b50fdd6f747b5fa235...706c924bc15979f349c9cc6671910972b04b251c 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 Sun Nov 29 23:13:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 18:13:12 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/stringbuffer Message-ID: <5fc42b08b5008_86cf5745688639e4@gitlab.mail> Ben Gamari pushed new branch wip/stringbuffer at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/stringbuffer 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 Sun Nov 29 23:26:23 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 18:26:23 -0500 Subject: [Git][ghc/ghc][wip/stringbuffer] StringBuffer: Rid it of ForeignPtrs Message-ID: <5fc42e1f65a5e_86c879fa9c866050@gitlab.mail> Ben Gamari pushed to branch wip/stringbuffer at Glasgow Haskell Compiler / GHC Commits: b3027eb0 by Ben Gamari at 2020-11-29T18:26:15-05:00 StringBuffer: Rid it of ForeignPtrs Bumps haddock submodule. - - - - - 9 changed files: - compiler/GHC/Data/ByteArray.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Types/Error.hs - compiler/ghc.cabal.in - libraries/ghc-boot/GHC/Utils/Encoding.hs - testsuite/tests/parser/should_run/CountParserDeps.stdout - utils/haddock Changes: ===================================== compiler/GHC/Data/ByteArray.hs ===================================== @@ -14,6 +14,7 @@ module GHC.Data.ByteArray , MutableByteArray , getMutableByteArray , unsafeMutableByteArrayContents + , sizeofMutableByteArray , newMutableByteArray , newPinnedMutableByteArray , copyByteArray @@ -92,6 +93,10 @@ newPinnedMutableByteArray (I# size) = IO $ \s -> case newPinnedByteArray# size s of (# s', mba #) -> (# s', MutableByteArray mba #) +sizeofMutableByteArray :: MutableByteArray -> Int +sizeofMutableByteArray (MutableByteArray mba) = + I# (sizeofMutableByteArray# mba) + copyByteArray :: ByteArray -- ^ source -> Int -- ^ source offset ===================================== compiler/GHC/Data/StringBuffer.hs ===================================== @@ -17,8 +17,7 @@ Buffers for scanning string input stored in external arrays. module GHC.Data.StringBuffer ( - StringBuffer(..), - -- non-abstract for vs\/HaskellService + StringBuffer, -- * Creation\/destruction hGetStringBuffer, @@ -26,8 +25,11 @@ module GHC.Data.StringBuffer hPutStringBuffer, appendStringBuffers, stringToStringBuffer, + byteStringToStringBuffer, + withStringBufferContents, -- * Inspection + lengthStringBuffer, nextChar, currentChar, prevChar, @@ -51,13 +53,18 @@ module GHC.Data.StringBuffer #include "HsVersions.h" import GHC.Prelude +import GHC.Stack import GHC.Utils.Encoding import GHC.Data.FastString +import GHC.Data.ByteArray import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain import GHC.Utils.Misc +import Foreign.C.String +import qualified Data.ByteString as BS +import qualified Data.ByteString.Unsafe as BS import Data.Maybe import Control.Exception import System.IO @@ -65,6 +72,7 @@ import System.IO.Unsafe ( unsafePerformIO ) import GHC.IO.Encoding.UTF8 ( mkUTF8 ) import GHC.IO.Encoding.Failure ( CodingFailureMode(IgnoreCodingFailure) ) +import GHC.Word import GHC.Exts import Foreign @@ -72,18 +80,15 @@ import Foreign -- ----------------------------------------------------------------------------- -- The StringBuffer type --- |A StringBuffer is an internal pointer to a sized chunk of bytes. +-- | A 'StringBuffer' is an internal pointer to a sized chunk of bytes. -- The bytes are intended to be *immutable*. There are pure --- operations to read the contents of a StringBuffer. --- --- A StringBuffer may have a finalizer, depending on how it was --- obtained. +-- operations to read the contents of a 'StringBuffer'. -- data StringBuffer = StringBuffer { - buf :: {-# UNPACK #-} !(ForeignPtr Word8), - len :: {-# UNPACK #-} !Int, -- length - cur :: {-# UNPACK #-} !Int -- current pos + buf :: {-# UNPACK #-} !ByteArray, + cur :: {-# UNPACK #-} !Int + -- ^ Current position in bytes. } -- The buffer is assumed to be UTF-8 encoded, and furthermore -- we add three @\'\\0\'@ bytes to the end as sentinels so that the @@ -92,9 +97,17 @@ data StringBuffer instance Show StringBuffer where showsPrec _ s = showString "" +isValid :: StringBuffer -> Bool +isValid sb = sizeofByteArray (buf sb) >= cur sb + +checkValid :: HasCallStack => StringBuffer -> StringBuffer +checkValid sb + | not (isValid sb) = error "isValid" + | otherwise = sb + -- ----------------------------------------------------------------------------- -- Creation / Destruction @@ -102,34 +115,35 @@ instance Show StringBuffer where -- managed by the garbage collector. hGetStringBuffer :: FilePath -> IO StringBuffer hGetStringBuffer fname = do - h <- openBinaryFile fname ReadMode - size_i <- hFileSize h - offset_i <- skipBOM h size_i 0 -- offset is 0 initially - let size = fromIntegral $ size_i - offset_i - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> do - r <- if size == 0 then return 0 else hGetBuf h ptr size - hClose h - if (r /= size) - then ioError (userError "short read of file") - else newUTF8StringBuffer buf ptr size + h <- openBinaryFile fname ReadMode + size_i <- hFileSize h + offset_i <- skipBOM h size_i 0 -- offset is 0 initially + let size = fromIntegral $ size_i - offset_i + buf <- newPinnedMutableByteArray (size+3) + r <- if size == 0 + then return 0 + else hGetBuf h (unsafeMutableByteArrayContents buf) size + hClose h + if r /= size + then ioError (userError "short read of file") + else newUTF8StringBuffer buf size hGetStringBufferBlock :: Handle -> Int -> IO StringBuffer -hGetStringBufferBlock handle wanted - = do size_i <- hFileSize handle - offset_i <- hTell handle >>= skipBOM handle size_i - let size = min wanted (fromIntegral $ size_i-offset_i) - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> - do r <- if size == 0 then return 0 else hGetBuf handle ptr size - if r /= size - then ioError (userError $ "short read of file: "++show(r,size,size_i,handle)) - else newUTF8StringBuffer buf ptr size +hGetStringBufferBlock handle wanted = do + size_i <- hFileSize handle + offset_i <- hTell handle >>= skipBOM handle size_i + let size = min wanted (fromIntegral $ size_i-offset_i) + buf <- newPinnedMutableByteArray (size+3) + r <- if size == 0 + then return 0 + else hGetBuf handle (unsafeMutableByteArrayContents buf) size + if r /= size + then ioError (userError $ "short read of file: "++show(r,size,size_i,handle)) + else newUTF8StringBuffer buf size hPutStringBuffer :: Handle -> StringBuffer -> IO () -hPutStringBuffer hdl (StringBuffer buf len cur) - = withForeignPtr (plusForeignPtr buf cur) $ \ptr -> - hPutBuf hdl ptr len +hPutStringBuffer hdl (StringBuffer buf cur) = do + withByteArrayContents buf $ \ptr -> hPutBuf hdl (ptr `plusPtr` cur) (sizeofByteArray buf) -- | Skip the byte-order mark if there is one (see #1744 and #6016), -- and return the new position of the handle in bytes. @@ -156,39 +170,49 @@ skipBOM h size offset = where safeEncoding = mkUTF8 IgnoreCodingFailure -newUTF8StringBuffer :: ForeignPtr Word8 -> Ptr Word8 -> Int -> IO StringBuffer -newUTF8StringBuffer buf ptr size = do - pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0] +-- | @newUTF8StringBuffer buf size@ creates a 'StringBuffer' from a +-- 'MutableByteArray' of length @size+3@ containing UTF-8 encoded text. A three +-- byte sentinel will be added to the end of the buffer. +newUTF8StringBuffer :: MutableByteArray -> Int -> IO StringBuffer +newUTF8StringBuffer buf size = do + ASSERTM(return $ sizeofMutableByteArray buf == (size + 3)) -- sentinels for UTF-8 decoding - return $ StringBuffer buf size 0 + writeWord8Array buf (size+0) 0 + writeWord8Array buf (size+1) 0 + writeWord8Array buf (size+3) 0 + buf' <- unsafeFreezeByteArray buf + return $ StringBuffer buf' 0 appendStringBuffers :: StringBuffer -> StringBuffer -> IO StringBuffer -appendStringBuffers sb1 sb2 - = do newBuf <- mallocForeignPtrArray (size+3) - withForeignPtr newBuf $ \ptr -> - withForeignPtr (buf sb1) $ \sb1Ptr -> - withForeignPtr (buf sb2) $ \sb2Ptr -> - do copyArray ptr (sb1Ptr `advancePtr` cur sb1) sb1_len - copyArray (ptr `advancePtr` sb1_len) (sb2Ptr `advancePtr` cur sb2) sb2_len - pokeArray (ptr `advancePtr` size) [0,0,0] - return (StringBuffer newBuf size 0) - where sb1_len = calcLen sb1 - sb2_len = calcLen sb2 - calcLen sb = len sb - cur sb - size = sb1_len + sb2_len +appendStringBuffers sb1 sb2 = do + dst <- newPinnedMutableByteArray (size+3) + copyByteArray (buf sb1) (cur sb1) dst 0 sb1_len + copyByteArray (buf sb2) (cur sb2) dst sb1_len sb2_len + newUTF8StringBuffer dst size + where + sb1_len = lengthStringBuffer sb1 + sb2_len = lengthStringBuffer sb2 + size = sb1_len + sb2_len + +withStringBufferContents :: StringBuffer -> (CStringLen -> IO a) -> IO a +withStringBufferContents sb@(StringBuffer buf cur) action = + withByteArrayContents buf $ \p -> action (p `plusPtr` cur, lengthStringBuffer sb) + +byteStringToStringBuffer :: BS.ByteString -> StringBuffer +byteStringToStringBuffer bs = unsafePerformIO $ do + let size = BS.length bs + buf <- newPinnedMutableByteArray (size+3) + BS.unsafeUseAsCString bs (\p -> copyAddrToMutableByteArray p buf 0 size) + newUTF8StringBuffer buf size -- | Encode a 'String' into a 'StringBuffer' as UTF-8. The resulting buffer -- is automatically managed by the garbage collector. stringToStringBuffer :: String -> StringBuffer -stringToStringBuffer str = - unsafePerformIO $ do +stringToStringBuffer str = unsafePerformIO $ do let size = utf8EncodedLength str - buf <- mallocForeignPtrArray (size+3) - withForeignPtr buf $ \ptr -> do - utf8EncodeString ptr str - pokeArray (ptr `plusPtr` size :: Ptr Word8) [0,0,0] - -- sentinels for UTF-8 decoding - return (StringBuffer buf size 0) + buf <- newPinnedMutableByteArray (size+3) + utf8EncodeString (unsafeMutableByteArrayContents buf) str + newUTF8StringBuffer buf size -- ----------------------------------------------------------------------------- -- Grab a character @@ -200,14 +224,11 @@ stringToStringBuffer str = -- character cannot be decoded as UTF-8, @\'\\0\'@ is returned. {-# INLINE nextChar #-} nextChar :: StringBuffer -> (Char,StringBuffer) -nextChar (StringBuffer buf len (I# cur#)) = +nextChar sb@(StringBuffer buf (I# cur#)) = -- Getting our fingers dirty a little here, but this is performance-critical - inlinePerformIO $ - withForeignPtr buf $ \(Ptr a#) -> - case utf8DecodeCharAddr# (a# `plusAddr#` cur#) 0# of - (# c#, nBytes# #) -> - let cur' = I# (cur# +# nBytes#) in - return (C# c#, StringBuffer buf len cur') + case utf8DecodeCharByteArray# (getByteArray buf) cur# of + (# c#, nBytes# #) -> + (C# c#, checkValid $ sb { cur = I# (cur# +# nBytes#) }) -- | Return the first UTF-8 character of a nonempty 'StringBuffer' (analogous -- to 'Data.List.head'). __Warning:__ The behavior is undefined if the @@ -217,12 +238,11 @@ currentChar :: StringBuffer -> Char currentChar = fst . nextChar prevChar :: StringBuffer -> Char -> Char -prevChar (StringBuffer _ _ 0) deflt = deflt -prevChar (StringBuffer buf _ cur) _ = - inlinePerformIO $ - withForeignPtr buf $ \p -> do - p' <- utf8PrevChar (p `plusPtr` cur) - return (fst (utf8DecodeChar p')) +prevChar (StringBuffer _ 0) deflt = deflt +prevChar (StringBuffer buf cur) _ = + let !(I# p') = utf8PrevChar (getByteArray buf) cur + !(# c, _ #) = utf8DecodeCharByteArray# (getByteArray buf) p' + in C# c -- ----------------------------------------------------------------------------- -- Moving @@ -241,7 +261,7 @@ stepOn s = snd (nextChar s) offsetBytes :: Int -- ^ @n@, the number of bytes -> StringBuffer -> StringBuffer -offsetBytes i s = s { cur = cur s + i } +offsetBytes i s = checkValid $ s { cur = cur (checkValid s) + i } -- | Compute the difference in offset between two 'StringBuffer's that share -- the same buffer. __Warning:__ The behavior is undefined if the @@ -249,33 +269,34 @@ offsetBytes i s = s { cur = cur s + i } byteDiff :: StringBuffer -> StringBuffer -> Int byteDiff s1 s2 = cur s2 - cur s1 +lengthStringBuffer :: StringBuffer -> Int +lengthStringBuffer sb = sizeofByteArray (buf sb) - cur sb - 3 + -- | Check whether a 'StringBuffer' is empty (analogous to 'Data.List.null'). atEnd :: StringBuffer -> Bool -atEnd (StringBuffer _ l c) = l == c +atEnd sb = lengthStringBuffer sb == 0 -- | Computes a 'StringBuffer' which points to the first character of the -- wanted line. Lines begin at 1. atLine :: Int -> StringBuffer -> Maybe StringBuffer -atLine line sb@(StringBuffer buf len _) = - inlinePerformIO $ - withForeignPtr buf $ \p -> do - p' <- skipToLine line len p - if p' == nullPtr - then return Nothing - else - let - delta = p' `minusPtr` p - in return $ Just (sb { cur = delta - , len = len - delta - }) - +atLine line sb@(StringBuffer buf _) = + inlinePerformIO $ withByteArrayContents buf $ \p -> do + p' <- skipToLine line (lengthStringBuffer sb) p + if p' == nullPtr + then return Nothing + else + let !delta = p' `minusPtr` p + in return $! Just $! checkValid $ sb { cur = delta } + +-- | @skipToLine line len op0@ finds the byte offset to the beginning of +-- the given line number. skipToLine :: Int -> Int -> Ptr Word8 -> IO (Ptr Word8) skipToLine !line !len !op0 = go 1 op0 where - !opend = op0 `plusPtr` len + !op_end = op0 `plusPtr` len go !i_line !op - | op >= opend = pure nullPtr + | op >= op_end = pure nullPtr | i_line == line = pure op | otherwise = do w <- peek op :: IO Word8 @@ -300,39 +321,46 @@ lexemeToString :: StringBuffer -> Int -- ^ @n@, the number of bytes -> String lexemeToString _ 0 = "" -lexemeToString (StringBuffer buf _ cur) bytes = - utf8DecodeStringLazy buf cur bytes +lexemeToString sb bytes + | lengthStringBuffer sb < bytes = panic "lexemeToString: overflow 1" + | not (isValid sb) = panic "lexemeToString: overflow 2" +lexemeToString (StringBuffer buf (I# cur#)) (I# bytes#) = + utf8DecodeByteArrayLazy# (getByteArray buf) cur# bytes# lexemeToFastString :: StringBuffer -> Int -- ^ @n@, the number of bytes -> FastString lexemeToFastString _ 0 = nilFS -lexemeToFastString (StringBuffer buf _ cur) len = - inlinePerformIO $ - withForeignPtr buf $ \ptr -> - return $! mkFastStringBytes (ptr `plusPtr` cur) len +lexemeToFastString sb len | len > lengthStringBuffer sb = panic "lexemeToFastString" +lexemeToFastString (StringBuffer buf cur) len = + inlinePerformIO $ + withByteArrayContents buf $ \ptr -> + return $! mkFastStringBytes (ptr `plusPtr` cur) len -- | Return the previous @n@ characters (or fewer if we are less than @n@ -- characters into the buffer. decodePrevNChars :: Int -> StringBuffer -> String -decodePrevNChars n (StringBuffer buf _ cur) = - inlinePerformIO $ withForeignPtr buf $ \p0 -> - go p0 n "" (p0 `plusPtr` (cur - 1)) +decodePrevNChars n (StringBuffer buf0 cur) = + go (getByteArray buf0) (min n (cur - 1)) "" (cur - 1) where - go :: Ptr Word8 -> Int -> String -> Ptr Word8 -> IO String - go buf0 n acc p | n == 0 || buf0 >= p = return acc - go buf0 n acc p = do - p' <- utf8PrevChar p - let (c,_) = utf8DecodeChar p' - go buf0 (n - 1) (c:acc) p' + go :: ByteArray# -> Int -> String -> Int -> String + go buf n acc ofs + | n == 0 = acc + | otherwise = + let !ofs'@(I# ofs'#) = utf8PrevChar buf ofs + !(# c,_ #) = utf8DecodeCharByteArray# buf ofs'# + in go buf (n - 1) (C# c:acc) ofs' -- ----------------------------------------------------------------------------- -- Parsing integer strings in various bases parseUnsignedInteger :: StringBuffer -> Int -> Integer -> (Char->Int) -> Integer -parseUnsignedInteger (StringBuffer buf _ cur) len radix char_to_int - = inlinePerformIO $ withForeignPtr buf $ \ptr -> return $! let - go i x | i == len = x - | otherwise = case fst (utf8DecodeChar (ptr `plusPtr` (cur + i))) of - '_' -> go (i + 1) x -- skip "_" (#14473) - char -> go (i + 1) (x * radix + toInteger (char_to_int char)) - in go 0 0 +parseUnsignedInteger (StringBuffer buf (I# cur)) (I# len) radix char_to_int + = go (len +# cur) cur 0 + where + go :: Int# -> Int# -> Integer -> Integer + go end i !acc + | isTrue# (i ==# end) = acc + | otherwise = + case utf8DecodeCharByteArray# (getByteArray buf) i of + (# '_'#, _ #) -> go end (i +# 1#) acc -- skip "_" (#14473) + (# char, _ #) -> go end (i +# 1#) (acc * radix + toInteger (char_to_int (C# char))) ===================================== compiler/GHC/Parser/Header.hs ===================================== @@ -214,7 +214,7 @@ lazyGetToks popts filename handle = do -- counteracts the quadratic slowdown we otherwise get for very -- large module names (#5981) nextbuf <- hGetStringBufferBlock handle new_size - if (len nextbuf == 0) then lazyLexBuf handle state True new_size else do + if lengthStringBuffer nextbuf == 0 then lazyLexBuf handle state True new_size else do newbuf <- appendStringBuffers (buffer state) nextbuf unsafeInterleaveIO $ lazyLexBuf handle state{buffer=newbuf} False new_size ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -1894,7 +1894,7 @@ lex_string_tok span buf _len = do ITprimstring _ bs -> ITprimstring (SourceText src) bs ITstring _ s -> ITstring (SourceText src) s _ -> panic "lex_string_tok" - src = lexemeToString buf (cur bufEnd - cur buf) + src = lexemeToString buf (lengthStringBuffer buf - lengthStringBuffer bufEnd) return (L (mkPsSpan (psSpanStart span) end) tok') lex_string :: String -> P Token @@ -1994,7 +1994,7 @@ finish_char_tok buf loc ch -- We've already seen the closing quote -- Just need to check for trailing # = do magicHash <- getBit MagicHashBit i@(AI end bufEnd) <- getInput - let src = lexemeToString buf (cur bufEnd - cur buf) + let src = lexemeToString buf (lengthStringBuffer buf - lengthStringBuffer bufEnd) if magicHash then do case alexGetChar' i of Just ('#',i@(AI end _)) -> do ===================================== compiler/GHC/Types/Error.hs ===================================== @@ -30,7 +30,7 @@ import GHC.Utils.Outputable as Outputable import qualified GHC.Utils.Ppr.Colour as Col import GHC.Types.SrcLoc as SrcLoc import GHC.Data.FastString (unpackFS) -import GHC.Data.StringBuffer (atLine, hGetStringBuffer, len, lexemeToString) +import GHC.Data.StringBuffer (atLine, hGetStringBuffer, lengthStringBuffer, lexemeToString) import GHC.Utils.Json import System.IO.Error ( catchIOError ) @@ -175,7 +175,7 @@ getCaretDiagnostic severity (RealSrcSpan span _) = content <- hGetStringBuffer fn case atLine i content of Just at_line -> pure $ - case lines (fix <$> lexemeToString at_line (len at_line)) of + case lines (fix <$> lexemeToString at_line (lengthStringBuffer at_line)) of srcLine : _ -> Just srcLine _ -> Nothing _ -> pure Nothing ===================================== compiler/ghc.cabal.in ===================================== @@ -356,6 +356,7 @@ Library GHC.Data.Bag GHC.Data.Bitmap GHC.Data.BooleanFormula + GHC.Data.ByteArray GHC.Data.EnumSet GHC.Data.FastMutInt GHC.Data.FastString ===================================== libraries/ghc-boot/GHC/Utils/Encoding.hs ===================================== @@ -17,12 +17,15 @@ module GHC.Utils.Encoding ( -- * UTF-8 utf8DecodeCharAddr#, + utf8DecodeCharByteArray#, utf8PrevChar, utf8CharStart, utf8DecodeChar, utf8DecodeByteString, + utf8DecodeByteArray, utf8DecodeShortByteString, utf8CompareShortByteString, + utf8DecodeByteArrayLazy#, utf8DecodeStringLazy, utf8EncodeChar, utf8EncodeString, @@ -53,6 +56,7 @@ import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import Data.ByteString.Short.Internal (ShortByteString(..)) +import GHC.Word import GHC.Exts -- ----------------------------------------------------------------------------- @@ -131,15 +135,20 @@ utf8DecodeChar !(Ptr a#) = -- the start of the current character is, given any position in a -- stream. This function finds the start of the previous character, -- assuming there *is* a previous character. -utf8PrevChar :: Ptr Word8 -> IO (Ptr Word8) -utf8PrevChar p = utf8CharStart (p `plusPtr` (-1)) +utf8PrevChar :: ByteArray# -> Int -> Int +utf8PrevChar arr ofs = utf8CharStart arr (ofs - 1) -utf8CharStart :: Ptr Word8 -> IO (Ptr Word8) -utf8CharStart p = go p - where go p = do w <- peek p - if w >= 0x80 && w < 0xC0 - then go (p `plusPtr` (-1)) - else return p +utf8CharStart :: ByteArray# -> Int -> Int +utf8CharStart = go + where + go arr ofs@(I# ofs#) + | True + , ofs < 0 || ofs > I# (sizeofByteArray# arr) + = error "utf8CharStart: overflow" + | w >= 0x80 && w < 0xC0 = go arr (ofs - 1) + | otherwise = ofs + where + w = W8# (indexWord8Array# arr ofs#) {-# INLINE utf8DecodeLazy# #-} utf8DecodeLazy# :: (IO ()) -> (Int# -> (# Char#, Int# #)) -> Int# -> IO [Char] @@ -158,6 +167,12 @@ utf8DecodeByteString :: ByteString -> [Char] utf8DecodeByteString (BS.PS fptr offset len) = utf8DecodeStringLazy fptr offset len +utf8DecodeByteArrayLazy# :: ByteArray# -> Int# -> Int# -> [Char] +utf8DecodeByteArrayLazy# a# offset# len# + = unsafeDupablePerformIO $ + let decodeChar i = utf8DecodeCharByteArray# a# (i +# offset#) + in utf8DecodeLazy# (return ()) decodeChar len# + utf8DecodeStringLazy :: ForeignPtr Word8 -> Int -> Int -> [Char] utf8DecodeStringLazy fp offset (I# len#) = unsafeDupablePerformIO $ do @@ -200,12 +215,15 @@ utf8CompareShortByteString (SBS a1) (SBS a2) = go 0# 0# | isTrue# (b1_1 `ltWord#` b2_1) -> LT | otherwise -> go (off1 +# 1#) (off2 +# 1#) -utf8DecodeShortByteString :: ShortByteString -> [Char] -utf8DecodeShortByteString (SBS ba#) +utf8DecodeByteArray :: ByteArray# -> [Char] +utf8DecodeByteArray ba# = unsafeDupablePerformIO $ let len# = sizeofByteArray# ba# in utf8DecodeLazy# (return ()) (utf8DecodeCharByteArray# ba#) len# +utf8DecodeShortByteString :: ShortByteString -> [Char] +utf8DecodeShortByteString (SBS ba#) = utf8DecodeByteArray ba# + countUTF8Chars :: ShortByteString -> IO Int countUTF8Chars (SBS ba) = go 0# 0# where ===================================== testsuite/tests/parser/should_run/CountParserDeps.stdout ===================================== @@ -1,4 +1,4 @@ -Found 235 parser module dependencies +Found 236 parser module dependencies GHC.Builtin.Names GHC.Builtin.PrimOps GHC.Builtin.Types @@ -62,6 +62,7 @@ GHC.Core.Utils GHC.CoreToIface GHC.Data.Bag GHC.Data.BooleanFormula +GHC.Data.ByteArray GHC.Data.EnumSet GHC.Data.FastMutInt GHC.Data.FastString ===================================== utils/haddock ===================================== @@ -1 +1 @@ -Subproject commit 25fa8fde84701c010fa466c2648f8f6d10265e8f +Subproject commit 8850e481da7c65cd023af9b3a37bad02edfb47e1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3027eb0a1c1b3cedbb54b0fc8d0924283a7cd25 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3027eb0a1c1b3cedbb54b0fc8d0924283a7cd25 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 Sun Nov 29 23:57:49 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 18:57:49 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/backports-9.0 Message-ID: <5fc4357db27da_86cf5745688666ae@gitlab.mail> Ben Gamari pushed new branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/backports-9.0 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 Mon Nov 30 00:16:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 19:16:25 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] 13 commits: Force argument in setIdMult (#18925) Message-ID: <5fc439d9d1be5_86cf574568872571@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 4fb008d8 by Krzysztof Gogolewski at 2020-11-29T18:59:20-05:00 Force argument in setIdMult (#18925) (cherry picked from commit 5506f1342e51bad71a7525ddad0650d1ac63afeb) - - - - - dd9989e8 by Moritz Angermann at 2020-11-29T19:06:22-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. (cherry picked from commit 8887102fc4ed8ed1089c1aafd19bab424ad706f3) - - - - - ca164a8e by Krzysztof Gogolewski at 2020-11-29T19:07:18-05:00 Export indexError from GHC.Ix (#18579) (cherry picked from commit 165352a2d163537afb01a835bccc7cd0a667410a) - - - - - cdcd8293 by Ben Gamari at 2020-11-29T19:07:38-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. (cherry picked from commit 9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251) - - - - - 2aba0183 by Ben Gamari at 2020-11-29T19:07:54-05:00 testsuite: Add testcase for #18733 (cherry picked from commit 787e93ae141ae0f33bc36895494d48a2a5e49e08) - - - - - 6676240e by Ben Gamari at 2020-11-29T19:09:25-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. (cherry picked from commit 5353fd500b1e92636cd9d45274585fd88a915ff6) - - - - - d0e54c32 by Ben Gamari at 2020-11-29T19:10:34-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. (cherry picked from commit a1a75aa9be2c133dd1372a08eeb6a92c31688df7) - - - - - af791a80 by Ben Gamari at 2020-11-29T19:11:04-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label (cherry picked from commit 7c03cc5010999d0f0f9dfc549984023b3a1f2c8d) - - - - - 5ae9157f by Ben Gamari at 2020-11-29T19:13:52-05:00 rts/linker: Ensure that .rodata is aligned to 16 bytes Pulled out of !4310. - - - - - 87641e70 by Ömer Sinan Ağacan at 2020-11-29T19:15:55-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - b24ffb88 by Ray Shih at 2020-11-29T19:15:57-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. (cherry picked from commit 2782487f5f6ad9df4dc8725226a47f07fec77f9f) - - - - - 7294ba96 by GHC GitLab CI at 2020-11-29T19:15:58-05:00 rts: Introduce highMemDynamic (cherry picked from commit 7a65f9e140906087273ce95f062775f18f6a708d) - - - - - d73edf58 by GHC GitLab CI at 2020-11-29T19:15:59-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. (cherry picked from commit e9e1b2e75de17be47ab887a26943f5517a8463ac) - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs - compiler/GHC/Platform/Regs.hs - compiler/GHC/Runtime/Linker.hs - compiler/GHC/Types/Var.hs - compiler/ghc.cabal.in - config.sub - includes/CodeGen.Platform.hs - includes/rts/Flags.h - includes/rts/Linker.h - includes/rts/storage/GC.h - libraries/base/GHC/Ix.hs - libraries/ghc-boot/GHC/Platform.hs - libraries/ghci/GHCi/InfoTable.hsc - llvm-targets - rts/Adjustor.c - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3aea3e8d8dd47ad16a5a4f607519d051a72c220d...d73edf587260b159c8c0121e7be1a9b4957b9b92 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3aea3e8d8dd47ad16a5a4f607519d051a72c220d...d73edf587260b159c8c0121e7be1a9b4957b9b92 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 Mon Nov 30 00:20:45 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 19:20:45 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Bump ci-images Message-ID: <5fc43add3788b_86cf574568873337@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: fe159dad by Ben Gamari at 2020-11-29T19:20:26-05:00 gitlab-ci: Bump ci-images - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -2,7 +2,7 @@ variables: GIT_SSL_NO_VERIFY: "1" # Commit of ghc/ci-images repository from which to pull Docker images - DOCKER_REV: 6223fe0b5942f4fa35bdec92c74566cf195bfb42 + DOCKER_REV: 0da9c4be73f2d73868f610d20352af856e8f2727 # Sequential version number capturing the versions of all tools fetched by # .gitlab/ci.sh. Used for invalidation of GitLab CI cache. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fe159dad5c8702428eefaf144e0ca3af8645f01c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fe159dad5c8702428eefaf144e0ca3af8645f01c 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 Mon Nov 30 00:34:25 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 19:34:25 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Backport ci.sh from master Message-ID: <5fc43e116e26b_86cbee25908755df@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 34382005 by Ben Gamari at 2020-11-29T19:34:08-05:00 gitlab-ci: Backport ci.sh from master - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -2,62 +2,78 @@ # shellcheck disable=SC2230 # This is the primary driver of the GitLab CI infrastructure. +# Run `ci.sh usage` for usage information. + set -e -o pipefail # Configuration: -hackage_index_state="@1579718451" - +hackage_index_state="2020-09-14T19:30:43Z" +MIN_HAPPY_VERSION="1.20" MIN_ALEX_VERSION="3.2" -# Colors -BLACK="0;30" -GRAY="1;30" -RED="0;31" -LT_RED="1;31" -BROWN="0;33" -LT_BROWN="1;33" -GREEN="0;32" -LT_GREEN="1;32" -BLUE="0;34" -LT_BLUE="1;34" -PURPLE="0;35" -LT_PURPLE="1;35" -CYAN="0;36" -LT_CYAN="1;36" -WHITE="1;37" -LT_GRAY="0;37" - -# GitLab Pipelines log section delimiters -# https://gitlab.com/gitlab-org/gitlab-foss/issues/14664 -start_section() { - name="$1" - echo -e "section_start:$(date +%s):$name\015\033[0K" -} +TOP="$(pwd)" +if [ ! -d "$TOP/.gitlab" ]; then + echo "This script expects to be run from the root of a ghc checkout" +fi -end_section() { - name="$1" - echo -e "section_end:$(date +%s):$name\015\033[0K" -} +source $TOP/.gitlab/common.sh -echo_color() { - local color="$1" - local msg="$2" - echo -e "\033[${color}m${msg}\033[0m" -} +function usage() { + cat < mk/build.mk echo 'GhcLibHcOpts+=-haddock' >> mk/build.mk @@ -405,6 +430,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -412,16 +442,24 @@ function test_make() { } function build_hadrian() { - if [ -z "$FLAVOUR" ]; then - fail "FLAVOUR not set" + if [ -z "$BUILD_FLAVOUR" ]; then + fail "BUILD_FLAVOUR not set" + fi + if [ -z "$BIN_DIST_NAME" ]; then + fail "BIN_DIST_NAME not set" fi run_hadrian binary-dist - mv _build/bindist/ghc*.tar.xz ghc.tar.xz + mv _build/bindist/ghc*.tar.xz $BIN_DIST_NAME.tar.xz } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -433,6 +471,34 @@ function test_hadrian() { --test-compiler="$TOP"/_build/install/bin/ghc } +function cabal_test() { + if [ -z "$OUT" ]; then + fail "OUT not set" + fi + + start_section "Cabal test: $OUT" + mkdir -p "$OUT" + run "$HC" \ + -hidir tmp -odir tmp -fforce-recomp \ + -ddump-to-file -dumpdir "$OUT/dumps" -ddump-timings \ + +RTS --machine-readable "-t$OUT/rts.log" -RTS \ + -package mtl -ilibraries/Cabal/Cabal libraries/Cabal/Cabal/Setup.hs \ + $@ + rm -Rf tmp + end_section "Cabal test: $OUT" +} + +function run_perf_test() { + if [ -z "$HC" ]; then + fail "HC not set" + fi + + mkdir -p out + OUT=out/Cabal-O0 cabal_test -O0 + OUT=out/Cabal-O1 cabal_test -O1 + OUT=out/Cabal-O2 cabal_test -O2 +} + function clean() { rm -R tmp run "$MAKE" --quiet clean || true @@ -441,8 +507,9 @@ function clean() { function run_hadrian() { if [ -z "$BIGNUM_BACKEND" ]; then BIGNUM_BACKEND="gmp"; fi + if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi run hadrian/build-cabal \ - --flavour="$FLAVOUR" \ + --flavour="$BUILD_FLAVOUR" \ -j"$cores" \ --broken-test="$BROKEN_TESTS" \ --bignum=$BIGNUM_BACKEND \ @@ -480,9 +547,15 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in + usage) usage ;; setup) setup && cleanup_submodules ;; configure) configure ;; build_make) build_make ;; @@ -503,6 +576,7 @@ case $1 in push_perf_notes exit $res ;; run_hadrian) run_hadrian $@ ;; + perf_test) run_perf_test ;; clean) clean ;; shell) shell $@ ;; *) fail "unknown mode $1" ;; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34382005dc47baa278c92e85c370d47284c8372d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34382005dc47baa278c92e85c370d47284c8372d 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 Mon Nov 30 00:35:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 19:35:12 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix ghc path Message-ID: <5fc43e40c4365_86cf574568876140@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/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 3819230b by Ben Gamari at 2020-11-29T19:34:56-05:00 gitlab-ci: Fix ghc path - - - - - [...] Content analysis details: (5.0 points, 5.0 required) pts rule name description ---- ---------------------- -------------------------------------------------- 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.8 RDNS_NONE Delivered to internal network by a host with no rDNS 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 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix ghc path Date: Sun, 29 Nov 2020 19:35:12 -0500 Size: 12132 URL: From gitlab at gitlab.haskell.org Mon Nov 30 00:42:00 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 19:42:00 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Backport gitlab-ci.yml from master Message-ID: <5fc43fd8de351_86c879fa9c87969c@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 6e427145 by Ben Gamari at 2020-11-29T19:41:46-05:00 gitlab-ci: Backport gitlab-ci.yml from master - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -17,14 +17,14 @@ variables: GIT_SUBMODULE_STRATEGY: "recursive" stages: - - lint # Source linting - - quick-build # A very quick smoke-test to weed out broken commits - - build # A quick smoke-test to weed out broken commits - - full-build # Build all the things - - cleanup # See Note [Cleanup after the shell executor] - - packaging # Source distribution, etc. - - testing # head.hackage correctness and compiler performance testing - - deploy # push documentation + - tool-lint # Source linting of the tools + - quick-build # A very quick smoke-test to weed out broken commits + - lint # Source linting of GHC + - build # A quick smoke-test to weed out broken commits + - full-build # Build all the things + - packaging # Source distribution, etc. + - testing # head.hackage correctness and compiler performance testing + - deploy # push documentation # Note [The CI Story] # ~~~~~~~~~~~~~~~~~~~ @@ -47,6 +47,7 @@ workflow: rules: - if: $CI_MERGE_REQUEST_ID - if: $CI_COMMIT_TAG + - if: '$CI_COMMIT_BRANCH == "master"' - if: '$CI_COMMIT_BRANCH == "wip/marge_bot_batch_merge_job"' - if: '$CI_COMMIT_BRANCH =~ /ghc-[0-9]+\.[0-9]+/' - if: '$CI_PIPELINE_SOURCE == "web"' @@ -61,7 +62,6 @@ workflow: .release: &release variables: BUILD_FLAVOUR: "perf" - FLAVOUR: "perf" artifacts: when: always expire_in: 1 year @@ -81,11 +81,11 @@ workflow: ############################################################ -# Linting +# tool linting ############################################################ ghc-linters: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME @@ -105,7 +105,7 @@ ghc-linters: # Run mypy Python typechecker on linter scripts. lint-linters: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - mypy .gitlab/linters/*.py @@ -115,7 +115,7 @@ lint-linters: # Check that .T files all parse by listing broken tests. lint-testsuite: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" script: - make -Ctestsuite list_broken TEST_HC=$GHC @@ -125,7 +125,7 @@ lint-testsuite: # Run mypy Python typechecker on testsuite driver typecheck-testsuite: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - mypy testsuite/driver/runtests.py @@ -137,7 +137,7 @@ typecheck-testsuite: # accommodate, e.g., haddock changes not yet upstream) but not on `master` or # Marge jobs. .lint-submods: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME @@ -169,7 +169,7 @@ lint-submods-branch: - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/' .lint-changelogs: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" dependencies: [] tags: @@ -189,14 +189,13 @@ lint-release-changelogs: rules: - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/' - ############################################################ # Validation via Pipelines (hadrian) ############################################################ .validate-hadrian: variables: - FLAVOUR: "validate" + BUILD_FLAVOUR: "validate" script: - .gitlab/ci.sh setup - .gitlab/ci.sh configure @@ -212,7 +211,7 @@ lint-release-changelogs: junit: junit.xml expire_in: 2 week paths: - - ghc.tar.xz + - "$BIN_DIST_NAME.tar.xz" - junit.xml .validate-linux-hadrian: @@ -220,6 +219,7 @@ lint-release-changelogs: image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" variables: TEST_ENV: "x86_64-linux-deb9-hadrian" + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" before_script: # workaround for docker permissions - sudo chown ghc:ghc -R . @@ -228,23 +228,65 @@ lint-release-changelogs: - git checkout .gitmodules - "git fetch https://gitlab.haskell.org/ghc/ghc-performance-notes.git refs/notes/perf:refs/notes/perf || true" after_script: + - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean tags: - x86_64-linux +# Verify that Hadrian builds with stack. Note that we don't actually perform a +# build of GHC itself; we merely test that the Hadrian executable builds and +# works (by invoking `hadrian --version`). +stack-hadrian-build: + extends: .validate-linux-hadrian + stage: build + script: + - .gitlab/ci.sh setup + - .gitlab/ci.sh configure + - hadrian/build-stack --version + validate-x86_64-linux-deb9-hadrian: extends: .validate-linux-hadrian + needs: [hadrian-ghc-in-ghci] stage: build validate-x86_64-linux-deb9-unreg-hadrian: extends: .validate-linux-hadrian + needs: [validate-x86_64-linux-deb9-hadrian] stage: full-build variables: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +validate-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV" + variables: + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*cross-compilation.*/' + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build + needs: [lint-linters, lint-submods] image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" before_script: # workaround for docker permissions @@ -257,20 +299,56 @@ hadrian-ghc-in-ghci: tags: - x86_64-linux script: + - .gitlab/ci.sh setup - cabal update - - cd hadrian; cabal new-build --project-file=ci.project; cd .. + - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. - git clean -xdf && git submodule foreach git clean -xdf - - .gitlab/ci.sh setup - - if [[ -d ./cabal-cache ]]; then cp -R ./.cabal-cache ~/.cabal-cache; fi - ./boot - ./configure $CONFIGURE_ARGS # Load ghc-in-ghci then immediately exit and check the modules loaded - echo ":q" | hadrian/ghci -j`mk/detect-cpu-count.sh`| tail -n2 | grep "Ok," + after_script: + - cp -Rf $HOME/.cabal cabal-cache cache: key: hadrian-ghci paths: - cabal-cache +############################################################ +# GHC source code linting +############################################################ + +.lint-params: + stage: lint + needs: [lint-submods] + tags: + - lint + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" + before_script: + - export PATH="/opt/toolchain/bin:$PATH" + # workaround for docker permissions + - sudo chown ghc:ghc -R . + - git submodule sync --recursive + - git submodule update --init --recursive + - git checkout .gitmodules + - .gitlab/ci.sh setup + - cabal update + - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache + variables: + GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache + +lint-base: + extends: .lint-params + script: + - hadrian/build -c -j stage1:lib:base + - hadrian/build -j lint:base + ############################################################ # Validation via Pipelines (make) ############################################################ @@ -299,7 +377,9 @@ hadrian-ghc-in-ghci: ################################# .build-x86_64-freebsd: + stage: full-build extends: .validate + needs: [validate-x86_64-linux-deb9-hadrian] tags: - x86_64-freebsd allow_failure: true @@ -329,23 +409,19 @@ hadrian-ghc-in-ghci: # Conditional due to lack of builder capacity validate-x86_64-freebsd: extends: .build-x86_64-freebsd - stage: full-build rules: - if: '$CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/' nightly-x86_64-freebsd: <<: *nightly extends: .build-x86_64-freebsd - stage: full-build release-x86_64-freebsd: <<: *release extends: .build-x86_64-freebsd - stage: full-build .build-x86_64-freebsd-hadrian: extends: .validate-hadrian - stage: full-build tags: - x86_64-freebsd allow_failure: true @@ -354,9 +430,9 @@ release-x86_64-freebsd: HADRIAN_ARGS: "--docs=no-sphinx" GHC_VERSION: 8.6.3 CABAL_INSTALL_VERSION: 3.0.0.0 - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-portbld-freebsd.tar.xz" + BIN_DIST_NAME: "ghc-x86_64-portbld-freebsd" TEST_ENV: "x86_64-freebsd-hadrian" - FLAVOUR: "validate" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -372,7 +448,6 @@ release-x86_64-freebsd: # Disabled due to lack of builder capacity .validate-x86_64-freebsd-hadrian: extends: .build-x86_64-freebsd-hadrian - stage: full-build ################################# # x86_64-darwin @@ -380,6 +455,7 @@ release-x86_64-freebsd: validate-x86_64-darwin: extends: .validate + needs: [validate-x86_64-linux-deb9-hadrian] stage: full-build tags: - x86_64-darwin @@ -409,6 +485,7 @@ validate-x86_64-darwin: # Disabled because of OS X CI capacity .validate-x86_64-darwin-hadrian: stage: full-build + needs: [validate-x86_64-linux-deb9-hadrian] tags: - x86_64-darwin variables: @@ -418,7 +495,8 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: --with-intree-gmp TEST_ENV: "x86_64-darwin-hadrian" - FLAVOUR: "validate" + BIN_DIST_NAME: "ghc-x86_64-apple-darwin" + BUILD_FLAVOUR: "validate" script: - .gitlab/ci.sh setup - .gitlab/ci.sh configure @@ -433,11 +511,12 @@ validate-x86_64-darwin: reports: junit: junit.xml paths: - - ghc.tar.xz + - "$BIN_DIST_NAME.tar.xz" - junit.xml .validate-linux: extends: .validate + needs: [validate-x86_64-linux-deb9-hadrian] tags: - x86_64-linux variables: @@ -460,66 +539,74 @@ validate-x86_64-darwin: - toolchain ################################# -# aarch64-linux-deb9 +# aarch64-linux-deb10 ################################# -.build-aarch64-linux-deb9: +.build-aarch64-linux-deb10: extends: .validate-linux stage: full-build - image: "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb9:$DOCKER_REV" + image: "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV" allow_failure: true variables: - TEST_ENV: "aarch64-linux-deb9" - BIN_DIST_PREP_TAR_COMP: "ghc-aarch64-linux-deb9.tar.xz" + TEST_ENV: "aarch64-linux-deb10" + BIN_DIST_PREP_TAR_COMP: "ghc-aarch64-linux-deb10.tar.xz" cache: - key: linux-aarch64-deb9 + key: linux-aarch64-deb10 + tags: + - aarch64-linux + +.build-aarch64-linux-deb10-llvm: + extends: .build-aarch64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm tags: - aarch64-linux -validate-aarch64-linux-deb9: - extends: .build-aarch64-linux-deb9 +validate-aarch64-linux-deb10: + extends: .build-aarch64-linux-deb10 artifacts: when: always expire_in: 2 week -nightly-aarch64-linux-deb9: +nightly-aarch64-linux-deb10: <<: *nightly - extends: .build-aarch64-linux-deb9 + extends: .build-aarch64-linux-deb10 variables: TEST_TYPE: slowtest ################################# -# armv7-linux-deb9 +# armv7-linux-deb10 ################################# -.build-armv7-linux-deb9: +.build-armv7-linux-deb10: extends: .validate-linux stage: full-build - image: "registry.gitlab.haskell.org/ghc/ci-images/armv7-linux-deb9:$DOCKER_REV" + image: "registry.gitlab.haskell.org/ghc/ci-images/armv7-linux-deb10:$DOCKER_REV" # Due to linker issues allow_failure: true variables: - TEST_ENV: "armv7-linux-deb9" - BIN_DIST_PREP_TAR_COMP: "ghc-armv7-linux-deb9.tar.xz" + TEST_ENV: "armv7-linux-deb10" + BIN_DIST_PREP_TAR_COMP: "ghc-armv7-linux-deb10.tar.xz" CONFIGURE_ARGS: "--host=armv7-linux-gnueabihf --build=armv7-linux-gnueabihf --target=armv7-linux-gnueabihf" # N.B. We disable ld.lld explicitly here because it appears to fail # non-deterministically on ARMv7. See #18280. LD: "ld.gold" GccUseLdOpt: "-fuse-ld=gold" cache: - key: linux-armv7-deb9 + key: linux-armv7-deb10 tags: - armv7-linux -validate-armv7-linux-deb9: - extends: .build-armv7-linux-deb9 +validate-armv7-linux-deb10: + extends: .build-armv7-linux-deb10 artifacts: when: always expire_in: 2 week -nightly-armv7-linux-deb9: +nightly-armv7-linux-deb10: <<: *nightly - extends: .build-armv7-linux-deb9 + extends: .build-armv7-linux-deb10 variables: TEST_TYPE: slowtest @@ -599,23 +686,6 @@ validate-x86_64-linux-deb9-debug: when: always expire_in: 2 week -validate-x86_64-linux-deb9-llvm: - extends: .build-x86_64-linux-deb9 - stage: full-build - rules: - - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/' - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - -nightly-x86_64-linux-deb9-llvm: - <<: *nightly - extends: .build-x86_64-linux-deb9 - stage: full-build - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - validate-x86_64-linux-deb9-integer-simple: extends: .build-x86_64-linux-deb9 stage: full-build @@ -691,6 +761,61 @@ release-x86_64-linux-deb10: <<: *release extends: .build-x86_64-linux-deb10 +release-x86_64-linux-deb10-dwarf: + <<: *release + extends: .build-x86_64-linux-deb10 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + TEST_ENV: "x86_64-linux-deb10-dwarf" + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz" + +validate-x86_64-linux-deb10-llvm: + extends: .build-x86_64-linux-deb10 + stage: full-build + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/' + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + +nightly-x86_64-linux-deb10-llvm: + <<: *nightly + extends: .build-x86_64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + +################################# +# x86_64-linux-ubuntu 20.04 +################################# + +.build-x86_64-linux-ubuntu2004: + extends: .validate-linux + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV" + variables: + TEST_ENV: "x86_64-linux-ubuntu2004" + BIN_DIST_PREP_TAR_COMP: "./ghc-x86_64-ubuntu2004-linux.tar.xz" + cache: + key: linux-x86_64-ubuntu2004 + +# Disabled to alleviate CI load +.validate-x86_64-linux-ubuntu2004: + extends: .build-x86_64-linux-ubuntu2004 + stage: full-build + +nightly-x86_64-linux-ubuntu2004: + <<: *nightly + extends: .build-x86_64-linux-ubuntu2004 + variables: + TEST_TYPE: slowtest + +release-x86_64-linux-ubuntu2004: + <<: *release + extends: .build-x86_64-linux-ubuntu2004 + ################################# # x86_64-linux-deb8 ################################# @@ -724,12 +849,12 @@ release-x86_64-linux-deb8: .build-x86_64-linux-alpine-hadrian: extends: .validate-linux-hadrian stage: full-build - image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine:$DOCKER_REV" + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV" # There are currently a few failing tests allow_failure: true variables: TEST_ENV: "x86_64-linux-alpine" - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-alpine-linux.tar.xz" + BIN_DIST_NAME: "ghc-x86_64-alpine-linux" # Can't use ld.gold due to #13958. CONFIGURE_ARGS: "--disable-ld-override" HADRIAN_ARGS: "--docs=no-sphinx" @@ -777,13 +902,15 @@ release-x86_64-linux-centos7: # x86_64-linux-fedora27 ################################# -validate-x86_64-linux-fedora27: +.build-x86_64-linux-fedora27: extends: .validate-linux stage: full-build image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora27:$DOCKER_REV" variables: + # LLVM 10 is not available for Fedora27 + LLC: /bin/false + OPT: /bin/false TEST_ENV: "x86_64-linux-fedora27" - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" cache: key: linux-x86_64-fedora27 artifacts: @@ -792,13 +919,26 @@ validate-x86_64-linux-fedora27: # longer. expire_in: 8 week +validate-x86_64-linux-fedora27: + extends: .build-x86_64-linux-fedora27 + variables: + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" + +release-x86_64-linux-fedora27-dwarf: + <<: *release + extends: .build-x86_64-linux-fedora27 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux-dwarf.tar.xz" + TEST_ENV: "x86_64-linux-fedora27-dwarf" + ############################################################ # Validation via Pipelines (Windows) ############################################################ .build-windows: - # For the reasons given in #17777 this build isn't reliable. - allow_failure: true + needs: [validate-x86_64-linux-deb9-hadrian] before_script: - git clean -xdf @@ -825,7 +965,7 @@ validate-x86_64-linux-fedora27: extends: .build-windows stage: full-build variables: - FLAVOUR: "validate" + BUILD_FLAVOUR: "validate" # skipping perf tests for now since we build a quick-flavoured GHC, # which might result in some broken perf tests? HADRIAN_ARGS: "--docs=no-sphinx --skip-perf" @@ -843,7 +983,7 @@ validate-x86_64-linux-fedora27: expire_in: 2 week when: always paths: - - ghc.tar.xz + - "$BIN_DIST_NAME.tar.xz" - junit.xml .build-x86_64-windows-hadrian: @@ -851,6 +991,7 @@ validate-x86_64-linux-fedora27: variables: MSYSTEM: MINGW64 TEST_ENV: "x86_64-windows" + BIN_DIST_NAME: "ghc-x86_64-unknown-mingw32" cache: key: "x86_64-windows-$WINDOWS_TOOLCHAIN_VERSION" @@ -910,45 +1051,8 @@ release-x86_64-windows-integer-simple: variables: BIGNUM_BACKEND: native BUILD_FLAVOUR: "perf" + BIN_DIST_NAME: "ghc-x86_64-mingw32-unknown-nogmp" -############################################################ -# Cleanup -############################################################ - -# Note [Cleaning up after shell executor] -# ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -# -# As noted in [1], gitlab-runner's shell executor doesn't clean up its working -# directory after builds. Unfortunately, we are forced to use the shell executor -# on Darwin. To avoid running out of disk space we add a stage at the end of -# the build to remove the /.../GitLabRunner/builds directory. Since we only run a -# single build at a time on Darwin this should be safe. -# -# We used to have a similar cleanup job on Windows as well however it ended up -# being quite fragile as we have multiple Windows builders yet there is no -# guarantee that the cleanup job is run on the same machine as the build itself -# was run. Consequently we were forced to instead handle cleanup with a separate -# cleanup cron job on Windows. -# -# [1] https://gitlab.com/gitlab-org/gitlab-runner/issues/3856 - -# See Note [Cleanup after shell executor] -cleanup-darwin: - stage: cleanup - tags: - - x86_64-darwin - when: always - dependencies: [] - before_script: - - echo "Time to clean up" - script: - - echo "Let's go" - after_script: - - BUILD_DIR=$CI_PROJECT_DIR - - echo "Cleaning $BUILD_DIR" - - cd $HOME - - rm -Rf $BUILD_DIR/* - - exit 0 ############################################################ # Packaging @@ -956,6 +1060,9 @@ cleanup-darwin: doc-tarball: stage: packaging + needs: [validate-x86_64-linux-deb9-debug, validate-x86_64-windows-hadrian, validate-x86_64-linux-deb9-unreg-hadrian] + # N.B. Documentation isn't correctly packaged in Hadrian bindists + allow_failure: true tags: - x86_64-linux image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" @@ -964,9 +1071,7 @@ doc-tarball: - validate-x86_64-windows-hadrian variables: LINUX_BINDIST: "ghc-x86_64-deb9-linux-debug.tar.xz" - WINDOWS_BINDIST: "ghc-x86_64-mingw32.tar.xz" - # Due to Windows allow_failure - allow_failure: true + WINDOWS_BINDIST: "ghc-x86_64-unknown-mingw32.tar.xz" artifacts: paths: - haddock.html.tar.xz @@ -991,6 +1096,7 @@ doc-tarball: source-tarball: stage: packaging + needs: [validate-x86_64-linux-deb9-unreg-hadrian] tags: - x86_64-linux image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" @@ -1025,6 +1131,7 @@ source-tarball: .hackage: stage: testing + needs: [doc-tarball] image: ghcci/x86_64-linux-deb9:0.2 tags: - x86_64-linux @@ -1053,6 +1160,7 @@ nightly-hackage: perf-nofib: stage: testing + needs: [validate-x86_64-linux-deb9-dwarf, doc-tarball] dependencies: - validate-x86_64-linux-deb9-dwarf image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" @@ -1072,8 +1180,8 @@ perf-nofib: make install popd rm -Rf tmp - - export BOOT_HC=$(which ghc) - - cabal update; cabal install -w $BOOT_HC regex-compat + - export BOOT_HC=$GHC + - cabal update; cabal install -w "$BOOT_HC" --lib regex-compat - export PATH=$root/bin:$PATH - make -C nofib boot mode=fast -j$CPUS - "make -C nofib EXTRA_RUNTEST_OPTS='-cachegrind +RTS -V0 -RTS' NoFibRuns=1 mode=fast -j$CPUS 2>&1 | tee nofib.log" @@ -1083,17 +1191,52 @@ perf-nofib: paths: - nofib.log +############################################################ +# Ad-hoc performance testing +############################################################ + +perf: + stage: testing + needs: [validate-x86_64-linux-deb9-dwarf, doc-tarball] + dependencies: + - validate-x86_64-linux-deb9-dwarf + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" + rules: + - if: $CI_MERGE_REQUEST_ID + - if: '$CI_COMMIT_BRANCH == "master"' + - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/' + tags: + - x86_64-linux-perf + script: + - root=$(pwd)/ghc + - | + mkdir tmp + tar -xf ghc-x86_64-deb9-linux-dwarf.tar.xz -C tmp + pushd tmp/ghc-*/ + ./configure --prefix=$root + make install + popd + rm -Rf tmp + - export BOOT_HC=$(which ghc) + - export HC=$root/bin/ghc + - .gitlab/ci.sh perf_test + artifacts: + expire_in: 12 week + when: always + paths: + - out + + ############################################################ # Documentation deployment via GitLab Pages ############################################################ pages: stage: deploy + needs: [doc-tarball] dependencies: - doc-tarball image: ghcci/x86_64-linux-deb9:0.2 - # Due to Windows allow_failure - allow_failure: true tags: - x86_64-linux script: @@ -1109,7 +1252,9 @@ pages: EOF - cp -f index.html public/doc rules: - - if: '$CI_COMMIT_BRANCH == "master"' + # N.B. only run this on ghc/ghc since the deployed pages are quite large + # and we only serve GitLab Pages for ghc/ghc. + - if: '$CI_COMMIT_BRANCH == "master" && $CI_PROJECT_NAMESPACE == "ghc"' artifacts: paths: - public View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e4271452a171b5aef74b177f7b70e99f232f598 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6e4271452a171b5aef74b177f7b70e99f232f598 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 Mon Nov 30 00:49:23 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 19:49:23 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Backport ci.sh from master Message-ID: <5fc44193ba364_86c3fc6a6aa1b24880477@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 46e8a41a by Ben Gamari at 2020-11-29T19:49:17-05:00 gitlab-ci: Backport ci.sh from master - - - - - 3 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/common.sh Changes: ===================================== .gitlab-ci.yml ===================================== @@ -17,14 +17,14 @@ variables: GIT_SUBMODULE_STRATEGY: "recursive" stages: - - lint # Source linting - - quick-build # A very quick smoke-test to weed out broken commits - - build # A quick smoke-test to weed out broken commits - - full-build # Build all the things - - cleanup # See Note [Cleanup after the shell executor] - - packaging # Source distribution, etc. - - testing # head.hackage correctness and compiler performance testing - - deploy # push documentation + - tool-lint # Source linting of the tools + - quick-build # A very quick smoke-test to weed out broken commits + - lint # Source linting of GHC + - build # A quick smoke-test to weed out broken commits + - full-build # Build all the things + - packaging # Source distribution, etc. + - testing # head.hackage correctness and compiler performance testing + - deploy # push documentation # Note [The CI Story] # ~~~~~~~~~~~~~~~~~~~ @@ -47,6 +47,7 @@ workflow: rules: - if: $CI_MERGE_REQUEST_ID - if: $CI_COMMIT_TAG + - if: '$CI_COMMIT_BRANCH == "master"' - if: '$CI_COMMIT_BRANCH == "wip/marge_bot_batch_merge_job"' - if: '$CI_COMMIT_BRANCH =~ /ghc-[0-9]+\.[0-9]+/' - if: '$CI_PIPELINE_SOURCE == "web"' @@ -61,7 +62,6 @@ workflow: .release: &release variables: BUILD_FLAVOUR: "perf" - FLAVOUR: "perf" artifacts: when: always expire_in: 1 year @@ -81,11 +81,11 @@ workflow: ############################################################ -# Linting +# tool linting ############################################################ ghc-linters: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME @@ -105,7 +105,7 @@ ghc-linters: # Run mypy Python typechecker on linter scripts. lint-linters: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - mypy .gitlab/linters/*.py @@ -115,17 +115,17 @@ lint-linters: # Check that .T files all parse by listing broken tests. lint-testsuite: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" script: - - make -Ctestsuite list_broken TEST_HC=ghc + - make -Ctestsuite list_broken TEST_HC=$GHC dependencies: [] tags: - lint # Run mypy Python typechecker on testsuite driver typecheck-testsuite: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - mypy testsuite/driver/runtests.py @@ -137,7 +137,7 @@ typecheck-testsuite: # accommodate, e.g., haddock changes not yet upstream) but not on `master` or # Marge jobs. .lint-submods: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" script: - git fetch "$CI_MERGE_REQUEST_PROJECT_URL" $CI_MERGE_REQUEST_TARGET_BRANCH_NAME @@ -169,7 +169,7 @@ lint-submods-branch: - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/' .lint-changelogs: - stage: lint + stage: tool-lint image: "registry.gitlab.haskell.org/ghc/ci-images/linters:$DOCKER_REV" dependencies: [] tags: @@ -189,14 +189,13 @@ lint-release-changelogs: rules: - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/' - ############################################################ # Validation via Pipelines (hadrian) ############################################################ .validate-hadrian: variables: - FLAVOUR: "validate" + BUILD_FLAVOUR: "validate" script: - .gitlab/ci.sh setup - .gitlab/ci.sh configure @@ -212,7 +211,7 @@ lint-release-changelogs: junit: junit.xml expire_in: 2 week paths: - - ghc.tar.xz + - "$BIN_DIST_NAME.tar.xz" - junit.xml .validate-linux-hadrian: @@ -220,6 +219,7 @@ lint-release-changelogs: image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" variables: TEST_ENV: "x86_64-linux-deb9-hadrian" + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" before_script: # workaround for docker permissions - sudo chown ghc:ghc -R . @@ -228,23 +228,65 @@ lint-release-changelogs: - git checkout .gitmodules - "git fetch https://gitlab.haskell.org/ghc/ghc-performance-notes.git refs/notes/perf:refs/notes/perf || true" after_script: + - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean tags: - x86_64-linux +# Verify that Hadrian builds with stack. Note that we don't actually perform a +# build of GHC itself; we merely test that the Hadrian executable builds and +# works (by invoking `hadrian --version`). +stack-hadrian-build: + extends: .validate-linux-hadrian + stage: build + script: + - .gitlab/ci.sh setup + - .gitlab/ci.sh configure + - hadrian/build-stack --version + validate-x86_64-linux-deb9-hadrian: extends: .validate-linux-hadrian + needs: [hadrian-ghc-in-ghci] stage: build validate-x86_64-linux-deb9-unreg-hadrian: extends: .validate-linux-hadrian + needs: [validate-x86_64-linux-deb9-hadrian] stage: full-build variables: CONFIGURE_ARGS: --enable-unregisterised TEST_ENV: "x86_64-linux-deb9-unreg-hadrian" +validate-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb10:$DOCKER_REV" + variables: + BIN_DIST_NAME: "ghc-x86_64-deb9-linux" + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*cross-compilation.*/' + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + +nightly-x86_64-linux-deb10-hadrian-cross-aarch64: + <<: *nightly + extends: .validate-linux-hadrian + stage: full-build + variables: + CONFIGURE_ARGS: --with-intree-gmp + CROSS_TARGET: "aarch64-linux-gnu" + + + +############################################################ +# GHC-in-GHCi (Hadrian) +############################################################ + hadrian-ghc-in-ghci: stage: quick-build + needs: [lint-linters, lint-submods] image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" before_script: # workaround for docker permissions @@ -257,20 +299,56 @@ hadrian-ghc-in-ghci: tags: - x86_64-linux script: + - .gitlab/ci.sh setup - cabal update - - cd hadrian; cabal new-build --project-file=ci.project; cd .. + - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. - git clean -xdf && git submodule foreach git clean -xdf - - .gitlab/ci.sh setup - - if [[ -d ./cabal-cache ]]; then cp -R ./.cabal-cache ~/.cabal-cache; fi - ./boot - ./configure $CONFIGURE_ARGS # Load ghc-in-ghci then immediately exit and check the modules loaded - echo ":q" | hadrian/ghci -j`mk/detect-cpu-count.sh`| tail -n2 | grep "Ok," + after_script: + - cp -Rf $HOME/.cabal cabal-cache cache: key: hadrian-ghci paths: - cabal-cache +############################################################ +# GHC source code linting +############################################################ + +.lint-params: + stage: lint + needs: [lint-submods] + tags: + - lint + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" + before_script: + - export PATH="/opt/toolchain/bin:$PATH" + # workaround for docker permissions + - sudo chown ghc:ghc -R . + - git submodule sync --recursive + - git submodule update --init --recursive + - git checkout .gitmodules + - .gitlab/ci.sh setup + - cabal update + - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. + after_script: + - cp -Rf $HOME/.cabal cabal-cache + variables: + GHC_FLAGS: -Werror + cache: + key: lint + paths: + - cabal-cache + +lint-base: + extends: .lint-params + script: + - hadrian/build -c -j stage1:lib:base + - hadrian/build -j lint:base + ############################################################ # Validation via Pipelines (make) ############################################################ @@ -299,7 +377,9 @@ hadrian-ghc-in-ghci: ################################# .build-x86_64-freebsd: + stage: full-build extends: .validate + needs: [validate-x86_64-linux-deb9-hadrian] tags: - x86_64-freebsd allow_failure: true @@ -329,23 +409,19 @@ hadrian-ghc-in-ghci: # Conditional due to lack of builder capacity validate-x86_64-freebsd: extends: .build-x86_64-freebsd - stage: full-build rules: - if: '$CI_MERGE_REQUEST_LABELS =~ /.*FreeBSD.*/' nightly-x86_64-freebsd: <<: *nightly extends: .build-x86_64-freebsd - stage: full-build release-x86_64-freebsd: <<: *release extends: .build-x86_64-freebsd - stage: full-build .build-x86_64-freebsd-hadrian: extends: .validate-hadrian - stage: full-build tags: - x86_64-freebsd allow_failure: true @@ -354,9 +430,9 @@ release-x86_64-freebsd: HADRIAN_ARGS: "--docs=no-sphinx" GHC_VERSION: 8.6.3 CABAL_INSTALL_VERSION: 3.0.0.0 - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-portbld-freebsd.tar.xz" + BIN_DIST_NAME: "ghc-x86_64-portbld-freebsd" TEST_ENV: "x86_64-freebsd-hadrian" - FLAVOUR: "validate" + BUILD_FLAVOUR: "validate" after_script: - cp -Rf $HOME/.cabal cabal-cache - .gitlab/ci.sh clean @@ -372,7 +448,6 @@ release-x86_64-freebsd: # Disabled due to lack of builder capacity .validate-x86_64-freebsd-hadrian: extends: .build-x86_64-freebsd-hadrian - stage: full-build ################################# # x86_64-darwin @@ -380,6 +455,7 @@ release-x86_64-freebsd: validate-x86_64-darwin: extends: .validate + needs: [validate-x86_64-linux-deb9-hadrian] stage: full-build tags: - x86_64-darwin @@ -409,6 +485,7 @@ validate-x86_64-darwin: # Disabled because of OS X CI capacity .validate-x86_64-darwin-hadrian: stage: full-build + needs: [validate-x86_64-linux-deb9-hadrian] tags: - x86_64-darwin variables: @@ -418,7 +495,8 @@ validate-x86_64-darwin: LANG: "en_US.UTF-8" CONFIGURE_ARGS: --with-intree-gmp TEST_ENV: "x86_64-darwin-hadrian" - FLAVOUR: "validate" + BIN_DIST_NAME: "ghc-x86_64-apple-darwin" + BUILD_FLAVOUR: "validate" script: - .gitlab/ci.sh setup - .gitlab/ci.sh configure @@ -433,11 +511,12 @@ validate-x86_64-darwin: reports: junit: junit.xml paths: - - ghc.tar.xz + - "$BIN_DIST_NAME.tar.xz" - junit.xml .validate-linux: extends: .validate + needs: [validate-x86_64-linux-deb9-hadrian] tags: - x86_64-linux variables: @@ -460,66 +539,74 @@ validate-x86_64-darwin: - toolchain ################################# -# aarch64-linux-deb9 +# aarch64-linux-deb10 ################################# -.build-aarch64-linux-deb9: +.build-aarch64-linux-deb10: extends: .validate-linux stage: full-build - image: "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb9:$DOCKER_REV" + image: "registry.gitlab.haskell.org/ghc/ci-images/aarch64-linux-deb10:$DOCKER_REV" allow_failure: true variables: - TEST_ENV: "aarch64-linux-deb9" - BIN_DIST_PREP_TAR_COMP: "ghc-aarch64-linux-deb9.tar.xz" + TEST_ENV: "aarch64-linux-deb10" + BIN_DIST_PREP_TAR_COMP: "ghc-aarch64-linux-deb10.tar.xz" cache: - key: linux-aarch64-deb9 + key: linux-aarch64-deb10 + tags: + - aarch64-linux + +.build-aarch64-linux-deb10-llvm: + extends: .build-aarch64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm tags: - aarch64-linux -validate-aarch64-linux-deb9: - extends: .build-aarch64-linux-deb9 +validate-aarch64-linux-deb10: + extends: .build-aarch64-linux-deb10 artifacts: when: always expire_in: 2 week -nightly-aarch64-linux-deb9: +nightly-aarch64-linux-deb10: <<: *nightly - extends: .build-aarch64-linux-deb9 + extends: .build-aarch64-linux-deb10 variables: TEST_TYPE: slowtest ################################# -# armv7-linux-deb9 +# armv7-linux-deb10 ################################# -.build-armv7-linux-deb9: +.build-armv7-linux-deb10: extends: .validate-linux stage: full-build - image: "registry.gitlab.haskell.org/ghc/ci-images/armv7-linux-deb9:$DOCKER_REV" + image: "registry.gitlab.haskell.org/ghc/ci-images/armv7-linux-deb10:$DOCKER_REV" # Due to linker issues allow_failure: true variables: - TEST_ENV: "armv7-linux-deb9" - BIN_DIST_PREP_TAR_COMP: "ghc-armv7-linux-deb9.tar.xz" + TEST_ENV: "armv7-linux-deb10" + BIN_DIST_PREP_TAR_COMP: "ghc-armv7-linux-deb10.tar.xz" CONFIGURE_ARGS: "--host=armv7-linux-gnueabihf --build=armv7-linux-gnueabihf --target=armv7-linux-gnueabihf" # N.B. We disable ld.lld explicitly here because it appears to fail # non-deterministically on ARMv7. See #18280. LD: "ld.gold" GccUseLdOpt: "-fuse-ld=gold" cache: - key: linux-armv7-deb9 + key: linux-armv7-deb10 tags: - armv7-linux -validate-armv7-linux-deb9: - extends: .build-armv7-linux-deb9 +validate-armv7-linux-deb10: + extends: .build-armv7-linux-deb10 artifacts: when: always expire_in: 2 week -nightly-armv7-linux-deb9: +nightly-armv7-linux-deb10: <<: *nightly - extends: .build-armv7-linux-deb9 + extends: .build-armv7-linux-deb10 variables: TEST_TYPE: slowtest @@ -599,23 +686,6 @@ validate-x86_64-linux-deb9-debug: when: always expire_in: 2 week -validate-x86_64-linux-deb9-llvm: - extends: .build-x86_64-linux-deb9 - stage: full-build - rules: - - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/' - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - -nightly-x86_64-linux-deb9-llvm: - <<: *nightly - extends: .build-x86_64-linux-deb9 - stage: full-build - variables: - BUILD_FLAVOUR: perf-llvm - TEST_ENV: "x86_64-linux-deb9-llvm" - validate-x86_64-linux-deb9-integer-simple: extends: .build-x86_64-linux-deb9 stage: full-build @@ -691,6 +761,61 @@ release-x86_64-linux-deb10: <<: *release extends: .build-x86_64-linux-deb10 +release-x86_64-linux-deb10-dwarf: + <<: *release + extends: .build-x86_64-linux-deb10 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + TEST_ENV: "x86_64-linux-deb10-dwarf" + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-deb10-linux-dwarf.tar.xz" + +validate-x86_64-linux-deb10-llvm: + extends: .build-x86_64-linux-deb10 + stage: full-build + rules: + - if: '$CI_MERGE_REQUEST_LABELS =~ /.*LLVM backend.*/' + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + +nightly-x86_64-linux-deb10-llvm: + <<: *nightly + extends: .build-x86_64-linux-deb10 + stage: full-build + variables: + BUILD_FLAVOUR: perf-llvm + TEST_ENV: "x86_64-linux-deb10-llvm" + +################################# +# x86_64-linux-ubuntu 20.04 +################################# + +.build-x86_64-linux-ubuntu2004: + extends: .validate-linux + stage: full-build + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-ubuntu20_04:$DOCKER_REV" + variables: + TEST_ENV: "x86_64-linux-ubuntu2004" + BIN_DIST_PREP_TAR_COMP: "./ghc-x86_64-ubuntu2004-linux.tar.xz" + cache: + key: linux-x86_64-ubuntu2004 + +# Disabled to alleviate CI load +.validate-x86_64-linux-ubuntu2004: + extends: .build-x86_64-linux-ubuntu2004 + stage: full-build + +nightly-x86_64-linux-ubuntu2004: + <<: *nightly + extends: .build-x86_64-linux-ubuntu2004 + variables: + TEST_TYPE: slowtest + +release-x86_64-linux-ubuntu2004: + <<: *release + extends: .build-x86_64-linux-ubuntu2004 + ################################# # x86_64-linux-deb8 ################################# @@ -724,12 +849,12 @@ release-x86_64-linux-deb8: .build-x86_64-linux-alpine-hadrian: extends: .validate-linux-hadrian stage: full-build - image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine:$DOCKER_REV" + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-alpine3_12:$DOCKER_REV" # There are currently a few failing tests allow_failure: true variables: TEST_ENV: "x86_64-linux-alpine" - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-alpine-linux.tar.xz" + BIN_DIST_NAME: "ghc-x86_64-alpine-linux" # Can't use ld.gold due to #13958. CONFIGURE_ARGS: "--disable-ld-override" HADRIAN_ARGS: "--docs=no-sphinx" @@ -777,13 +902,15 @@ release-x86_64-linux-centos7: # x86_64-linux-fedora27 ################################# -validate-x86_64-linux-fedora27: +.build-x86_64-linux-fedora27: extends: .validate-linux stage: full-build image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora27:$DOCKER_REV" variables: + # LLVM 10 is not available for Fedora27 + LLC: /bin/false + OPT: /bin/false TEST_ENV: "x86_64-linux-fedora27" - BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" cache: key: linux-x86_64-fedora27 artifacts: @@ -792,13 +919,26 @@ validate-x86_64-linux-fedora27: # longer. expire_in: 8 week +validate-x86_64-linux-fedora27: + extends: .build-x86_64-linux-fedora27 + variables: + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux.tar.xz" + +release-x86_64-linux-fedora27-dwarf: + <<: *release + extends: .build-x86_64-linux-fedora27 + variables: + CONFIGURE_ARGS: "--enable-dwarf-unwind" + BUILD_FLAVOUR: dwarf + BIN_DIST_PREP_TAR_COMP: "ghc-x86_64-fedora27-linux-dwarf.tar.xz" + TEST_ENV: "x86_64-linux-fedora27-dwarf" + ############################################################ # Validation via Pipelines (Windows) ############################################################ .build-windows: - # For the reasons given in #17777 this build isn't reliable. - allow_failure: true + needs: [validate-x86_64-linux-deb9-hadrian] before_script: - git clean -xdf @@ -825,7 +965,7 @@ validate-x86_64-linux-fedora27: extends: .build-windows stage: full-build variables: - FLAVOUR: "validate" + BUILD_FLAVOUR: "validate" # skipping perf tests for now since we build a quick-flavoured GHC, # which might result in some broken perf tests? HADRIAN_ARGS: "--docs=no-sphinx --skip-perf" @@ -843,7 +983,7 @@ validate-x86_64-linux-fedora27: expire_in: 2 week when: always paths: - - ghc.tar.xz + - "$BIN_DIST_NAME.tar.xz" - junit.xml .build-x86_64-windows-hadrian: @@ -851,6 +991,7 @@ validate-x86_64-linux-fedora27: variables: MSYSTEM: MINGW64 TEST_ENV: "x86_64-windows" + BIN_DIST_NAME: "ghc-x86_64-unknown-mingw32" cache: key: "x86_64-windows-$WINDOWS_TOOLCHAIN_VERSION" @@ -910,45 +1051,8 @@ release-x86_64-windows-integer-simple: variables: BIGNUM_BACKEND: native BUILD_FLAVOUR: "perf" + BIN_DIST_NAME: "ghc-x86_64-mingw32-unknown-nogmp" -############################################################ -# Cleanup -############################################################ - -# Note [Cleaning up after shell executor] -# ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -# -# As noted in [1], gitlab-runner's shell executor doesn't clean up its working -# directory after builds. Unfortunately, we are forced to use the shell executor -# on Darwin. To avoid running out of disk space we add a stage at the end of -# the build to remove the /.../GitLabRunner/builds directory. Since we only run a -# single build at a time on Darwin this should be safe. -# -# We used to have a similar cleanup job on Windows as well however it ended up -# being quite fragile as we have multiple Windows builders yet there is no -# guarantee that the cleanup job is run on the same machine as the build itself -# was run. Consequently we were forced to instead handle cleanup with a separate -# cleanup cron job on Windows. -# -# [1] https://gitlab.com/gitlab-org/gitlab-runner/issues/3856 - -# See Note [Cleanup after shell executor] -cleanup-darwin: - stage: cleanup - tags: - - x86_64-darwin - when: always - dependencies: [] - before_script: - - echo "Time to clean up" - script: - - echo "Let's go" - after_script: - - BUILD_DIR=$CI_PROJECT_DIR - - echo "Cleaning $BUILD_DIR" - - cd $HOME - - rm -Rf $BUILD_DIR/* - - exit 0 ############################################################ # Packaging @@ -956,6 +1060,9 @@ cleanup-darwin: doc-tarball: stage: packaging + needs: [validate-x86_64-linux-deb9-debug, validate-x86_64-windows-hadrian, validate-x86_64-linux-deb9-unreg-hadrian] + # N.B. Documentation isn't correctly packaged in Hadrian bindists + allow_failure: true tags: - x86_64-linux image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" @@ -964,9 +1071,7 @@ doc-tarball: - validate-x86_64-windows-hadrian variables: LINUX_BINDIST: "ghc-x86_64-deb9-linux-debug.tar.xz" - WINDOWS_BINDIST: "ghc-x86_64-mingw32.tar.xz" - # Due to Windows allow_failure - allow_failure: true + WINDOWS_BINDIST: "ghc-x86_64-unknown-mingw32.tar.xz" artifacts: paths: - haddock.html.tar.xz @@ -991,6 +1096,7 @@ doc-tarball: source-tarball: stage: packaging + needs: [validate-x86_64-linux-deb9-unreg-hadrian] tags: - x86_64-linux image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" @@ -1025,6 +1131,7 @@ source-tarball: .hackage: stage: testing + needs: [doc-tarball] image: ghcci/x86_64-linux-deb9:0.2 tags: - x86_64-linux @@ -1053,6 +1160,7 @@ nightly-hackage: perf-nofib: stage: testing + needs: [validate-x86_64-linux-deb9-dwarf, doc-tarball] dependencies: - validate-x86_64-linux-deb9-dwarf image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" @@ -1072,8 +1180,8 @@ perf-nofib: make install popd rm -Rf tmp - - export BOOT_HC=$(which ghc) - - cabal update; cabal install -w $BOOT_HC regex-compat + - export BOOT_HC=$GHC + - cabal update; cabal install -w "$BOOT_HC" --lib regex-compat - export PATH=$root/bin:$PATH - make -C nofib boot mode=fast -j$CPUS - "make -C nofib EXTRA_RUNTEST_OPTS='-cachegrind +RTS -V0 -RTS' NoFibRuns=1 mode=fast -j$CPUS 2>&1 | tee nofib.log" @@ -1083,17 +1191,52 @@ perf-nofib: paths: - nofib.log +############################################################ +# Ad-hoc performance testing +############################################################ + +perf: + stage: testing + needs: [validate-x86_64-linux-deb9-dwarf, doc-tarball] + dependencies: + - validate-x86_64-linux-deb9-dwarf + image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-deb9:$DOCKER_REV" + rules: + - if: $CI_MERGE_REQUEST_ID + - if: '$CI_COMMIT_BRANCH == "master"' + - if: '$CI_COMMIT_BRANCH =~ /ghc-[0.9]+\.[0-9]+/' + tags: + - x86_64-linux-perf + script: + - root=$(pwd)/ghc + - | + mkdir tmp + tar -xf ghc-x86_64-deb9-linux-dwarf.tar.xz -C tmp + pushd tmp/ghc-*/ + ./configure --prefix=$root + make install + popd + rm -Rf tmp + - export BOOT_HC=$(which ghc) + - export HC=$root/bin/ghc + - .gitlab/ci.sh perf_test + artifacts: + expire_in: 12 week + when: always + paths: + - out + + ############################################################ # Documentation deployment via GitLab Pages ############################################################ pages: stage: deploy + needs: [doc-tarball] dependencies: - doc-tarball image: ghcci/x86_64-linux-deb9:0.2 - # Due to Windows allow_failure - allow_failure: true tags: - x86_64-linux script: @@ -1109,7 +1252,9 @@ pages: EOF - cp -f index.html public/doc rules: - - if: '$CI_COMMIT_BRANCH == "master"' + # N.B. only run this on ghc/ghc since the deployed pages are quite large + # and we only serve GitLab Pages for ghc/ghc. + - if: '$CI_COMMIT_BRANCH == "master" && $CI_PROJECT_NAMESPACE == "ghc"' artifacts: paths: - public ===================================== .gitlab/ci.sh ===================================== @@ -2,62 +2,78 @@ # shellcheck disable=SC2230 # This is the primary driver of the GitLab CI infrastructure. +# Run `ci.sh usage` for usage information. + set -e -o pipefail # Configuration: -hackage_index_state="@1579718451" - +hackage_index_state="2020-09-14T19:30:43Z" +MIN_HAPPY_VERSION="1.20" MIN_ALEX_VERSION="3.2" -# Colors -BLACK="0;30" -GRAY="1;30" -RED="0;31" -LT_RED="1;31" -BROWN="0;33" -LT_BROWN="1;33" -GREEN="0;32" -LT_GREEN="1;32" -BLUE="0;34" -LT_BLUE="1;34" -PURPLE="0;35" -LT_PURPLE="1;35" -CYAN="0;36" -LT_CYAN="1;36" -WHITE="1;37" -LT_GRAY="0;37" - -# GitLab Pipelines log section delimiters -# https://gitlab.com/gitlab-org/gitlab-foss/issues/14664 -start_section() { - name="$1" - echo -e "section_start:$(date +%s):$name\015\033[0K" -} +TOP="$(pwd)" +if [ ! -d "$TOP/.gitlab" ]; then + echo "This script expects to be run from the root of a ghc checkout" +fi -end_section() { - name="$1" - echo -e "section_end:$(date +%s):$name\015\033[0K" -} +source $TOP/.gitlab/common.sh -echo_color() { - local color="$1" - local msg="$2" - echo -e "\033[${color}m${msg}\033[0m" -} +function usage() { + cat < mk/build.mk echo 'GhcLibHcOpts+=-haddock' >> mk/build.mk @@ -405,6 +430,11 @@ function determine_metric_baseline() { } function test_make() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + run "$MAKE" test_bindist TEST_PREP=YES run "$MAKE" V=0 test \ THREADS="$cores" \ @@ -412,16 +442,24 @@ function test_make() { } function build_hadrian() { - if [ -z "$FLAVOUR" ]; then - fail "FLAVOUR not set" + if [ -z "$BUILD_FLAVOUR" ]; then + fail "BUILD_FLAVOUR not set" + fi + if [ -z "$BIN_DIST_NAME" ]; then + fail "BIN_DIST_NAME not set" fi run_hadrian binary-dist - mv _build/bindist/ghc*.tar.xz ghc.tar.xz + mv _build/bindist/ghc*.tar.xz $BIN_DIST_NAME.tar.xz } function test_hadrian() { + if [ -n "$CROSS_TARGET" ]; then + info "Can't test cross-compiled build." + return + fi + cd _build/bindist/ghc-*/ run ./configure --prefix="$TOP"/_build/install run "$MAKE" install @@ -433,6 +471,34 @@ function test_hadrian() { --test-compiler="$TOP"/_build/install/bin/ghc } +function cabal_test() { + if [ -z "$OUT" ]; then + fail "OUT not set" + fi + + start_section "Cabal test: $OUT" + mkdir -p "$OUT" + run "$HC" \ + -hidir tmp -odir tmp -fforce-recomp \ + -ddump-to-file -dumpdir "$OUT/dumps" -ddump-timings \ + +RTS --machine-readable "-t$OUT/rts.log" -RTS \ + -package mtl -ilibraries/Cabal/Cabal libraries/Cabal/Cabal/Setup.hs \ + $@ + rm -Rf tmp + end_section "Cabal test: $OUT" +} + +function run_perf_test() { + if [ -z "$HC" ]; then + fail "HC not set" + fi + + mkdir -p out + OUT=out/Cabal-O0 cabal_test -O0 + OUT=out/Cabal-O1 cabal_test -O1 + OUT=out/Cabal-O2 cabal_test -O2 +} + function clean() { rm -R tmp run "$MAKE" --quiet clean || true @@ -441,8 +507,9 @@ function clean() { function run_hadrian() { if [ -z "$BIGNUM_BACKEND" ]; then BIGNUM_BACKEND="gmp"; fi + if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi run hadrian/build-cabal \ - --flavour="$FLAVOUR" \ + --flavour="$BUILD_FLAVOUR" \ -j"$cores" \ --broken-test="$BROKEN_TESTS" \ --bignum=$BIGNUM_BACKEND \ @@ -480,9 +547,15 @@ case "$(uname)" in *) fail "uname $(uname) is not supported" ;; esac +if [ -n "$CROSS_TARGET" ]; then + info "Cross-compiling for $CROSS_TARGET..." + target_triple="$CROSS_TARGET" +fi + set_toolchain_paths case $1 in + usage) usage ;; setup) setup && cleanup_submodules ;; configure) configure ;; build_make) build_make ;; @@ -503,6 +576,7 @@ case $1 in push_perf_notes exit $res ;; run_hadrian) run_hadrian $@ ;; + perf_test) run_perf_test ;; clean) clean ;; shell) shell $@ ;; *) fail "unknown mode $1" ;; ===================================== .gitlab/common.sh ===================================== @@ -0,0 +1,50 @@ +# Common bash utilities +# ---------------------- + +# Colors +BLACK="0;30" +GRAY="1;30" +RED="0;31" +LT_RED="1;31" +BROWN="0;33" +LT_BROWN="1;33" +GREEN="0;32" +LT_GREEN="1;32" +BLUE="0;34" +LT_BLUE="1;34" +PURPLE="0;35" +LT_PURPLE="1;35" +CYAN="0;36" +LT_CYAN="1;36" +WHITE="1;37" +LT_GRAY="0;37" + +# GitLab Pipelines log section delimiters +# https://gitlab.com/gitlab-org/gitlab-foss/issues/14664 +start_section() { + name="$1" + echo -e "section_start:$(date +%s):$name\015\033[0K" +} + +end_section() { + name="$1" + echo -e "section_end:$(date +%s):$name\015\033[0K" +} + +echo_color() { + local color="$1" + local msg="$2" + echo -e "\033[${color}m${msg}\033[0m" +} + +error() { echo_color "${RED}" "$1"; } +warn() { echo_color "${LT_BROWN}" "$1"; } +info() { echo_color "${LT_BLUE}" "$1"; } + +fail() { error "error: $1"; exit 1; } + +function run() { + info "Running $*..." + "$@" || ( error "$* failed"; return 1; ) +} + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46e8a41ab3d9f0d7c7eae69f74689d6bf1f77e27 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46e8a41ab3d9f0d7c7eae69f74689d6bf1f77e27 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 Mon Nov 30 01:00:17 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:00:17 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix maximum happy version Message-ID: <5fc4442166d30_86cfd752bc8812df@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 96960190 by Ben Gamari at 2020-11-29T20:00:02-05:00 gitlab-ci: Fix maximum happy version - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -9,7 +9,8 @@ set -e -o pipefail # Configuration: hackage_index_state="2020-09-14T19:30:43Z" -MIN_HAPPY_VERSION="1.20" +MIN_HAPPY_VERSION="1.19.10" +MAX_HAPPY_VERSION="1.20" MIN_ALEX_VERSION="3.2" TOP="$(pwd)" @@ -317,7 +318,7 @@ function setup_toolchain() { cabal update info "Building happy..." - $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION" + $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION" --constraint="happy<$MAX_HAPPY_VERSION" info "Building alex..." $cabal_install alex --constraint="alex>=$MIN_ALEX_VERSION" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9696019052ac16afd30a67f53f9b31e5dca1ed37 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9696019052ac16afd30a67f53f9b31e5dca1ed37 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 Mon Nov 30 01:09:46 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:09:46 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix maximum happy version Message-ID: <5fc4465ae4b5c_86c15c5d388882048@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: cf52dbb4 by Ben Gamari at 2020-11-29T20:09:39-05:00 gitlab-ci: Fix maximum happy version - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -9,7 +9,8 @@ set -e -o pipefail # Configuration: hackage_index_state="2020-09-14T19:30:43Z" -MIN_HAPPY_VERSION="1.20" +MIN_HAPPY_VERSION="1.19.10" +MAX_HAPPY_VERSION="1.20" MIN_ALEX_VERSION="3.2" TOP="$(pwd)" @@ -317,7 +318,7 @@ function setup_toolchain() { cabal update info "Building happy..." - $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION" + $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION && <$MAX_HAPPY_VERSION" info "Building alex..." $cabal_install alex --constraint="alex>=$MIN_ALEX_VERSION" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf52dbb419ae12d552528d97b716112373979c5b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf52dbb419ae12d552528d97b716112373979c5b 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 Mon Nov 30 01:14:58 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:14:58 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix maximum happy version Message-ID: <5fc4479214ac5_86c111d4a00882626@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: fb35657b by Ben Gamari at 2020-11-29T20:14:52-05:00 gitlab-ci: Fix maximum happy version - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -9,7 +9,8 @@ set -e -o pipefail # Configuration: hackage_index_state="2020-09-14T19:30:43Z" -MIN_HAPPY_VERSION="1.20" +MIN_HAPPY_VERSION="1.19.10" +MAX_HAPPY_VERSION="1.20" MIN_ALEX_VERSION="3.2" TOP="$(pwd)" @@ -317,10 +318,10 @@ function setup_toolchain() { cabal update info "Building happy..." - $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION" + run $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION && <$MAX_HAPPY_VERSION" info "Building alex..." - $cabal_install alex --constraint="alex>=$MIN_ALEX_VERSION" + run $cabal_install alex --constraint="alex>=$MIN_ALEX_VERSION" } function cleanup_submodules() { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fb35657b6a6d204e1d8cdc82aec624153f12323d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fb35657b6a6d204e1d8cdc82aec624153f12323d 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 Mon Nov 30 01:21:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:21:40 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix maximum happy version Message-ID: <5fc449247baf3_86cf7c522c8838ef@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 37584e09 by Ben Gamari at 2020-11-29T20:21:24-05:00 gitlab-ci: Fix maximum happy version - - - - - 1 changed file: - .gitlab/ci.sh Changes: ===================================== .gitlab/ci.sh ===================================== @@ -9,7 +9,8 @@ set -e -o pipefail # Configuration: hackage_index_state="2020-09-14T19:30:43Z" -MIN_HAPPY_VERSION="1.20" +MIN_HAPPY_VERSION="1.19.10" +MAX_HAPPY_VERSION="1.20" MIN_ALEX_VERSION="3.2" TOP="$(pwd)" @@ -174,6 +175,9 @@ function set_toolchain_paths() { *) ;; esac + # HACK: GHC-9.0 requires happy 1.19 + HAPPY="$toolchain/bin/happy$exe" + if [[ "$needs_toolchain" = 1 ]]; then # These are populated by setup_toolchain GHC="$toolchain/bin/ghc$exe" @@ -317,10 +321,10 @@ function setup_toolchain() { cabal update info "Building happy..." - $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION" + run $cabal_install happy --constraint="happy>=$MIN_HAPPY_VERSION && <$MAX_HAPPY_VERSION" info "Building alex..." - $cabal_install alex --constraint="alex>=$MIN_ALEX_VERSION" + run $cabal_install alex --constraint="alex>=$MIN_ALEX_VERSION" } function cleanup_submodules() { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/37584e09238da2fbff166f965f964576e76eee3b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/37584e09238da2fbff166f965f964576e76eee3b 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 Mon Nov 30 01:34:51 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:34:51 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Use ci.sh to configure the ghci job Message-ID: <5fc44c3b8b46f_86c3fc6a6aa1b24884629@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: ecb8aabe by Ben Gamari at 2020-11-29T20:34:22-05:00 gitlab-ci: Use ci.sh to configure the ghci job - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -300,11 +300,10 @@ hadrian-ghc-in-ghci: - x86_64-linux script: - .gitlab/ci.sh setup + - .gitlab/ci.sh configure - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. - git clean -xdf && git submodule foreach git clean -xdf - - ./boot - - ./configure $CONFIGURE_ARGS # Load ghc-in-ghci then immediately exit and check the modules loaded - echo ":q" | hadrian/ghci -j`mk/detect-cpu-count.sh`| tail -n2 | grep "Ok," after_script: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ecb8aabef9e141f4c4030090799055936863797e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ecb8aabef9e141f4c4030090799055936863797e 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 Mon Nov 30 01:45:12 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:45:12 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Use ci.sh to configure the ghci job Message-ID: <5fc44ea83db99_86cbee259088567a@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: b6ce92a8 by Ben Gamari at 2020-11-29T20:44:58-05:00 gitlab-ci: Use ci.sh to configure the ghci job - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -299,12 +299,11 @@ hadrian-ghc-in-ghci: tags: - x86_64-linux script: + - git clean -xdf && git submodule foreach git clean -xdf - .gitlab/ci.sh setup + - .gitlab/ci.sh configure - cabal update - cd hadrian; cabal new-build -j`../mk/detect-cpu-count.sh` --with-compiler=$GHC --project-file=ci.project; cd .. - - git clean -xdf && git submodule foreach git clean -xdf - - ./boot - - ./configure $CONFIGURE_ARGS # Load ghc-in-ghci then immediately exit and check the modules loaded - echo ":q" | hadrian/ghci -j`mk/detect-cpu-count.sh`| tail -n2 | grep "Ok," after_script: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6ce92a8d47ce8e3fef5c202cf9e4afe5cd0fe42 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6ce92a8d47ce8e3fef5c202cf9e4afe5cd0fe42 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 Mon Nov 30 01:58:32 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 20:58:32 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix it Message-ID: <5fc451c868f8b_86cf7c522c8864ad@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: b1b0aa14 by Ben Gamari at 2020-11-29T20:58:21-05:00 gitlab-ci: Fix it - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -345,8 +345,10 @@ hadrian-ghc-in-ghci: lint-base: extends: .lint-params script: - - hadrian/build -c -j stage1:lib:base - - hadrian/build -j lint:base + - .gitlab/ci.sh setup + - .gitlab/ci.sh configure + - HADRIAN_ARGS="-c stage1:lib:base" .gitlab/ci.sh build_hadrian + - HADRIAN_ARGS="lint:base" .gitlab/ci.sh build_hadrian ############################################################ # Validation via Pipelines (make) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1b0aa14e633286219f09283ff576ff5556f982f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1b0aa14e633286219f09283ff576ff5556f982f 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 Mon Nov 30 02:07:32 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 21:07:32 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] gitlab-ci: Fix it Message-ID: <5fc453e4a67ab_86cf7c522c888254@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: ddb67503 by Ben Gamari at 2020-11-29T21:07:25-05:00 gitlab-ci: Fix it - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -344,9 +344,13 @@ hadrian-ghc-in-ghci: lint-base: extends: .lint-params + variables: + BUILD_FLAVOUR: default script: - - hadrian/build -c -j stage1:lib:base - - hadrian/build -j lint:base + - .gitlab/ci.sh setup + - .gitlab/ci.sh configure + - HADRIAN_ARGS="-c stage1:lib:base" .gitlab/ci.sh build_hadrian + - HADRIAN_ARGS="lint:base" .gitlab/ci.sh build_hadrian ############################################################ # Validation via Pipelines (make) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ddb6750323defb7422451d37373063d4cc1ea229 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ddb6750323defb7422451d37373063d4cc1ea229 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 Mon Nov 30 02:17:54 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 21:17:54 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] ghci-cabal Message-ID: <5fc456528f5f4_86c113040b08894c0@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 41928ca4 by Ben Gamari at 2020-11-29T21:17:46-05:00 ghci-cabal - - - - - 1 changed file: - hadrian/ghci-cabal.in Changes: ===================================== hadrian/ghci-cabal.in ===================================== @@ -5,5 +5,5 @@ set -e # Replace newlines with spaces, as these otherwise break the ghci invocation on windows. -GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-cabal" tool:ghc/Main.hs -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci $HADRIAN_ARGS | tr '\n\r' ' ')" +GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-cabal" -w "$GHC" tool:ghc/Main.hs -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci $HADRIAN_ARGS | tr '\n\r' ' ')" @WithGhc@ --interactive $GHC_FLAGS $@ -fno-code -fwrite-interface -hidir=.hadrian_ghci/interface -O0 +RTS -A128m View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41928ca4d42a6af52262af782b6daa737df1eac7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/41928ca4d42a6af52262af782b6daa737df1eac7 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 Mon Nov 30 02:22:38 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 21:22:38 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] ghci-cabal Message-ID: <5fc4576e74629_86ce89fc5c89002b@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: b2f3f92d by Ben Gamari at 2020-11-29T21:22:32-05:00 ghci-cabal - - - - - 2 changed files: - .gitlab-ci.yml - hadrian/ghci-cabal.in Changes: ===================================== .gitlab-ci.yml ===================================== @@ -346,6 +346,7 @@ lint-base: extends: .lint-params variables: BUILD_FLAVOUR: default + BIN_DIST_NAME: ghc.tar.xz script: - .gitlab/ci.sh setup - .gitlab/ci.sh configure ===================================== hadrian/ghci-cabal.in ===================================== @@ -5,5 +5,5 @@ set -e # Replace newlines with spaces, as these otherwise break the ghci invocation on windows. -GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-cabal" tool:ghc/Main.hs -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci $HADRIAN_ARGS | tr '\n\r' ' ')" +GHC_FLAGS="$GHC_FLAGS $(TERM=dumb CABFLAGS=-v0 "hadrian/build-cabal" -w "$GHC" tool:ghc/Main.hs -q --build-root=.hadrian_ghci --flavour=ghc-in-ghci $HADRIAN_ARGS | tr '\n\r' ' ')" @WithGhc@ --interactive $GHC_FLAGS $@ -fno-code -fwrite-interface -hidir=.hadrian_ghci/interface -O0 +RTS -A128m View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2f3f92d38bc2efd744c652dfde75b2327e714d7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2f3f92d38bc2efd744c652dfde75b2327e714d7 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 Mon Nov 30 02:31:11 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 21:31:11 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] More Message-ID: <5fc4596fd403d_86c111d4a00891056@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 751ece6f by Ben Gamari at 2020-11-29T21:31:01-05:00 More - - - - - 1 changed file: - hadrian/build-cabal Changes: ===================================== hadrian/build-cabal ===================================== @@ -1,8 +1,9 @@ #!/usr/bin/env bash -CABAL=cabal -CABFLAGS=("--disable-documentation" "--disable-profiling" "--disable-library-profiling" $CABFLAGS) -( ${GHC:-ghc} --info | grep -s '("Support SMP","YES")' > /dev/null ) || CABFLAGS+=("--constraint=hadrian -threaded") +CABAL="${CABAL:-cabal}" +GHC="${GHC:-ghc}" +CABFLAGS=("--with-compiler=$GHC" "--disable-documentation" "--disable-profiling" "--disable-library-profiling" $CABFLAGS) +( $GHC --info | grep -s '("Support SMP","YES")' > /dev/null ) || CABFLAGS+=("--constraint=hadrian -threaded") # It is currently more robust to pass Cabal an absolute path to the project file. PROJ="$PWD/hadrian/cabal.project" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/751ece6f52701e3cadb9d8da9612704ea2518f3c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/751ece6f52701e3cadb9d8da9612704ea2518f3c 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 Mon Nov 30 02:45:11 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 21:45:11 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] squash Small changes to Message-ID: <5fc45cb7116d_86c15c5d3888918d8@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 65ea34e9 by Ben Gamari at 2020-11-29T21:44:53-05:00 squash Small changes to - - - - - 1 changed file: - compiler/GHC/StgToCmm/Prim.hs Changes: ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -848,10 +848,6 @@ emitPrimOp dflags primop = case primop of emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] InterlockedExchange_Word -> \[src, value] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Xchg (wordWidth platform)) [src, value] - AtomicCompareExchange_Int -> \[dst, expected, new] -> opIntoRegs $ \[res] -> - emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] - AtomicCompareExchange_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> - emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] CasAddrOp_Addr -> \[dst, expected, new] -> opIntoRegs $ \[res] -> emitPrimCall [res] (MO_Cmpxchg (wordWidth platform)) [dst, expected, new] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/65ea34e932a8b42c94228bebc636730aeac1b32e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/65ea34e932a8b42c94228bebc636730aeac1b32e 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 Mon Nov 30 02:53:34 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Sun, 29 Nov 2020 21:53:34 -0500 Subject: [Git][ghc/ghc][wip/ghc-8.10-backports] 4 commits: CmmToLlvm: Declare signature for memcmp Message-ID: <5fc45eae92168_86ce89fc5c892414@gitlab.mail> Ben Gamari pushed to branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC Commits: 70ac4ed8 by Moritz Angermann at 2020-11-25T10:41:34+08:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - d0a18f89 by Viktor Dukhovni at 2020-11-29T21:53:30-05:00 8.10 - dirty MVAR after mutating TSO queue head While the original head and tail of the TSO queue may be in the same generation as the MVAR, interior elements of the queue could be younger after a GC run and may then be exposed by putMVar operation that updates the queue head. Resolves #18919 (cherry picked from commit 699facec0bc8dd7d5b82cc537fbf131b74f5bd2c) - - - - - 92c9bed7 by Ömer Sinan Ağacan at 2020-11-29T21:53:30-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 2d72607e by Ben Gamari at 2020-11-29T21:53:30-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. (cherry picked from commit 802e9180dd9a9a88c4e8869f0de1048e1edd6343) - - - - - 30 changed files: - .gitlab/ci.sh - compiler/ghci/Linker.hs - compiler/llvmGen/LlvmCodeGen/Base.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/PrimOps.cmm - rts/RtsStartup.c - rts/Threads.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/linker/elf_reloc_aarch64.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/driver/testlib.py - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d3458ac8e1a4cae1cacf25309072bebb7bac70f1...2d72607e7b6346ad3e0a7fe39e86ceb8f85e557b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d3458ac8e1a4cae1cacf25309072bebb7bac70f1...2d72607e7b6346ad3e0a7fe39e86ceb8f85e557b 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 Mon Nov 30 07:55:26 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 30 Nov 2020 02:55:26 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: rts/m32: Refactor handling of allocator seeding Message-ID: <5fc4a56e351da_86c3fc6a6aa1b249116cb@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 3fdad956 by Ben Gamari at 2020-11-30T02:55:14-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - ab14de08 by Ben Gamari at 2020-11-30T02:55:14-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 738bb286 by Ben Gamari at 2020-11-30T02:55:14-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - be04dc9b by Ryan Scott at 2020-11-30T02:55:14-05:00 Allow deploy:pages job to fail See #18973. - - - - - 9 changed files: - .gitlab-ci.yml - rts/Linker.c - rts/linker/Elf.c - rts/linker/M32Alloc.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/linker/elf_reloc_aarch64.c - rts/win32/veh_excn.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1237,6 +1237,8 @@ pages: dependencies: - doc-tarball image: ghcci/x86_64-linux-deb9:0.2 + # See #18973 + allow_failure: true tags: - x86_64-linux script: ===================================== rts/Linker.c ===================================== @@ -49,7 +49,6 @@ #include #include #include -#include #include #if defined(HAVE_SYS_STAT_H) @@ -885,12 +884,11 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) */ IF_DEBUG(linker, debugBelch("lookupSymbol: looking up %s with dlsym\n", lbl)); - ASSERT(lbl[0] == '_'); + CHECK(lbl[0] == '_'); return internal_dlsym(lbl + 1); # else - ASSERT(false); - return NULL; +# error No OBJFORMAT_* macro set # endif } else { if (dependent) { @@ -2112,7 +2110,7 @@ HsInt unloadNativeObj (void *handle) n_unloaded_objects += 1; // dynamic objects have no symbols - ASSERT(nc->symbols == NULL); + CHECK(nc->symbols == NULL); freeOcStablePtrs(nc); // Remove object code from root set ===================================== rts/linker/Elf.c ===================================== @@ -416,7 +416,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) "\nSection header table: start %ld, n_entries %d, ent_size %d\n", (long)ehdr->e_shoff, shnum, ehdr->e_shentsize )); - ASSERT(ehdr->e_shentsize == sizeof(Elf_Shdr)); + CHECK(ehdr->e_shentsize == sizeof(Elf_Shdr)); shdr = (Elf_Shdr*) (ehdrC + ehdr->e_shoff); @@ -537,7 +537,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) #if defined(SHN_XINDEX) /* See Note [Many ELF Sections] */ if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -864,7 +864,7 @@ ocGetNames_ELF ( ObjectCode* oc ) PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); - ASSERT(common_mem != NULL); + CHECK(common_mem != NULL); } //TODO: we ignore local symbols anyway right? So we can use the @@ -893,7 +893,7 @@ ocGetNames_ELF ( ObjectCode* oc ) secno = shndx; #if defined(SHN_XINDEX) if (shndx == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -902,11 +902,11 @@ ocGetNames_ELF ( ObjectCode* oc ) if (shndx == SHN_COMMON) { isLocal = false; - ASSERT(common_used < common_size); - ASSERT(common_mem); + CHECK(common_used < common_size); + CHECK(common_mem); symbol->addr = (void*)((uintptr_t)common_mem + common_used); common_used += symbol->elf_sym->st_size; - ASSERT(common_used <= common_size); + CHECK(common_used <= common_size); IF_DEBUG(linker, debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", @@ -935,7 +935,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ) ) { /* Section 0 is the undefined section, hence > and not >=. */ - ASSERT(secno > 0 && secno < shnum); + CHECK(secno > 0 && secno < shnum); /* if (shdr[secno].sh_type == SHT_NOBITS) { debugBelch(" BSS symbol, size %d off %d name %s\n", @@ -945,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - ASSERT(symbol->addr != 0x0); + CHECK(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -962,7 +962,7 @@ ocGetNames_ELF ( ObjectCode* oc ) /* And the decision is ... */ if (symbol->addr != NULL) { - ASSERT(nm != NULL); + CHECK(nm != NULL); /* Acquire! */ if (!isLocal) { @@ -1045,7 +1045,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, break; } } - ASSERT(stab != NULL); + CHECK(stab != NULL); targ = (Elf_Word*)oc->sections[target_shndx].start; IF_DEBUG(linker,debugBelch( @@ -1251,7 +1251,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, result = ((S + A) | T) - P; result &= ~1; // Clear thumb indicator bit - ASSERT(isInt(26, result)); /* X in range */ + CHECK(isInt(26, result)); /* X in range */ } // Update the branch target @@ -1426,7 +1426,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, case COMPAT_R_ARM_GOT_PREL: { int32_t A = *pP; void* GOT_S = symbol->got_addr; - ASSERT(GOT_S); + CHECK(GOT_S); *(uint32_t *)P = (uint32_t) GOT_S + A - P; break; } @@ -1552,21 +1552,21 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, case R_SPARC_WDISP30: w1 = *pP & 0xC0000000; w2 = (Elf_Word)((value - P) >> 2); - ASSERT((w2 & 0xC0000000) == 0); + CHECK((w2 & 0xC0000000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_HI22: w1 = *pP & 0xFFC00000; w2 = (Elf_Word)(value >> 10); - ASSERT((w2 & 0xFFC00000) == 0); + CHECK((w2 & 0xFFC00000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_LO10: w1 = *pP & ~0x3FF; w2 = (Elf_Word)(value & 0x3FF); - ASSERT((w2 & ~0x3FF) == 0); + CHECK((w2 & ~0x3FF) == 0); w1 |= w2; *pP = w1; break; @@ -1866,13 +1866,13 @@ ocResolve_ELF ( ObjectCode* oc ) Elf_Word secno = symbol->elf_sym->st_shndx; #if defined(SHN_XINDEX) if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[i]; } #endif - ASSERT(symbol->elf_sym->st_name == 0); - ASSERT(symbol->elf_sym->st_value == 0); - ASSERT(0x0 != oc->sections[ secno ].start); + CHECK(symbol->elf_sym->st_name == 0); + CHECK(symbol->elf_sym->st_value == 0); + CHECK(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1946,7 +1946,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { - ASSERT(0x0 != *init); + CHECK(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/M32Alloc.c ===================================== @@ -81,6 +81,7 @@ The allocator manages two kinds of allocations: * small allocations, which are allocated into a set of "nursery" pages (recorded in m32_allocator_t.pages; the size of the set is <= M32_MAX_PAGES) + * large allocations are those larger than a page and are mapped directly Each page (or the first page of a large allocation) begins with a m32_page_t @@ -126,7 +127,9 @@ code accordingly). To avoid unnecessary mapping/unmapping we maintain a global list of free pages (which can grow up to M32_MAX_FREE_PAGE_POOL_SIZE long). Pages on this list have the usual m32_page_t header and are linked together with -m32_page_t.free_page.next. +m32_page_t.free_page.next. When run out of free pages we allocate a chunk of +M32_MAP_PAGES to both avoid fragmenting our address space and amortize the +runtime cost of the mapping. The allocator is *not* thread-safe. @@ -139,7 +142,12 @@ The allocator is *not* thread-safe. * M32 ALLOCATOR (see Note [M32 Allocator] ***************************************************************************/ +/* How many open pages each allocator will keep around? */ #define M32_MAX_PAGES 32 +/* How many pages should we map at once when re-filling the free page pool? */ +#define M32_MAP_PAGES 32 +/* Upper bound on the number of pages to keep in the free page pool */ +#define M32_MAX_FREE_PAGE_POOL_SIZE 64 /** * Page header @@ -204,7 +212,6 @@ struct m32_allocator_t { * * We keep a small pool of free pages around to avoid fragmentation. */ -#define M32_MAX_FREE_PAGE_POOL_SIZE 16 struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO @@ -250,18 +257,33 @@ m32_release_page(struct m32_page_t *page) static struct m32_page_t * m32_alloc_page(void) { - if (m32_free_page_pool_size > 0) { - struct m32_page_t *page = m32_free_page_pool; - m32_free_page_pool = page->free_page.next; - m32_free_page_pool_size --; - return page; - } else { - struct m32_page_t *page = mmapForLinker(getPageSize(), PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); - if (page > (struct m32_page_t *) 0xffffffff) { + if (m32_free_page_pool_size == 0) { + /* + * Free page pool is empty; refill it with a new batch of M32_MAP_PAGES + * pages. + */ + const size_t pgsz = getPageSize(); + char *chunk = mmapForLinker(pgsz * M32_MAP_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + if (chunk > (char *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } - return page; + +#define GET_PAGE(i) ((struct m32_page_t *) (chunk + (i) * pgsz)) + for (int i=0; i < M32_MAP_PAGES; i++) { + struct m32_page_t *page = GET_PAGE(i); + page->free_page.next = GET_PAGE(i+1); + } + + GET_PAGE(M32_MAP_PAGES-1)->free_page.next = m32_free_page_pool; + m32_free_page_pool = (struct m32_page_t *) chunk; + m32_free_page_pool_size += M32_MAP_PAGES; +#undef GET_PAGE } + + struct m32_page_t *page = m32_free_page_pool; + m32_free_page_pool = page->free_page.next; + m32_free_page_pool_size --; + return page; } /** @@ -276,19 +298,6 @@ m32_allocator_new(bool executable) stgMallocBytes(sizeof(m32_allocator), "m32_new_allocator"); memset(alloc, 0, sizeof(struct m32_allocator_t)); alloc->executable = executable; - - // Preallocate the initial M32_MAX_PAGES to ensure that they don't - // fragment the memory. - size_t pgsz = getPageSize(); - char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); - if (bigchunk == NULL) - barf("m32_allocator_init: Failed to map"); - - int i; - for (i=0; ipages[i] = (struct m32_page_t *) (bigchunk + i*pgsz); - alloc->pages[i]->current_size = sizeof(struct m32_page_t); - } return alloc; } @@ -350,7 +359,9 @@ m32_allocator_push_filled_list(struct m32_page_t **head, struct m32_page_t *page void m32_allocator_flush(m32_allocator *alloc) { for (int i=0; ipages[i]->current_size == sizeof(struct m32_page_t)) { + if (alloc->pages[i] == NULL) { + continue; + } else if (alloc->pages[i]->current_size == sizeof(struct m32_page_t)) { // the page is empty, free it m32_release_page(alloc->pages[i]); } else { ===================================== rts/linker/MachO.c ===================================== @@ -252,7 +252,6 @@ resolveImports( "%s: unknown symbol `%s'", oc->fileName, symbol->name); return 0; } - ASSERT(addr); checkProddableBlock(oc, ((void**)(oc->image + sect->offset)) + i, @@ -847,7 +846,7 @@ relocateSection(ObjectCode* oc, int curSection) IF_DEBUG(linker, debugBelch(" : value = %p\n", (void *)symbol->nlist->n_value)); if ((symbol->nlist->n_type & N_TYPE) == N_SECT) { - ASSERT(symbol->addr != NULL); + CHECK(symbol->addr != NULL); value = (uint64_t) symbol->addr; IF_DEBUG(linker, debugBelch("relocateSection, defined external symbol %s, relocated address %p\n", nm, (void *)value)); @@ -949,29 +948,29 @@ relocateSection(ObjectCode* oc, int curSection) { if((int32_t)(value - baseValue) != (int64_t)(value - baseValue)) { - ASSERT(reloc->r_extern); + CHECK(reloc->r_extern); value = (uint64_t) &makeSymbolExtra(oc, reloc->r_symbolnum, value) -> jumpIsland; } - ASSERT((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); + CHECK((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); type = X86_64_RELOC_SIGNED; } switch(type) { case X86_64_RELOC_UNSIGNED: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing += value; break; case X86_64_RELOC_SIGNED: case X86_64_RELOC_SIGNED_1: case X86_64_RELOC_SIGNED_2: case X86_64_RELOC_SIGNED_4: - ASSERT(reloc->r_pcrel); + CHECK(reloc->r_pcrel); thing += value - baseValue; break; case X86_64_RELOC_SUBTRACTOR: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing -= value; break; default: ===================================== rts/linker/PEi386.c ===================================== @@ -1594,7 +1594,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) barf ("Could not allocate any heap memory from private heap."); } - ASSERT(section.size == 0 || section.info->virtualSize == 0); + CHECK(section.size == 0 || section.info->virtualSize == 0); sz = section.size; if (sz < section.info->virtualSize) sz = section.info->virtualSize; @@ -2032,7 +2032,7 @@ ocRunInit_PEi386 ( ObjectCode *oc ) getProgEnvv(&envc, &envv); Section section = *oc->info->init; - ASSERT(SECTIONKIND_INIT_ARRAY == section.kind); + CHECK(SECTIONKIND_INIT_ARRAY == section.kind); uint8_t *init_startC = section.start; init_t *init_start = (init_t*)init_startC; ===================================== rts/linker/elf_got.c ===================================== @@ -136,10 +136,10 @@ verifyGot(ObjectCode * oc) { for(size_t i=0; i < symTab->n_symbols; i++) { ElfSymbol * symbol = &symTab->symbols[i]; if(symbol->got_addr) { - ASSERT((void*)(*(void**)symbol->got_addr) - == (void*)symbol->addr); + CHECK((void*)(*(void**)symbol->got_addr) + == (void*)symbol->addr); } - ASSERT(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); + CHECK(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); } } return EXIT_SUCCESS; ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -6,7 +6,6 @@ #include "elf_plt.h" #include -#include #if defined(aarch64_HOST_ARCH) @@ -71,15 +70,15 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { *(uint64_t*)P = (uint64_t)addend; break; case COMPAT_R_AARCH64_ABS32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); case COMPAT_R_AARCH64_PREL32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); *(uint32_t*)P = (uint32_t)addend; break; case COMPAT_R_AARCH64_ABS16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); case COMPAT_R_AARCH64_PREL16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); *(uint16_t*)P = (uint16_t)addend; break; /* static aarch64 relocations */ @@ -95,8 +94,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { // imm64 = SignExtend(hi:lo:0x000,64) // Range is 21 bits + the 12 page relative bits // known to be 0. -2^32 <= X < 2^32 - assert(isInt64(21+12, addend)); - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t) (((uint64_t) addend << 17) & 0x60000000) @@ -106,7 +105,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { /* - control flow relocations */ case COMPAT_R_AARCH64_JUMP26: /* relocate b ... */ case COMPAT_R_AARCH64_CALL26: { /* relocate bl ... */ - assert(isInt64(26+2, addend)); /* X in range */ + CHECK(isInt64(26+2, addend)); /* X in range */ *(inst_t *)P = (*(inst_t *)P & 0xfc000000) /* keep upper 6 (32-6) * bits */ | ((uint32_t)(addend >> 2) & 0x03ffffff); @@ -114,8 +113,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { } case COMPAT_R_AARCH64_ADR_GOT_PAGE: { /* range is -2^32 <= X < 2^32 */ - assert(isInt64(21+12, addend)); /* X in range */ - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); /* X in range */ + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t)(((uint64_t)addend << 17) & 0x60000000) // lo @@ -149,10 +148,10 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { FALLTHROUGH; case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { if(exp_shift == -1) { - assert( (addend & 7) == 0 ); + CHECK( (addend & 7) == 0 ); exp_shift = 3; } - assert((addend & 0xfff) == addend); + CHECK((addend & 0xfff) == addend); int shift = 0; if(isLoadStore(P)) { /* bits 31, 30 encode the size. */ @@ -161,7 +160,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { shift = 4; } } - assert(addend == 0 || exp_shift == shift); + CHECK(addend == 0 || exp_shift == shift); *(inst_t *)P = (*(inst_t *)P & 0xffc003ff) | ((inst_t)(addend >> shift << 10) & 0x003ffc00); break; @@ -188,12 +187,12 @@ computeAddend(Section * section, Elf_Rel * rel, /* Position where something is relocated */ addr_t P = (addr_t)((uint8_t*)section->start + rel->r_offset); - assert(0x0 != P); - assert((uint64_t)section->start <= P); - assert(P <= (uint64_t)section->start + section->size); + CHECK(0x0 != P); + CHECK((uint64_t)section->start <= P); + CHECK(P <= (uint64_t)section->start + section->size); /* Address of the symbol */ addr_t S = (addr_t) symbol->addr; - assert(0x0 != S); + CHECK(0x0 != S); /* GOT slot for the symbol */ addr_t GOT_S = (addr_t) symbol->got_addr; @@ -243,16 +242,16 @@ computeAddend(Section * section, Elf_Rel * rel, } } - assert(0 == (0xffff000000000000 & S)); + CHECK(0 == (0xffff000000000000 & S)); V = S + A - P; - assert(isInt64(26+2, V)); /* X in range */ + CHECK(isInt64(26+2, V)); /* X in range */ } return V; } - case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: assert(0 == ((S+A) & 0x0f)); - case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: assert(0 == ((S+A) & 0x07)); - case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: assert(0 == ((S+A) & 0x03)); - case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: assert(0 == ((S+A) & 0x01)); + case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x0f)); + case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x07)); + case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x03)); + case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x01)); case COMPAT_R_AARCH64_LDST8_ABS_LO12_NC: /* type: static, class: aarch64, op: S + A */ return (S + A) & 0xfff; @@ -266,12 +265,12 @@ computeAddend(Section * section, Elf_Rel * rel, // TODO: fix this story proper, so that the transformation // makes sense without resorting to: everyone else // does it like this as well. - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return Page(GOT_S+A) - Page(P); } case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { // G(GDAT(S+A)) - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return (GOT_S + A) & 0xfff; } default: @@ -297,7 +296,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); + CHECK(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -323,8 +322,8 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relaTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); - assert(0x0 != symbol->addr); + CHECK(0x0 != symbol); + CHECK(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== rts/win32/veh_excn.c ===================================== @@ -10,7 +10,6 @@ #include "ghcconfig.h" #include "veh_excn.h" #include "LinkerInternals.h" -#include #include #include #include @@ -195,7 +194,7 @@ void __register_hs_exception_handler( void ) __hs_handle = AddVectoredContinueHandler(CALL_LAST, __hs_exception_handler); // should the handler not be registered this will return a null. - assert(__hs_handle); + CHECK(__hs_handle); // Register for an exception filter to ensure the continue handler gets // hit if no one handled the exception. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/706c924bc15979f349c9cc6671910972b04b251c...be04dc9b63621f4500d31126df1701d14f3abf83 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/706c924bc15979f349c9cc6671910972b04b251c...be04dc9b63621f4500d31126df1701d14f3abf83 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 Mon Nov 30 11:16:34 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 06:16:34 -0500 Subject: [Git][ghc/ghc] Deleted branch wip/ghc-8.10-backports Message-ID: <5fc4d492146ba_86cf5745689352df@gitlab.mail> Ben Gamari deleted branch wip/ghc-8.10-backports at Glasgow Haskell Compiler / GHC -- 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 Mon Nov 30 11:16:40 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 06:16:40 -0500 Subject: [Git][ghc/ghc][ghc-8.10] 3 commits: 8.10 - dirty MVAR after mutating TSO queue head Message-ID: <5fc4d49899e85_86c111d4a009354a5@gitlab.mail> Ben Gamari pushed to branch ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: d0a18f89 by Viktor Dukhovni at 2020-11-29T21:53:30-05:00 8.10 - dirty MVAR after mutating TSO queue head While the original head and tail of the TSO queue may be in the same generation as the MVAR, interior elements of the queue could be younger after a GC run and may then be exposed by putMVar operation that updates the queue head. Resolves #18919 (cherry picked from commit 699facec0bc8dd7d5b82cc537fbf131b74f5bd2c) - - - - - 92c9bed7 by Ömer Sinan Ağacan at 2020-11-29T21:53:30-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 2d72607e by Ben Gamari at 2020-11-29T21:53:30-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. (cherry picked from commit 802e9180dd9a9a88c4e8869f0de1048e1edd6343) - - - - - 28 changed files: - .gitlab/ci.sh - compiler/ghci/Linker.hs - rts/CheckUnload.c - rts/CheckUnload.h - rts/Hash.c - rts/Hash.h - rts/Linker.c - rts/LinkerInternals.h - rts/PrimOps.cmm - rts/RtsStartup.c - rts/Threads.c - rts/linker/Elf.c - rts/linker/LoadArchive.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/sm/Evac.c - rts/sm/GC.c - rts/sm/GC.h - testsuite/tests/ghci/T16525a/T16525a.script - testsuite/tests/ghci/T16525a/T16525a.stdout - testsuite/tests/ghci/T16525a/all.T - + testsuite/tests/ghci/T16525b/A.hs - + testsuite/tests/ghci/T16525b/B.hs - + testsuite/tests/ghci/T16525b/T16525b.script - + testsuite/tests/ghci/T16525b/T16525b.stdout - + testsuite/tests/ghci/T16525b/all.T - testsuite/tests/rts/linker/linker_error.c Changes: ===================================== .gitlab/ci.sh ===================================== @@ -348,6 +348,11 @@ function build_make() { if [[ -z "$BIN_DIST_PREP_TAR_COMP" ]]; then fail "BIN_DIST_PREP_TAR_COMP is not set" fi + if [[ -n "$VERBOSE" ]]; then + MAKE_ARGS="$MAKE_ARGS V=1" + else + MAKE_ARGS="$MAKE_ARGS V=0" + fi echo "include mk/flavours/${BUILD_FLAVOUR}.mk" > mk/build.mk echo 'GhcLibHcOpts+=-haddock' >> mk/build.mk @@ -402,6 +407,7 @@ function clean() { } function run_hadrian() { + if [ -n "$VERBOSE" ]; then HADRIAN_ARGS="$HADRIAN_ARGS -V"; fi run hadrian/build.cabal.sh \ --flavour="$FLAVOUR" \ -j"$cores" \ ===================================== compiler/ghci/Linker.hs ===================================== @@ -1134,14 +1134,15 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do where unloadObjs :: Linkable -> IO () unloadObjs lnk + -- The RTS's PEi386 linker currently doesn't support unloading. + | isWindowsHost = return () + | dynamicGhc = return () -- We don't do any cleanup when linking objects with the -- dynamic linker. Doing so introduces extra complexity for -- not much benefit. - -- Code unloading currently disabled due to instability. - -- See #16841. - | False -- otherwise + | otherwise = mapM_ (unloadObj hsc_env) [f | DotO f <- linkableUnlinked lnk] -- The components of a BCO linkable may contain -- dot-o files. Which is very confusing. @@ -1149,7 +1150,6 @@ unload_wkr hsc_env keep_linkables pls at PersistentLinkerState{..} = do -- But the BCO parts can be unlinked just by -- letting go of them (plus of course depopulating -- the symbol table which is done in the main body) - | otherwise = return () -- see #16841 {- ********************************************************************** ===================================== rts/CheckUnload.c ===================================== @@ -17,43 +17,99 @@ #include "CheckUnload.h" #include "sm/Storage.h" #include "sm/GCThread.h" +#include "sm/HeapUtils.h" // -// Code that we unload may be referenced from: -// - info pointers in heap objects and stack frames -// - pointers to static objects from the heap -// - StablePtrs to static objects -// - pointers to cost centres from the cost centre tree +// Note [Object unloading] +// ~~~~~~~~~~~~~~~~~~~~~~~ // -// We can find live static objects after a major GC, so we don't have -// to look at every closure pointer in the heap. However, we do have -// to look at every info pointer. So this is like a heap census -// traversal: we look at the header of every object, but not its -// contents. +// Overview of object unloading: // -// On the assumption that there aren't many different info pointers in -// a typical heap, we insert addresses into a hash table. The -// first time we see an address, we check it against the pending -// unloadable objects and if it lies within any of them, we mark that -// object as referenced so that it won't get unloaded in this round. +// - In a major GC, for every static object we mark the object's object code and +// its dependencies as 'live'. This is done by `markObjectCode`, called by +// `evacuate`. // - -// Note [Speeding up checkUnload] -// ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -// In certain circumstances, there may be a lot of unloaded ObjectCode structs -// chained in `unloaded_objects` (such as when users `:load` a module in a very -// big repo in GHCi). To speed up checking whether an address lies within any of -// these objects, we populate the addresses of their mapped sections in -// an array sorted by their `start` address and do binary search for our address -// on that array. Note that this works because the sections are mapped to mutual -// exclusive memory regions, so we can simply find the largest lower bound among -// the `start` addresses of the sections and then check if our address is inside -// that section. In particular, we store the start address and end address of -// each mapped section in a OCSectionIndex, arrange them all on a contiguous -// memory range and then sort by start address. We then put this array in an -// OCSectionIndices struct to be passed into `checkAddress` to do binary search -// on. +// - Marking object code is done using a global "section index table" +// (global_s_indices below). When we load an object code we add its section +// indices to the table. `markObjectCode` does binary search on this table to +// find object code for the marked object, and mark it and its dependencies. +// +// Dependency of an object code is simply other object code that the object +// code refers to in its code. We know these dependencies by the relocations +// present in the referent. This is recorded by lookupSymbolDependent. +// +// - global_s_indices is updated as we load and unload objects. When we load an +// object code we add its section indices to the table, we remove those +// indices when we unload. +// +// The table is sorted and old indices are removed in `checkUnload`, instead +// on every load/unload, to avoid quadratic behavior when we load a list of +// objects. +// +// - After a major GC `checkUnload` unloads objects that are (1) explicitly +// asked for unloading (via `unloadObj`) and (2) are not marked during GC. +// +// Note that, crucially, we don't unload an object code even if it's not +// reachable from the heap, unless it's explicitly asked for unloading (via +// `unloadObj`). This is a feature and not a but! Two use cases: +// +// - The user might request a symbol from a loaded object at any point with +// lookupSymbol (e.g. GHCi might do this). +// +// - Sometimes we load objects that are not Haskell objects. +// +// To avoid unloading objects that are unreachable but are not asked for +// unloading we maintain a "root set" of object code, `loaded_objects` below. +// `loadObj` adds the loaded objects (and its dependencies) to the list. +// `unloadObj` removes. After a major GC, `checkUnload` first marks the root set +// (`loaded_objects`) to avoid unloading objects that are not asked for +// unloading. +// +// Two other lists `objects` and `old_objects` are similar to large object lists +// in GC. Before a major GC we move `objects` to `old_objects`, and move marked +// objects back to `objects` during evacuation and when marking roots in +// `checkUnload`. Any objects in `old_objects` after that is unloaded. +// +// TODO: We currently don't unload objects when non-moving GC is enabled. The +// implementation would be similar to `nonmovingGcCafs`: +// +// - Maintain a "snapshot": +// +// - Copy `loaded_objects` as the root set of the snapshot +// +// - Stash `objects` to `old_objects` as the snapshot. We don't need a new +// list for this as `old_objects` won't be used by any other code when +// non-moving GC is enabled. +// +// - Copy `global_s_indices` table to be able to mark objects while mutators +// call `loadObj_` and `unloadObj_` concurrently. +// +// - Don't mark object code in `evacuate`, marking will be done in the +// non-moving collector. // +// - After preparation, bump the object code mark bit (`object_code_mark_bit` +// below) and mark static objects using a version of `markObjectCode` that +// basically does the same thing but: +// +// - Needs to update `objects` list in a thread-safe way, as mutators will be +// concurrently calling `loadObj_` and add new stuff to `objects`. +// (alternatively we could have a new list for non-moving GC's objects list, +// and then merge it to the global list in the pause before moving to +// concurrent sweep phase) +// +// - Needs to use the copied `global_s_indices` +// +// - After marking anything left in `old_objects` are unreachable objects within +// the snapshot, unload those. The unload loop will be the same as in +// `checkUnload`. This step needs to happen in the final sync (before sweep +// begins) to avoid races when updating `global_s_indices`. +// +// - NOTE: We don't need write barriers in loadObj/unloadObj as we don't +// introduce a dependency from an already-loaded object to a newly loaded +// object and we don't delete existing dependencies. +// + +uint8_t object_code_mark_bit = 0; typedef struct { W_ start; @@ -62,20 +118,85 @@ typedef struct { } OCSectionIndex; typedef struct { + int capacity; // Doubled on resize int n_sections; + bool sorted; // Invalidated on insertion. Sorted in checkUnload. + bool unloaded; // Whether we removed anything from the table in + // removeOCSectionIndices. If this is set we "compact" the + // table (remove unused entries) in `sortOCSectionIndices. OCSectionIndex *indices; } OCSectionIndices; -static OCSectionIndices *createOCSectionIndices(int n_sections) +// List of currently live objects. Moved to `old_objects` before unload check. +// Marked objects moved back to this list in `markObjectLive`. Remaining objects +// are freed at the end of `checkUnload`. +// +// Double-linked list to be able to remove marked objects. List formed with +// `next` and `prev` fields of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *objects = NULL; + +// `objects` list is moved here before unload check. Marked objects are moved +// back to `objects`. Remaining objects are freed. +static ObjectCode *old_objects = NULL; + +// Number of objects that we want to unload. When this value is 0 we skip static +// object marking during GC and `checkUnload`. +// +// Not static: we use this value to skip static object marking in evacuate when +// this is 0. +// +// Incremented in `unloadObj_`, decremented as we unload objects in +// `checkUnload`. +int n_unloaded_objects = 0; + +// List of objects that we don't want to unload (i.e. we haven't called +// unloadObj on these yet). Used as root set for unload check in checkUnload. +// Objects are added with loadObj_ and removed with unloadObj_. +// +// List formed with `next_loaded_object` field of `ObjectCode`. +// +// Not static: used in Linker.c. +ObjectCode *loaded_objects; + +// Section index table for currently loaded objects. New indices are added by +// `loadObj_`, indices of unloaded objects are removed in `checkUnload`. Used to +// map static closures to their ObjectCode. +static OCSectionIndices *global_s_indices = NULL; + +static OCSectionIndices *createOCSectionIndices(void) { - OCSectionIndices *s_indices; - s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); - s_indices->n_sections = n_sections; - s_indices->indices = stgMallocBytes(n_sections*sizeof(OCSectionIndex), + // TODO (osa): Maybe initialize as empty (without allocation) and allocate + // on first insertion? + OCSectionIndices *s_indices = stgMallocBytes(sizeof(OCSectionIndices), "OCSectionIndices"); + int capacity = 1024; + s_indices->capacity = capacity; + s_indices->n_sections = 0; + s_indices->sorted = true; + s_indices->unloaded = false; + s_indices->indices = stgMallocBytes(capacity * sizeof(OCSectionIndex), "OCSectionIndices::indices"); return s_indices; } +static void freeOCSectionIndices(OCSectionIndices *s_indices) +{ + free(s_indices->indices); + free(s_indices); +} + +void initUnloadCheck() +{ + global_s_indices = createOCSectionIndices(); +} + +void exitUnloadCheck() +{ + freeOCSectionIndices(global_s_indices); + global_s_indices = NULL; +} + static int cmpSectionIndex(const void* indexa, const void *indexb) { W_ s1 = ((OCSectionIndex*)indexa)->start; @@ -88,44 +209,124 @@ static int cmpSectionIndex(const void* indexa, const void *indexb) return 0; } -static OCSectionIndices* buildOCSectionIndices(ObjectCode *ocs) +static void reserveOCSectionIndices(OCSectionIndices *s_indices, int len) { - int cnt_sections = 0; - ObjectCode *oc; - for (oc = ocs; oc; oc = oc->next) { - cnt_sections += oc->n_sections; + int current_capacity = s_indices->capacity; + int current_len = s_indices->n_sections; + if (current_capacity - current_len >= len) { + return; + } + + // Round up to nearest power of 2 + int new_capacity = 1 << (int)ceil(log2(current_len + len)); + + OCSectionIndex *old_indices = s_indices->indices; + OCSectionIndex *new_indices = stgMallocBytes(new_capacity * sizeof(OCSectionIndex), + "reserveOCSectionIndices"); + + for (int i = 0; i < current_len; ++i) { + new_indices[i] = old_indices[i]; } - OCSectionIndices* s_indices = createOCSectionIndices(cnt_sections); - int s_i = 0, i; - for (oc = ocs; oc; oc = oc->next) { - for (i = 0; i < oc->n_sections; i++) { - if (oc->sections[i].kind != SECTIONKIND_OTHER) { - s_indices->indices[s_i].start = (W_)oc->sections[i].start; - s_indices->indices[s_i].end = (W_)oc->sections[i].start - + oc->sections[i].size; - s_indices->indices[s_i].oc = oc; - s_i++; + + s_indices->capacity = new_capacity; + s_indices->indices = new_indices; + + free(old_indices); +} + +// Insert object section indices of a single ObjectCode. Invalidates 'sorted' +// state. +void insertOCSectionIndices(ObjectCode *oc) +{ + reserveOCSectionIndices(global_s_indices, oc->n_sections); + global_s_indices->sorted = false; + + int s_i = global_s_indices->n_sections; + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + global_s_indices->indices[s_i].start = (W_)oc->sections[i].start; + global_s_indices->indices[s_i].end = (W_)oc->sections[i].start + + oc->sections[i].size; + global_s_indices->indices[s_i].oc = oc; + s_i++; + } + } + + global_s_indices->n_sections = s_i; + + // Add object to 'objects' list + if (objects != NULL) { + objects->prev = oc; + } + oc->next = objects; + objects = oc; +} + +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr); + +static void removeOCSectionIndices(OCSectionIndices *s_indices, ObjectCode *oc) +{ + // To avoid quadratic behavior in checkUnload we set `oc` fields of indices + // of unloaded objects NULL here. Removing unused entries is done in + // `sortOCSectionIndices`. + + s_indices->unloaded = true; + + for (int i = 0; i < oc->n_sections; i++) { + if (oc->sections[i].kind != SECTIONKIND_OTHER) { + int section_idx = findSectionIdx(s_indices, oc->sections[i].start); + if (section_idx != -1) { + s_indices->indices[section_idx].oc = NULL; } } } - s_indices->n_sections = s_i; +} + +static void sortOCSectionIndices(OCSectionIndices *s_indices) { + if (s_indices->sorted) { + return; + } + qsort(s_indices->indices, s_indices->n_sections, sizeof(OCSectionIndex), cmpSectionIndex); - return s_indices; + + s_indices->sorted = true; } -static void freeOCSectionIndices(OCSectionIndices *section_indices) -{ - free(section_indices->indices); - free(section_indices); +static void removeRemovedOCSections(OCSectionIndices *s_indices) { + if (!s_indices->unloaded) { + return; + } + + int next_free_idx = 0; + for (int i = 0; i < s_indices->n_sections; ++i) { + if (s_indices->indices[i].oc == NULL) { + // free entry, skip + } else if (i == next_free_idx) { + ++next_free_idx; + } else { + s_indices->indices[next_free_idx] = s_indices->indices[i]; + ++next_free_idx; + } + } + + s_indices->n_sections = next_free_idx; + s_indices->unloaded = true; } -static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { +// Returns -1 if not found +static int findSectionIdx(OCSectionIndices *s_indices, const void *addr) { + ASSERT(s_indices->sorted); + W_ w_addr = (W_)addr; - if (s_indices->n_sections <= 0) return NULL; - if (w_addr < s_indices->indices[0].start) return NULL; + if (s_indices->n_sections <= 0) { + return -1; + } + if (w_addr < s_indices->indices[0].start) { + return -1; + } int left = 0, right = s_indices->n_sections; while (left + 1 < right) { @@ -139,330 +340,125 @@ static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { } ASSERT(w_addr >= s_indices->indices[left].start); if (w_addr < s_indices->indices[left].end) { - return s_indices->indices[left].oc; + return left; } - return NULL; + return -1; } -static void checkAddress (HashTable *addrs, const void *addr, - OCSectionIndices *s_indices) -{ - ObjectCode *oc; - - if (!lookupHashTable(addrs, (W_)addr)) { - insertHashTable(addrs, (W_)addr, addr); +static ObjectCode *findOC(OCSectionIndices *s_indices, const void *addr) { + int oc_idx = findSectionIdx(s_indices, addr); - oc = findOC(s_indices, addr); - if (oc != NULL) { - oc->referenced = 1; - return; - } + if (oc_idx == -1) { + return NULL; } + + return s_indices->indices[oc_idx].oc; } -static void searchStackChunk (HashTable *addrs, StgPtr sp, StgPtr stack_end, - OCSectionIndices *s_indices) -{ - StgPtr p; - const StgRetInfoTable *info; +static bool markObjectLive(void *data STG_UNUSED, StgWord key, const void *value STG_UNUSED) { + ObjectCode *oc = (ObjectCode*)key; + if (oc->mark == object_code_mark_bit) { + return true; // for hash table iteration + } + + oc->mark = object_code_mark_bit; + // Remove from 'old_objects' list + if (oc->prev != NULL) { + // TODO(osa): Maybe 'prev' should be a pointer to the referencing + // *field* ? (instead of referencing *object*) + oc->prev->next = oc->next; + } else { + old_objects = oc->next; + } + if (oc->next != NULL) { + oc->next->prev = oc->prev; + } - p = sp; - while (p < stack_end) { - info = get_ret_itbl((StgClosure *)p); + // Add it to 'objects' list + oc->prev = NULL; + oc->next = objects; + if (objects != NULL) { + objects->prev = oc; + } + objects = oc; - switch (info->i.type) { - case RET_SMALL: - case RET_BIG: - checkAddress(addrs, (const void*)info, s_indices); - break; + // Mark its dependencies + iterHashTable(oc->dependencies, NULL, markObjectLive); - default: - break; - } + return true; // for hash table iteration +} + +void markObjectCode(const void *addr) +{ + if (global_s_indices == NULL) { + return; + } - p += stack_frame_sizeW((StgClosure*)p); + // This should be checked at the call site + ASSERT(!HEAP_ALLOCED(addr)); + + ObjectCode *oc = findOC(global_s_indices, addr); + if (oc != NULL) { + // Mark the object code and its dependencies + markObjectLive(NULL, (W_)oc, NULL); } } - -static void searchHeapBlocks (HashTable *addrs, bdescr *bd, - OCSectionIndices *s_indices) +// Returns whether or not the GC that follows needs to mark code for potential +// unloading. +bool prepareUnloadCheck() { - StgPtr p; - const StgInfoTable *info; - uint32_t size; - bool prim; + if (global_s_indices == NULL) { + return false; + } - for (; bd != NULL; bd = bd->link) { + removeRemovedOCSections(global_s_indices); + sortOCSectionIndices(global_s_indices); - if (bd->flags & BF_PINNED) { - // Assume that objects in PINNED blocks cannot refer to - continue; - } + ASSERT(old_objects == NULL); - p = bd->start; - while (p < bd->free) { - info = get_itbl((StgClosure *)p); - prim = false; - - switch (info->type) { - - case THUNK: - size = thunk_sizeW_fromITBL(info); - break; - - case THUNK_1_1: - case THUNK_0_2: - case THUNK_2_0: - size = sizeofW(StgThunkHeader) + 2; - break; - - case THUNK_1_0: - case THUNK_0_1: - case THUNK_SELECTOR: - size = sizeofW(StgThunkHeader) + 1; - break; - - case FUN: - case FUN_1_0: - case FUN_0_1: - case FUN_1_1: - case FUN_0_2: - case FUN_2_0: - case CONSTR: - case CONSTR_NOCAF: - case CONSTR_1_0: - case CONSTR_0_1: - case CONSTR_1_1: - case CONSTR_0_2: - case CONSTR_2_0: - size = sizeW_fromITBL(info); - break; - - case BLACKHOLE: - case BLOCKING_QUEUE: - prim = true; - size = sizeW_fromITBL(info); - break; - - case IND: - // Special case/Delicate Hack: INDs don't normally - // appear, since we're doing this heap census right - // after GC. However, GarbageCollect() also does - // resurrectThreads(), which can update some - // blackholes when it calls raiseAsync() on the - // resurrected threads. So we know that any IND will - // be the size of a BLACKHOLE. - prim = true; - size = BLACKHOLE_sizeW(); - break; - - case BCO: - prim = true; - size = bco_sizeW((StgBCO *)p); - break; - - case MVAR_CLEAN: - case MVAR_DIRTY: - case TVAR: - case WEAK: - case PRIM: - case MUT_PRIM: - case MUT_VAR_CLEAN: - case MUT_VAR_DIRTY: - prim = true; - size = sizeW_fromITBL(info); - break; - - case AP: - prim = true; - size = ap_sizeW((StgAP *)p); - break; - - case PAP: - prim = true; - size = pap_sizeW((StgPAP *)p); - break; - - case AP_STACK: - { - StgAP_STACK *ap = (StgAP_STACK *)p; - prim = true; - size = ap_stack_sizeW(ap); - searchStackChunk(addrs, (StgPtr)ap->payload, - (StgPtr)ap->payload + ap->size, s_indices); - break; - } + object_code_mark_bit = ~object_code_mark_bit; + old_objects = objects; + objects = NULL; + return true; +} - case ARR_WORDS: - prim = true; - size = arr_words_sizeW((StgArrBytes*)p); - break; - - case MUT_ARR_PTRS_CLEAN: - case MUT_ARR_PTRS_DIRTY: - case MUT_ARR_PTRS_FROZEN_CLEAN: - case MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = mut_arr_ptrs_sizeW((StgMutArrPtrs *)p); - break; - - case SMALL_MUT_ARR_PTRS_CLEAN: - case SMALL_MUT_ARR_PTRS_DIRTY: - case SMALL_MUT_ARR_PTRS_FROZEN_CLEAN: - case SMALL_MUT_ARR_PTRS_FROZEN_DIRTY: - prim = true; - size = small_mut_arr_ptrs_sizeW((StgSmallMutArrPtrs *)p); - break; - - case TSO: - prim = true; - size = sizeofW(StgTSO); - break; - - case STACK: { - StgStack *stack = (StgStack*)p; - prim = true; - searchStackChunk(addrs, stack->sp, - stack->stack + stack->stack_size, s_indices); - size = stack_sizeW(stack); - break; - } +void checkUnload() +{ + if (global_s_indices == NULL) { + return; + } - case TREC_CHUNK: - prim = true; - size = sizeofW(StgTRecChunk); - break; + // At this point we've marked all dynamically loaded static objects + // (including their dependencies) during GC, but not the root set of object + // code (loaded_objects). Mark the roots first, then unload any unmarked + // objects. - default: - barf("searchHeapBlocks, unknown object: %d", info->type); - } + OCSectionIndices *s_indices = global_s_indices; + ASSERT(s_indices->sorted); - if (!prim) { - checkAddress(addrs,info, s_indices); - } - - p += size; - } + // Mark roots + for (ObjectCode *oc = loaded_objects; oc != NULL; oc = oc->next_loaded_object) { + markObjectLive(NULL, (W_)oc, NULL); } -} -#if defined(PROFILING) -// -// Do not unload the object if the CCS tree refers to a CCS or CC which -// originates in the object. -// -static void searchCostCentres (HashTable *addrs, CostCentreStack *ccs, - OCSectionIndices* s_indices) -{ - IndexTable *i; + // Free unmarked objects + ObjectCode *next = NULL; + for (ObjectCode *oc = old_objects; oc != NULL; oc = next) { + next = oc->next; - checkAddress(addrs, ccs, s_indices); - checkAddress(addrs, ccs->cc, s_indices); - for (i = ccs->indexTable; i != NULL; i = i->next) { - if (!i->back_edge) { - searchCostCentres(addrs, i->ccs, s_indices); - } + removeOCSectionIndices(s_indices, oc); + + // Symbols should be removed by unloadObj_. + // NB (osa): If this assertion doesn't hold then freeObjectCode below + // will corrupt symhash as keys of that table live in ObjectCodes. If + // you see a segfault in a hash table operation in linker (in non-debug + // RTS) then it's probably becuse this assertion did not hold. + ASSERT(oc->symbols == NULL); + + freeObjectCode(oc); + n_unloaded_objects -= 1; } -} -#endif -// -// Check whether we can unload any object code. This is called at the -// appropriate point during a GC, where all the heap data is nice and -// packed together and we have a linked list of the static objects. -// -// The check involves a complete heap traversal, but you only pay for -// this (a) when you have called unloadObj(), and (b) at a major GC, -// which is much more expensive than the traversal we're doing here. -// -void checkUnload (StgClosure *static_objects) -{ - uint32_t g, n; - HashTable *addrs; - StgClosure* p; - const StgInfoTable *info; - ObjectCode *oc, *prev, *next; - gen_workspace *ws; - StgClosure* link; - - if (unloaded_objects == NULL) return; - - ACQUIRE_LOCK(&linker_unloaded_mutex); - - OCSectionIndices *s_indices = buildOCSectionIndices(unloaded_objects); - // Mark every unloadable object as unreferenced initially - for (oc = unloaded_objects; oc; oc = oc->next) { - IF_DEBUG(linker, debugBelch("Checking whether to unload %" PATH_FMT "\n", - oc->fileName)); - oc->referenced = false; - } - - addrs = allocHashTable(); - - for (p = static_objects; p != END_OF_STATIC_OBJECT_LIST; p = link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - info = get_itbl(p); - checkAddress(addrs, info, s_indices); - link = *STATIC_LINK(info, p); - } - - // CAFs on revertible_caf_list are not on static_objects - for (p = (StgClosure*)revertible_caf_list; - p != END_OF_CAF_LIST; - p = ((StgIndStatic *)p)->static_link) { - p = UNTAG_STATIC_LIST_PTR(p); - checkAddress(addrs, p, s_indices); - } - - for (g = 0; g < RtsFlags.GcFlags.generations; g++) { - searchHeapBlocks (addrs, generations[g].blocks, s_indices); - searchHeapBlocks (addrs, generations[g].large_objects, s_indices); - - for (n = 0; n < n_capabilities; n++) { - ws = &gc_threads[n]->gens[g]; - searchHeapBlocks(addrs, ws->todo_bd, s_indices); - searchHeapBlocks(addrs, ws->part_list, s_indices); - searchHeapBlocks(addrs, ws->scavd_list, s_indices); - } - } - -#if defined(PROFILING) - /* Traverse the cost centre tree, calling checkAddress on each CCS/CC */ - searchCostCentres(addrs, CCS_MAIN, s_indices); - - /* Also check each cost centre in the CC_LIST */ - CostCentre *cc; - for (cc = CC_LIST; cc != NULL; cc = cc->link) { - checkAddress(addrs, cc, s_indices); - } -#endif /* PROFILING */ - - freeOCSectionIndices(s_indices); - // Look through the unloadable objects, and any object that is still - // marked as unreferenced can be physically unloaded, because we - // have no references to it. - prev = NULL; - for (oc = unloaded_objects; oc; oc = next) { - next = oc->next; - if (oc->referenced == 0) { - if (prev == NULL) { - unloaded_objects = oc->next; - } else { - prev->next = oc->next; - } - IF_DEBUG(linker, debugBelch("Unloading object file %" PATH_FMT "\n", - oc->fileName)); - freeObjectCode(oc); - } else { - IF_DEBUG(linker, debugBelch("Object file still in use: %" - PATH_FMT "\n", oc->fileName)); - prev = oc; - } - } - - freeHashTable(addrs, NULL); - - RELEASE_LOCK(&linker_unloaded_mutex); + old_objects = NULL; } ===================================== rts/CheckUnload.h ===================================== @@ -12,6 +12,34 @@ #include "BeginPrivate.h" -void checkUnload (StgClosure *static_objects); +#include "LinkerInternals.h" + +// Currently live objects +extern ObjectCode *objects; + +// Root set for object collection +extern ObjectCode *loaded_objects; + +// Mark bit for live objects +extern uint8_t object_code_mark_bit; + +// Number of object code currently marked for unloading. See the definition in +// CheckUnload.c for details. +extern int n_unloaded_objects; + +void initUnloadCheck(void); +void exitUnloadCheck(void); + +// Call before major GC to prepare section index table for marking +bool prepareUnloadCheck(void); + +// Mark object code of a static closure address as 'live' +void markObjectCode(const void *addr); + +// Call after major GC to unload unused and unmarked object code +void checkUnload(void); + +// Call on loaded object code +void insertOCSectionIndices(ObjectCode *oc); #include "EndPrivate.h" ===================================== rts/Hash.c ===================================== @@ -400,6 +400,27 @@ mapHashTable(HashTable *table, void *data, MapHashFn fn) } } +void +iterHashTable(HashTable *table, void *data, IterHashFn fn) +{ + /* The last bucket with something in it is table->max + table->split - 1 */ + long segment = (table->max + table->split - 1) / HSEGSIZE; + long index = (table->max + table->split - 1) % HSEGSIZE; + + while (segment >= 0) { + while (index >= 0) { + for (HashList *hl = table->dir[segment][index]; hl != NULL; hl = hl->next) { + if (!fn(data, hl->key, hl->data)) { + return; + } + } + index--; + } + segment--; + index = HSEGSIZE - 1; + } +} + /* ----------------------------------------------------------------------------- * When we initialize a hash table, we set up the first segment as well, * initializing all of the first segment's hash buckets to NULL. @@ -444,12 +465,6 @@ allocStrHashTable(void) return allocHashTable_(hashStr, compareStr); } -void -exitHashTable(void) -{ - /* nothing to do */ -} - int keyCountHashTable (HashTable *table) { return table->kcount; ===================================== rts/Hash.h ===================================== @@ -33,8 +33,11 @@ int keyCountHashTable (HashTable *table); int keysHashTable(HashTable *table, StgWord keys[], int szKeys); typedef void (*MapHashFn)(void *data, StgWord key, const void *value); +// Return true -> continue; false -> stop +typedef bool (*IterHashFn)(void *data, StgWord key, const void *value); void mapHashTable(HashTable *table, void *data, MapHashFn fn); +void iterHashTable(HashTable *table, void *data, IterHashFn); /* Hash table access where the keys are C strings (the strings are * assumed to be allocated by the caller, and mustn't be deallocated @@ -62,6 +65,32 @@ int hashStr(const HashTable *table, StgWord key); */ void freeHashTable ( HashTable *table, void (*freeDataFun)(void *) ); -void exitHashTable ( void ); +INLINE_HEADER void freeStrHashTable ( HashTable *table, void (*freeDataFun)(void *) ) +{ + freeHashTable((HashTable*)table, freeDataFun); +} + +/* + * Hash set API + * + * A hash set is bascially a hash table where values are NULL. + */ + +typedef struct hashtable HashSet; + +INLINE_HEADER HashSet *allocHashSet ( void ) +{ + return (HashSet*)allocHashTable(); +} + +INLINE_HEADER void freeHashSet ( HashSet *set ) +{ + freeHashTable((HashTable*)set, NULL); +} + +INLINE_HEADER void insertHashSet ( HashSet *set, StgWord key ) +{ + insertHashTable((HashTable*)set, key, NULL); +} #include "EndPrivate.h" ===================================== rts/Linker.c ===================================== @@ -32,6 +32,7 @@ #include "linker/CacheFlush.h" #include "linker/SymbolExtras.h" #include "PathUtils.h" +#include "CheckUnload.h" // createOCSectionIndices #if !defined(mingw32_HOST_OS) #include "posix/Signals.h" @@ -161,23 +162,9 @@ */ /*Str*/HashTable *symhash; -/* List of currently loaded objects */ -ObjectCode *objects = NULL; /* initially empty */ - -/* List of objects that have been unloaded via unloadObj(), but are waiting - to be actually freed via checkUnload() */ -ObjectCode *unloaded_objects = NULL; /* initially empty */ - #if defined(THREADED_RTS) -/* This protects all the Linker's global state except unloaded_objects */ +/* This protects all the Linker's global state */ Mutex linker_mutex; -/* - * This protects unloaded_objects. We have a separate mutex for this, because - * the GC needs to access unloaded_objects in checkUnload, while the linker only - * needs to access unloaded_objects in unloadObj(), so this allows most linker - * operations proceed concurrently with the GC. - */ -Mutex linker_unloaded_mutex; #endif /* Generic wrapper function to try and Resolve and RunInit oc files */ @@ -447,12 +434,10 @@ initLinker_ (int retain_cafs) linker_init_done = 1; } - objects = NULL; - unloaded_objects = NULL; + initUnloadCheck(); #if defined(THREADED_RTS) initMutex(&linker_mutex); - initMutex(&linker_unloaded_mutex); #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) initMutex(&dl_mutex); #endif @@ -538,6 +523,7 @@ exitLinker( void ) { #endif if (linker_init_done == 1) { freeHashTable(symhash, free); + exitUnloadCheck(); } #if defined(THREADED_RTS) closeMutex(&linker_mutex); @@ -864,18 +850,24 @@ HsInt insertSymbol(pathchar* obj_name, SymbolName* key, SymbolAddr* data) } /* ----------------------------------------------------------------------------- - * lookup a symbol in the hash table + * Lookup a symbol in the hash table + * + * When 'dependent' is not NULL, adds it as a dependent to the owner of the + * symbol. */ #if defined(OBJFORMAT_PEi386) -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + (void)dependent; // TODO + ASSERT_LOCK_HELD(&linker_mutex); return lookupSymbol_PEi386(lbl); } #else -SymbolAddr* lookupSymbol_ (SymbolName* lbl) +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) { + ASSERT_LOCK_HELD(&linker_mutex); IF_DEBUG(linker, debugBelch("lookupSymbol: looking up '%s'\n", lbl)); ASSERT(symhash != NULL); @@ -900,10 +892,18 @@ SymbolAddr* lookupSymbol_ (SymbolName* lbl) return internal_dlsym(lbl + 1); # else - ASSERT(2+2 == 5); + ASSERT(false); return NULL; # endif } else { + if (dependent) { + // Add dependent as symbol's owner's dependency + ObjectCode *owner = pinfo->owner; + if (owner) { + // TODO: what does it mean for a symbol to not have an owner? + insertHashSet(dependent->dependencies, (W_)owner); + } + } return loadSymbol(lbl, pinfo); } } @@ -942,7 +942,7 @@ SymbolAddr* loadSymbol(SymbolName *lbl, RtsSymbolInfo *pinfo) { SymbolAddr* lookupSymbol( SymbolName* lbl ) { ACQUIRE_LOCK(&linker_mutex); - SymbolAddr* r = lookupSymbol_(lbl); + SymbolAddr* r = lookupDependentSymbol(lbl, NULL); if (!r) { errorBelch("^^ Could not load '%s', dependency unresolved. " "See top entry above.\n", lbl); @@ -1342,6 +1342,8 @@ void freeObjectCode (ObjectCode *oc) stgFree(oc->fileName); stgFree(oc->archiveMemberName); + freeHashSet(oc->dependencies); + stgFree(oc); } @@ -1403,6 +1405,10 @@ mkOc( pathchar *path, char *image, int imageSize, /* chain it onto the list of objects */ oc->next = NULL; + oc->prev = NULL; + oc->next_loaded_object = NULL; + oc->mark = object_code_mark_bit; + oc->dependencies = allocHashSet(); #if RTS_LINKER_USE_MMAP oc->rw_m32 = m32_allocator_new(false); @@ -1421,9 +1427,9 @@ mkOc( pathchar *path, char *image, int imageSize, HsInt isAlreadyLoaded( pathchar *path ) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path) + && o->status != OBJECT_UNLOADED) { return 1; /* already loaded */ } } @@ -1557,21 +1563,16 @@ preloadObjectFile (pathchar *path) */ static HsInt loadObj_ (pathchar *path) { - ObjectCode* oc; - IF_DEBUG(linker, debugBelch("loadObj: %" PATH_FMT "\n", path)); - - /* debugBelch("loadObj %s\n", path ); */ - - /* Check that we haven't already loaded this object. - Ignore requests to load multiple times */ + // Check that we haven't already loaded this object. + // Ignore requests to load multiple times if (isAlreadyLoaded(path)) { IF_DEBUG(linker, debugBelch("ignoring repeated load of %" PATH_FMT "\n", path)); - return 1; /* success */ + return 1; // success } - oc = preloadObjectFile(path); + ObjectCode *oc = preloadObjectFile(path); if (oc == NULL) return 0; if (! loadOc(oc)) { @@ -1582,8 +1583,10 @@ static HsInt loadObj_ (pathchar *path) return 0; } - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); + + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; return 1; } @@ -1778,15 +1781,14 @@ int ocTryLoad (ObjectCode* oc) { */ static HsInt resolveObjs_ (void) { - ObjectCode *oc; - int r; - IF_DEBUG(linker, debugBelch("resolveObjs: start\n")); - for (oc = objects; oc; oc = oc->next) { - r = ocTryLoad(oc); + for (ObjectCode *oc = objects; oc; oc = oc->next) { + int r = ocTryLoad(oc); if (!r) { + errorBelch("Could not load Object Code %" PATH_FMT ".\n", OC_INFORMATIVE_FILENAME(oc)); + fflush(stderr); return r; } } @@ -1813,45 +1815,35 @@ HsInt resolveObjs (void) */ static HsInt unloadObj_ (pathchar *path, bool just_purge) { - ObjectCode *oc, *prev, *next; - HsBool unloadedAnyObj = HS_BOOL_FALSE; - ASSERT(symhash != NULL); ASSERT(objects != NULL); IF_DEBUG(linker, debugBelch("unloadObj: %" PATH_FMT "\n", path)); - prev = NULL; - for (oc = objects; oc; oc = next) { - next = oc->next; // oc might be freed - - if (!pathcmp(oc->fileName,path)) { + bool unloadedAnyObj = false; + ObjectCode *prev = NULL; + // NOTE (osa): There may be more than one object with the same file name + // (happens when loading archive files) so we don't stop after unloading one + for (ObjectCode *oc = loaded_objects; oc; oc = oc->next_loaded_object) { + if (pathcmp(oc->fileName,path) == 0) { + oc->status = OBJECT_UNLOADED; - // these are both idempotent, so in just_purge mode we can - // later call unloadObj() to really unload the object. + // These are both idempotent, so in just_purge mode we can later + // call unloadObj() to really unload the object. removeOcSymbols(oc); freeOcStablePtrs(oc); + unloadedAnyObj = true; + if (!just_purge) { + n_unloaded_objects += 1; + // Remove object code from root set if (prev == NULL) { - objects = oc->next; + loaded_objects = oc->next_loaded_object; } else { - prev->next = oc->next; + prev->next_loaded_object = oc->next_loaded_object; } - ACQUIRE_LOCK(&linker_unloaded_mutex); - oc->next = unloaded_objects; - unloaded_objects = oc; - oc->status = OBJECT_UNLOADED; - RELEASE_LOCK(&linker_unloaded_mutex); - // We do not own oc any more; it can be released at any time by - // the GC in checkUnload(). - } else { - prev = oc; } - - /* This could be a member of an archive so continue - * unloading other members. */ - unloadedAnyObj = HS_BOOL_TRUE; } else { prev = oc; } @@ -1859,8 +1851,7 @@ static HsInt unloadObj_ (pathchar *path, bool just_purge) if (unloadedAnyObj) { return 1; - } - else { + } else { errorBelch("unloadObj: can't find `%" PATH_FMT "' to unload", path); return 0; } @@ -1884,13 +1875,7 @@ HsInt purgeObj (pathchar *path) static OStatus getObjectLoadStatus_ (pathchar *path) { - ObjectCode *o; - for (o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } - } - for (o = unloaded_objects; o; o = o->next) { + for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { return o->status; } ===================================== rts/LinkerInternals.h ===================================== @@ -191,9 +191,6 @@ typedef struct _ObjectCode { /* non-zero if the object file was mmap'd, otherwise malloc'd */ int imageMapped; - /* flag used when deciding whether to unload an object file */ - int referenced; - /* record by how much image has been deliberately misaligned after allocation, so that we can use realloc */ int misalignment; @@ -205,8 +202,37 @@ typedef struct _ObjectCode { int n_segments; Segment *segments; - /* Allow a chain of these things */ - struct _ObjectCode * next; + // + // Garbage collection fields + // + + // Next object in `objects` list + struct _ObjectCode *next; + + // Previous object in `objects` list + struct _ObjectCode *prev; + + // Next object in `loaded_objects` list + struct _ObjectCode *next_loaded_object; + + // Mark bit + uint8_t mark; + + // Set of dependencies (ObjectCode*) of the object file. Traverse + // dependencies using `iterHashTable`. + // + // New entries are added as we resolve symbols in an object file, in + // `lookupDependentSymbol`. When an object file uses multiple symbols from + // another object file we add the dependent multiple times, so we use a + // `HashTable` here rather than a list/array to avoid copies. + // + // Used when unloading object files. See Note [Object unloading] in + // CheckUnload.c. + HashSet *dependencies; + + // + // End of garbage collection fields + // /* SANITY CHECK ONLY: a list of the only memory regions which may safely be prodded during relocation. Any attempt to prod @@ -250,12 +276,8 @@ typedef struct _ObjectCode { (OC)->fileName \ ) -extern ObjectCode *objects; -extern ObjectCode *unloaded_objects; - #if defined(THREADED_RTS) extern Mutex linker_mutex; -extern Mutex linker_unloaded_mutex; #endif /* Type of the initializer */ @@ -306,8 +328,9 @@ int ghciInsertSymbolTable( HsBool weak, ObjectCode *owner); -/* lock-free version of lookupSymbol */ -SymbolAddr* lookupSymbol_ (SymbolName* lbl); +/* Lock-free version of lookupSymbol. When 'dependent' is not NULL, adds it as a + * dependent to the owner of the symbol. */ +SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent); extern /*Str*/HashTable *symhash; ===================================== rts/PrimOps.cmm ===================================== @@ -1816,9 +1816,16 @@ loop: // There are readMVar/takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1843,10 +1850,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); @@ -1901,9 +1906,16 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1928,10 +1940,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/RtsStartup.c ===================================== @@ -512,9 +512,6 @@ hs_exit_(bool wait_foreign) shutdownAsyncIO(wait_foreign); #endif - /* free hash table storage */ - exitHashTable(); - // Finally, free all our storage. However, we only free the heap // memory if we have waited for foreign calls to complete; // otherwise a foreign call in progress may still be referencing ===================================== rts/Threads.c ===================================== @@ -790,9 +790,14 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = q->tso; - mvar->head = q->link; - if (mvar->head == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { + mvar->head = q = q->link; + if (q == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { mvar->tail = (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure; + } else { + if (info == &stg_MVAR_CLEAN_info) { + // Resolve #18919. + dirty_MVAR(&cap->r, (StgClosure*)mvar, mvar->value); + } } ASSERT(tso->block_info.closure == (StgClosure*)mvar); @@ -816,10 +821,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = ((StgMVarTSOQueue*)q)->link; + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/linker/Elf.c ===================================== @@ -1104,7 +1104,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) { S = (Elf_Addr)symbol->addr; } else { - S_tmp = lookupSymbol_( symbol->name ); + S_tmp = lookupDependentSymbol( symbol->name, oc ); S = (Elf_Addr)S_tmp; } if (!S) { @@ -1524,7 +1524,7 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, } else { /* No, so look up the name in our global table. */ symbol = strtab + sym.st_name; - S_tmp = lookupSymbol_( symbol ); + S_tmp = lookupDependentSymbol( symbol, oc ); S = (Elf_Addr)S_tmp; } if (!S) { ===================================== rts/linker/LoadArchive.c ===================================== @@ -5,6 +5,7 @@ #include "sm/OSMem.h" #include "RtsUtils.h" #include "LinkerInternals.h" +#include "CheckUnload.h" // loaded_objects, insertOCSectionIndices #include "linker/M32Alloc.h" /* Platform specific headers */ @@ -241,7 +242,6 @@ lookupGNUArchiveIndex(int gnuFileIndexSize, char **fileName_, static HsInt loadArchive_ (pathchar *path) { - ObjectCode* oc = NULL; char *image = NULL; HsInt retcode = 0; int memberSize; @@ -520,8 +520,8 @@ static HsInt loadArchive_ (pathchar *path) sprintf(archiveMemberName, "%" PATH_FMT "(%.*s)", path, (int)thisFileNameSize, fileName); - oc = mkOc(path, image, memberSize, false, archiveMemberName - , misalignment); + ObjectCode *oc = mkOc(path, image, memberSize, false, archiveMemberName, + misalignment); #if defined(OBJFORMAT_MACHO) ocInit_MachO( oc ); #endif @@ -536,8 +536,9 @@ static HsInt loadArchive_ (pathchar *path) fclose(f); return 0; } else { - oc->next = objects; - objects = oc; + insertOCSectionIndices(oc); // also adds the object to `objects` list + oc->next_loaded_object = loaded_objects; + loaded_objects = oc; } } else if (isGnuIndex) { ===================================== rts/linker/MachO.c ===================================== @@ -242,7 +242,7 @@ resolveImports( addr = (SymbolAddr*) (symbol->nlist->n_value); IF_DEBUG(linker, debugBelch("resolveImports: undefined external %s has value %p\n", symbol->name, addr)); } else { - addr = lookupSymbol_(symbol->name); + addr = lookupDependentSymbol(symbol->name, oc); IF_DEBUG(linker, debugBelch("resolveImports: looking up %s, %p\n", symbol->name, addr)); } @@ -564,12 +564,12 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { /* external symbols should be able to be - * looked up via the lookupSymbol_ function. + * looked up via the lookupDependentSymbol function. * Either through the global symbol hashmap * or asking the system, if not found * in the symbol hashmap */ - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -609,7 +609,7 @@ relocateSectionAarch64(ObjectCode * oc, Section * section) uint64_t pc = (uint64_t)section->start + ri->r_address; uint64_t value = 0; if(symbol->nlist->n_type & N_EXT) { - value = (uint64_t)lookupSymbol_((char*)symbol->name); + value = (uint64_t)lookupDependentSymbol((char*)symbol->name, oc); if(!value) barf("Could not lookup symbol: %s!", symbol->name); } else { @@ -784,7 +784,7 @@ relocateSection(ObjectCode* oc, int curSection) // symtab, or it is undefined, meaning dlsym must be used // to resolve it. - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); IF_DEBUG(linker, debugBelch("relocateSection: looked up %s, " "external X86_64_RELOC_GOT or X86_64_RELOC_GOT_LOAD\n" " : addr = %p\n", nm, addr)); @@ -845,7 +845,7 @@ relocateSection(ObjectCode* oc, int curSection) nm, (void *)value)); } else { - addr = lookupSymbol_(nm); + addr = lookupDependentSymbol(nm, oc); if (addr == NULL) { errorBelch("\nlookupSymbol failed in relocateSection (relocate external)\n" @@ -1345,7 +1345,7 @@ ocGetNames_MachO(ObjectCode* oc) if (oc->info->nlist[i].n_type & N_EXT) { if ( (oc->info->nlist[i].n_desc & N_WEAK_DEF) - && lookupSymbol_(nm)) { + && lookupDependentSymbol(nm, oc)) { // weak definition, and we already have a definition IF_DEBUG(linker, debugBelch(" weak: %s\n", nm)); } @@ -1497,7 +1497,7 @@ ocResolve_MachO(ObjectCode* oc) * have the address. */ if(NULL == symbol->addr) { - symbol->addr = lookupSymbol_((char*)symbol->name); + symbol->addr = lookupDependentSymbol((char*)symbol->name, oc); if(NULL == symbol->addr) barf("Failed to lookup symbol: %s", symbol->name); } else { ===================================== rts/linker/PEi386.c ===================================== @@ -185,6 +185,7 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" #include "GetEnv.h" +#include "CheckUnload.h" #include "linker/PEi386.h" #include "linker/PEi386Types.h" #include "linker/SymbolExtras.h" @@ -1894,7 +1895,7 @@ ocResolve_PEi386 ( ObjectCode* oc ) } else { copyName ( getSymShortName (info, sym), oc, symbol, sizeof(symbol)-1 ); - S = (size_t) lookupSymbol_( (char*)symbol ); + S = (size_t) lookupDependentSymbol( (char*)symbol, oc ); if ((void*)S == NULL) { errorBelch(" | %" PATH_FMT ": unknown symbol `%s'", oc->fileName, symbol); releaseOcInfo (oc); ===================================== rts/linker/elf_got.c ===================================== @@ -88,7 +88,7 @@ fillGot(ObjectCode * oc) { if( STT_NOTYPE == ELF_ST_TYPE(symbol->elf_sym->st_info) || STB_WEAK == ELF_ST_BIND(symbol->elf_sym->st_info)) { if(0x0 == symbol->addr) { - symbol->addr = lookupSymbol_(symbol->name); + symbol->addr = lookupDependentSymbol(symbol->name, oc); if(0x0 == symbol->addr) { if(0 == strncmp(symbol->name,"_GLOBAL_OFFSET_TABLE_",21)) { symbol->addr = oc->info->got_start; ===================================== rts/sm/Evac.c ===================================== @@ -28,6 +28,7 @@ #include "CNF.h" #include "Scav.h" #include "NonMoving.h" +#include "CheckUnload.h" // n_unloaded_objects and markObjectCode #if defined(THREADED_RTS) && !defined(PARALLEL_GC) #define evacuate(p) evacuate1(p) @@ -593,6 +594,11 @@ loop: if (!HEAP_ALLOCED_GC(q)) { if (!major_gc) return; + // Note [Object unloading] in CheckUnload.c + if (RTS_UNLIKELY(unload_mark_needed)) { + markObjectCode(q); + } + info = get_itbl(q); switch (info->type) { ===================================== rts/sm/GC.c ===================================== @@ -97,6 +97,13 @@ * See also: Note [STATIC_LINK fields] in Storage.h. */ +/* Hot GC globals + * ~~~~~~~~~~~~~~ + * The globals below are quite hot during GC but read-only, initialized during + * the beginning of collection. It is important that they reside in the same + * cache-line to minimize unnecessary cache misses. + */ + /* N is the oldest generation being collected, where the generations * are numbered starting at 0. A major GC (indicated by the major_gc * flag) is when we're collecting all generations. We only attempt to @@ -105,6 +112,7 @@ uint32_t N; bool major_gc; bool deadlock_detect_gc; +bool unload_mark_needed; /* Data used for allocation area sizing. */ @@ -297,6 +305,12 @@ GarbageCollect (uint32_t collect_gen, static_flag == STATIC_FLAG_A ? STATIC_FLAG_B : STATIC_FLAG_A; } + if (major_gc) { + unload_mark_needed = prepareUnloadCheck(); + } else { + unload_mark_needed = false; + } + #if defined(THREADED_RTS) work_stealing = RtsFlags.ParFlags.parGcLoadBalancingEnabled && N >= RtsFlags.ParFlags.parGcLoadBalancingGen; @@ -810,9 +824,12 @@ GarbageCollect (uint32_t collect_gen, resetNurseries(); - // mark the garbage collected CAFs as dead #if defined(DEBUG) - if (major_gc && !RtsFlags.GcFlags.useNonmoving) { gcCAFs(); } + // Mark the garbage collected CAFs as dead. Done in `nonmovingGcCafs()` when + // non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + gcCAFs(); + } #endif // Update the stable name hash table @@ -823,9 +840,14 @@ GarbageCollect (uint32_t collect_gen, // hs_free_stable_ptr(), both of which access the StablePtr table. stablePtrUnlock(); - // Must be after stablePtrUnlock(), because it might free stable ptrs. - if (major_gc) { - checkUnload (gct->scavenged_static_objects); + // Unload dynamically-loaded object code after a major GC. + // See Note [Object unloading] in CheckUnload.c for details. + // + // TODO: Similar to `nonmovingGcCafs` non-moving GC should have its own + // collector for these objects, but that's currently not implemented, so we + // simply don't unload object code when non-moving GC is enabled. + if (major_gc && !RtsFlags.GcFlags.useNonmoving) { + checkUnload(); } #if defined(PROFILING) ===================================== rts/sm/GC.h ===================================== @@ -35,6 +35,7 @@ extern uint32_t N; extern bool major_gc; /* See Note [Deadlock detection under nonmoving collector]. */ extern bool deadlock_detect_gc; +extern bool unload_mark_needed; extern bdescr *mark_stack_bd; extern bdescr *mark_stack_top_bd; ===================================== testsuite/tests/ghci/T16525a/T16525a.script ===================================== @@ -1,6 +1,10 @@ :set -fobject-code :load A import Control.Concurrent -_ <- forkIO $ threadDelay 1000000 >> (print (map v1 value)) +_ <- forkIO $ threadDelay 500000 >> print (map v1 value) :l [] System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC ===================================== testsuite/tests/ghci/T16525a/T16525a.stdout ===================================== @@ -0,0 +1 @@ +["a;lskdfa;lszkfsd;alkfjas"] ===================================== testsuite/tests/ghci/T16525a/all.T ===================================== @@ -1,6 +1,3 @@ test('T16525a', - [extra_files(['A.hs', 'B.hs', ]), - when(compiler_debugged(), extra_run_opts('+RTS -DS -RTS')), - # We don't support unloading with the dynamic linker - when(ghc_dynamic(), skip), ], + [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525a.script']) ===================================== testsuite/tests/ghci/T16525b/A.hs ===================================== @@ -0,0 +1,6 @@ +module A (a) where + +import B + +a :: () -> IO Int +a x = b x ===================================== testsuite/tests/ghci/T16525b/B.hs ===================================== @@ -0,0 +1,5 @@ +module B (b) where + +{-# NOINLINE b #-} +b :: () -> IO Int +b () = return 999999999 ===================================== testsuite/tests/ghci/T16525b/T16525b.script ===================================== @@ -0,0 +1,22 @@ +:set -fobject-code +:load A +import Control.Concurrent +import Control.Monad +:{ +_ <- forkIO $ do + replicateM_ 3 (a () >>= print >> threadDelay 500000) + putStrLn "===== THREAD DONE =====" +:} +:l [] +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 +System.Mem.performGC +threadDelay 500000 ===================================== testsuite/tests/ghci/T16525b/T16525b.stdout ===================================== @@ -0,0 +1,4 @@ +999999999 +999999999 +999999999 +===== THREAD DONE ===== ===================================== testsuite/tests/ghci/T16525b/all.T ===================================== @@ -0,0 +1,2 @@ +# Tests unloading an object file which is in use in a thread +test('T16525b', [extra_files(['A.hs', 'B.hs'])], ghci_script, ['T16525b.script']) ===================================== testsuite/tests/rts/linker/linker_error.c ===================================== @@ -57,7 +57,10 @@ int main (int argc, char *argv[]) r = resolveObjs(); if (!r) { debugBelch("resolveObjs failed\n"); + // Mark the object as unloadable: unloadObj(obj); + // Actually unload it: + performMajorGC(); continue; } errorBelch("loading succeeded"); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70ac4ed84f4e95f3b3772242368582cf911e50c4...2d72607e7b6346ad3e0a7fe39e86ceb8f85e557b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70ac4ed84f4e95f3b3772242368582cf911e50c4...2d72607e7b6346ad3e0a7fe39e86ceb8f85e557b 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 Mon Nov 30 15:13:01 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 10:13:01 -0500 Subject: [Git][ghc/ghc][wip/no-fptr] 8 commits: base: Introduce GHC.ForeignPtr.Ops module Message-ID: <5fc50bfdbcd12_86c113040b097884c@gitlab.mail> Ben Gamari pushed to branch wip/no-fptr at Glasgow Haskell Compiler / GHC Commits: a32c5a10 by Ben Gamari at 2020-11-30T10:12:52-05:00 base: Introduce GHC.ForeignPtr.Ops module This contains a variety of peek/poke operations for ForeignPtr accesses. - - - - - 38766e93 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.IO.Buffer: Use ForeignPtr-specialised peek/poke - - - - - 24cd42a2 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.Data.ByteArray: Initial commit - - - - - 39cd7b51 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - 4c30f373 by Ben Gamari at 2020-11-30T10:12:52-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 46b45be9 by Ben Gamari at 2020-11-30T10:12:52-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - 29d2bb26 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - 10db1230 by Ben Gamari at 2020-11-30T10:12:52-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - 7 changed files: - + compiler/GHC/Data/ByteArray.hs - compiler/GHC/Utils/Binary.hs - libraries/base/GHC/Event/Array.hs - + libraries/base/GHC/ForeignPtr/Ops.hs - libraries/base/GHC/IO/Buffer.hs - libraries/base/base.cabal - libraries/bytestring Changes: ===================================== compiler/GHC/Data/ByteArray.hs ===================================== @@ -0,0 +1,280 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE MagicHash #-} + +module GHC.Data.ByteArray + ( -- * Immutable byte arrays + ByteArray + , getByteArray + , unsafeByteArrayContents + , withByteArrayContents + , sizeofByteArray + + -- * Mutable byte arrays + , MutableByteArray + , getMutableByteArray + , unsafeMutableByteArrayContents + , newMutableByteArray + , newPinnedMutableByteArray + , copyByteArray + , copyAddrToMutableByteArray + , unsafeFreezeByteArray + + -- * Writing + , writeWordArray + , writeWord8Array + , writeWord16Array + , writeWord32Array + , writeWord64Array + , writeIntArray + , writeInt8Array + , writeInt16Array + , writeInt32Array + , writeInt64Array + , writeCharArray + + -- * Reading + , readWordArray + , readWord8Array + , readWord16Array + , readWord32Array + , readWord64Array + , readIntArray + , readInt8Array + , readInt16Array + , readInt32Array + , readInt64Array + , readCharArray + + -- * Immutable indexing + , indexWordArray + , indexWord8Array + , indexWord16Array + , indexWord32Array + , indexWord64Array + , indexIntArray + , indexInt8Array + , indexInt16Array + , indexInt32Array + , indexInt64Array + , indexCharArray + ) where + +import GHC.Base +import GHC.Exts +import GHC.Word +import GHC.Int +import Unsafe.Coerce + +data MutableByteArray = MutableByteArray { getMutableByteArray :: !(MutableByteArray# RealWorld) } + +data ByteArray = ByteArray { getByteArray :: !ByteArray# } + +unsafeByteArrayContents :: ByteArray -> Ptr a +unsafeByteArrayContents (ByteArray ba) = Ptr (byteArrayContents# ba) + +unsafeMutableByteArrayContents :: MutableByteArray -> Ptr a +unsafeMutableByteArrayContents = unsafeByteArrayContents . unsafeCoerce + +withByteArrayContents :: ByteArray -> (Ptr a -> IO b) -> IO b +withByteArrayContents (ByteArray ba) f = do + r <- f $ Ptr (byteArrayContents# ba) + IO $ \s -> case touch# ba s of s' -> (# s', () #) + return r + +newMutableByteArray :: Int -> IO MutableByteArray +newMutableByteArray (I# size) = IO $ \s -> + case newByteArray# size s of + (# s', mba #) -> (# s', MutableByteArray mba #) + +newPinnedMutableByteArray :: Int -> IO MutableByteArray +newPinnedMutableByteArray (I# size) = IO $ \s -> + case newPinnedByteArray# size s of + (# s', mba #) -> (# s', MutableByteArray mba #) + +copyByteArray + :: ByteArray -- ^ source + -> Int -- ^ source offset + -> MutableByteArray -- ^ destination + -> Int -- ^ destination offset + -> Int -- ^ length to copy + -> IO () +copyByteArray (ByteArray src) (I# src_ofs) (MutableByteArray dst) (I# dst_ofs) (I# len) = + IO $ \s -> + case copyByteArray# src src_ofs dst dst_ofs len s of + s' -> (# s', () #) + +copyAddrToMutableByteArray :: Ptr a -> MutableByteArray -> Int -> Int -> IO () +copyAddrToMutableByteArray (Ptr src) (MutableByteArray dst) (I# dst_ofs) (I# len) = IO $ \s -> + case copyAddrToByteArray# src dst dst_ofs len s of + s' -> (# s', () #) + +unsafeFreezeByteArray + :: MutableByteArray + -> IO ByteArray +unsafeFreezeByteArray (MutableByteArray mba) = IO $ \s -> + case unsafeFreezeByteArray# mba s of + (# s', ba #) -> (# s', ByteArray ba #) + +sizeofByteArray :: ByteArray -> Int +sizeofByteArray (ByteArray arr) = I# (sizeofByteArray# arr) + + +readWordArray :: MutableByteArray -> Int -> IO Word +readWordArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWordArray# arr ix s0 of + (# s1, r #) -> (# s1, W# r #) + +readWord8Array :: MutableByteArray -> Int -> IO Word8 +readWord8Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord8Array# arr ix s0 of + (# s1, r #) -> (# s1, W8# r #) + +readWord16Array :: MutableByteArray -> Int -> IO Word16 +readWord16Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord16Array# arr ix s0 of + (# s1, r #) -> (# s1, W16# r #) + +readWord32Array :: MutableByteArray -> Int -> IO Word32 +readWord32Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord32Array# arr ix s0 of + (# s1, r #) -> (# s1, W32# r #) + +readWord64Array :: MutableByteArray -> Int -> IO Word64 +readWord64Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readWord64Array# arr ix s0 of + (# s1, r #) -> (# s1, W64# r #) + +readIntArray :: MutableByteArray -> Int -> IO Int +readIntArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readIntArray# arr ix s0 of + (# s1, r #) -> (# s1, I# r #) + +readInt8Array :: MutableByteArray -> Int -> IO Int8 +readInt8Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt8Array# arr ix s0 of + (# s1, r #) -> (# s1, I8# r #) + +readInt16Array :: MutableByteArray -> Int -> IO Int16 +readInt16Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt16Array# arr ix s0 of + (# s1, r #) -> (# s1, I16# r #) + +readInt32Array :: MutableByteArray -> Int -> IO Int32 +readInt32Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt32Array# arr ix s0 of + (# s1, r #) -> (# s1, I32# r #) + +readInt64Array :: MutableByteArray -> Int -> IO Int64 +readInt64Array (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readInt64Array# arr ix s0 of + (# s1, r #) -> (# s1, I64# r #) + +readCharArray :: MutableByteArray -> Int -> IO Char +readCharArray (MutableByteArray arr) (I# ix) = IO $ \s0 -> + case readCharArray# arr ix s0 of + (# s1, r #) -> (# s1, C# r #) + + + +writeWordArray :: MutableByteArray -> Int -> Word -> IO () +writeWordArray (MutableByteArray arr) (I# ix) (W# x) = IO $ \s0 -> + case writeWordArray# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord8Array :: MutableByteArray -> Int -> Word8 -> IO () +writeWord8Array (MutableByteArray arr) (I# ix) (W8# x) = IO $ \s0 -> + case writeWord8Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord16Array :: MutableByteArray -> Int -> Word16 -> IO () +writeWord16Array (MutableByteArray arr) (I# ix) (W16# x) = IO $ \s0 -> + case writeWord16Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord32Array :: MutableByteArray -> Int -> Word32 -> IO () +writeWord32Array (MutableByteArray arr) (I# ix) (W32# x) = IO $ \s0 -> + case writeWord32Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeWord64Array :: MutableByteArray -> Int -> Word64 -> IO () +writeWord64Array (MutableByteArray arr) (I# ix) (W64# x) = IO $ \s0 -> + case writeWord64Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeIntArray :: MutableByteArray -> Int -> Int -> IO () +writeIntArray (MutableByteArray arr) (I# ix) (I# x) = IO $ \s0 -> + case writeIntArray# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt8Array :: MutableByteArray -> Int -> Int8 -> IO () +writeInt8Array (MutableByteArray arr) (I# ix) (I8# x) = IO $ \s0 -> + case writeInt8Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt16Array :: MutableByteArray -> Int -> Int16 -> IO () +writeInt16Array (MutableByteArray arr) (I# ix) (I16# x) = IO $ \s0 -> + case writeInt16Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt32Array :: MutableByteArray -> Int -> Int32 -> IO () +writeInt32Array (MutableByteArray arr) (I# ix) (I32# x) = IO $ \s0 -> + case writeInt32Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeInt64Array :: MutableByteArray -> Int -> Int64 -> IO () +writeInt64Array (MutableByteArray arr) (I# ix) (I64# x) = IO $ \s0 -> + case writeInt64Array# arr ix x s0 of + s1 -> (# s1, () #) + +writeCharArray :: MutableByteArray -> Int -> Char -> IO () +writeCharArray (MutableByteArray arr) (I# ix) (C# x) = IO $ \s0 -> + case writeCharArray# arr ix x s0 of + s1 -> (# s1, () #) + + + +indexWordArray :: ByteArray -> Int -> Word +indexWordArray (ByteArray arr) (I# ix) = + W# (indexWordArray# arr ix) + +indexWord8Array :: ByteArray -> Int -> Word8 +indexWord8Array (ByteArray arr) (I# ix) = + W8# (indexWord8Array# arr ix) + +indexWord16Array :: ByteArray -> Int -> Word16 +indexWord16Array (ByteArray arr) (I# ix) = + W16# (indexWord16Array# arr ix) + +indexWord32Array :: ByteArray -> Int -> Word32 +indexWord32Array (ByteArray arr) (I# ix) = + W32# (indexWord32Array# arr ix) + +indexWord64Array :: ByteArray -> Int -> Word64 +indexWord64Array (ByteArray arr) (I# ix) = + W64# (indexWord64Array# arr ix) + +indexIntArray :: ByteArray -> Int -> Int +indexIntArray (ByteArray arr) (I# ix) = + I# (indexIntArray# arr ix) + +indexInt8Array :: ByteArray -> Int -> Int8 +indexInt8Array (ByteArray arr) (I# ix) = + I8# (indexInt8Array# arr ix) + +indexInt16Array :: ByteArray -> Int -> Int16 +indexInt16Array (ByteArray arr) (I# ix) = + I16# (indexInt16Array# arr ix) + +indexInt32Array :: ByteArray -> Int -> Int32 +indexInt32Array (ByteArray arr) (I# ix) = + I32# (indexInt32Array# arr ix) + +indexInt64Array :: ByteArray -> Int -> Int64 +indexInt64Array (ByteArray arr) (I# ix) = + I64# (indexInt64Array# arr ix) + +indexCharArray :: ByteArray -> Int -> Char +indexCharArray (ByteArray arr) (I# ix) = + C# (indexCharArray# arr ix) + ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE BangPatterns #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -O2 -funbox-strict-fields #-} -- We always optimise this, otherwise performance of a non-optimised @@ -84,6 +85,7 @@ import Data.Array import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS +import GHC.ForeignPtr import Data.IORef import Data.Char ( ord, chr ) import Data.Time @@ -96,7 +98,10 @@ import GHC.Real ( Ratio(..) ) type BinArray = ForeignPtr Word8 - +#if !MIN_VERSION_base(4,15,0) +unsafeWithForeignPtr :: ForeignPtr a -> (Ptr a -> IO b) -> IO b +unsafeWithForeignPtr = withForeignPtr +#endif --------------------------------------------------------------- -- BinData @@ -111,14 +116,14 @@ instance Binary BinData where put_ bh (BinData sz dat) = do put_ bh sz putPrim bh sz $ \dest -> - withForeignPtr dat $ \orig -> + unsafeWithForeignPtr dat $ \orig -> copyBytes dest orig sz -- get bh = do sz <- get bh dat <- mallocForeignPtrBytes sz getPrim bh sz $ \orig -> - withForeignPtr dat $ \dest -> + unsafeWithForeignPtr dat $ \dest -> copyBytes dest orig sz return (BinData sz dat) @@ -226,7 +231,7 @@ writeBinMem (BinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode arr <- readIORef arr_r ix <- readFastMutInt ix_r - withForeignPtr arr $ \p -> hPutBuf h p ix + unsafeWithForeignPtr arr $ \p -> hPutBuf h p ix hClose h readBinMem :: FilePath -> IO BinHandle @@ -236,7 +241,7 @@ readBinMem filename = do filesize' <- hFileSize h let filesize = fromIntegral filesize' arr <- mallocForeignPtrBytes filesize - count <- withForeignPtr arr $ \p -> hGetBuf h p filesize + count <- unsafeWithForeignPtr arr $ \p -> hGetBuf h p filesize when (count /= filesize) $ error ("Binary.readBinMem: only read " ++ show count ++ " bytes") hClose h @@ -280,7 +285,7 @@ putPrim h@(BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ expandBin h (ix + size) arr <- readIORef arr_r - withForeignPtr arr $ \op -> f (op `plusPtr` ix) + unsafeWithForeignPtr arr $ \op -> f (op `plusPtr` ix) writeFastMutInt ix_r (ix + size) -- -- | Similar to putPrim but advances the index by the actual number of @@ -302,7 +307,10 @@ getPrim (BinMem _ ix_r sz_r arr_r) size f = do when (ix + size > sz) $ ioError (mkIOError eofErrorType "Data.Binary.getPrim" Nothing Nothing) arr <- readIORef arr_r - w <- withForeignPtr arr $ \op -> f (op `plusPtr` ix) + w <- f (unsafeForeignPtrToPtr arr `plusPtr` ix) + touchForeignPtr arr + -- This is safe WRT #17760 as we we guarantee that the above line doesn't + -- diverge writeFastMutInt ix_r (ix + size) return w ===================================== libraries/base/GHC/Event/Array.hs ===================================== @@ -33,7 +33,7 @@ import Foreign.ForeignPtr (ForeignPtr, withForeignPtr) import Foreign.Ptr (Ptr, nullPtr, plusPtr) import Foreign.Storable (Storable(..)) import GHC.Base hiding (empty) -import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_) +import GHC.ForeignPtr (mallocPlainForeignPtrBytes, newForeignPtr_, unsafeWithForeignPtr) import GHC.Num (Num(..)) import GHC.Real (fromIntegral) import GHC.Show (show) @@ -78,9 +78,9 @@ reallocArray p newSize oldSize = reallocHack undefined p reallocHack dummy src = do let size = sizeOf dummy dst <- mallocPlainForeignPtrBytes (newSize * size) - withForeignPtr src $ \s -> + unsafeWithForeignPtr src $ \s -> when (s /= nullPtr && oldSize > 0) . - withForeignPtr dst $ \d -> do + unsafeWithForeignPtr dst $ \d -> do _ <- memcpy d s (fromIntegral (oldSize * size)) return () return dst @@ -99,8 +99,8 @@ duplicate a = dupHack undefined a dupHack dummy (Array ref) = do AC es len cap <- readIORef ref ary <- allocArray cap - withForeignPtr ary $ \dest -> - withForeignPtr es $ \src -> do + unsafeWithForeignPtr ary $ \dest -> + unsafeWithForeignPtr es $ \src -> do _ <- memcpy dest src (fromIntegral (len * sizeOf dummy)) return () Array `fmap` newIORef (AC ary len cap) @@ -119,8 +119,8 @@ unsafeRead :: Storable a => Array a -> Int -> IO a unsafeRead (Array ref) ix = do AC es _ cap <- readIORef ref CHECK_BOUNDS("unsafeRead",cap,ix) - withForeignPtr es $ \p -> - peekElemOff p ix + unsafeWithForeignPtr es $ \ptr -> peekElemOff ptr ix + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge unsafeWrite :: Storable a => Array a -> Int -> a -> IO () unsafeWrite (Array ref) ix a = do @@ -130,13 +130,15 @@ unsafeWrite (Array ref) ix a = do unsafeWrite' :: Storable a => AC a -> Int -> a -> IO () unsafeWrite' (AC es _ cap) ix a = CHECK_BOUNDS("unsafeWrite'",cap,ix) - withForeignPtr es $ \p -> - pokeElemOff p ix a + unsafeWithForeignPtr es $ \ptr -> pokeElemOff ptr ix a + -- this is safe WRT #17760 as we assume that peekElemOff doesn't diverge +-- | Precondition: continuation must not diverge due to use of +-- 'unsafeWithForeignPtr'. unsafeLoad :: Array a -> (Ptr a -> Int -> IO Int) -> IO Int unsafeLoad (Array ref) load = do AC es _ cap <- readIORef ref - len' <- withForeignPtr es $ \p -> load p cap + len' <- unsafeWithForeignPtr es $ \p -> load p cap writeIORef ref (AC es len' cap) return len' @@ -146,7 +148,7 @@ unsafeCopyFromBuffer :: Storable a => Array a -> Ptr a -> Int -> IO () unsafeCopyFromBuffer (Array ref) sptr n = readIORef ref >>= \(AC es _ cap) -> CHECK_BOUNDS("unsafeCopyFromBuffer", cap, n) - withForeignPtr es $ \pdest -> do + unsafeWithForeignPtr es $ \pdest -> do let size = sizeOfPtr sptr undefined _ <- memcpy pdest sptr (fromIntegral $ n * size) writeIORef ref (AC es n cap) @@ -198,7 +200,7 @@ forM_ ary g = forHack ary g undefined AC es len _ <- readIORef ref let size = sizeOf dummy offset = len * size - withForeignPtr es $ \p -> do + unsafeWithForeignPtr es $ \p -> do let go n | n >= offset = return () | otherwise = do f =<< peek (p `plusPtr` n) @@ -269,8 +271,8 @@ copy' d dstart s sstart maxCount = copyHack d s undefined then return dac else do AC dst dlen dcap <- ensureCapacity' dac (dstart + count) - withForeignPtr dst $ \dptr -> - withForeignPtr src $ \sptr -> do + unsafeWithForeignPtr dst $ \dptr -> + unsafeWithForeignPtr src $ \sptr -> do _ <- memcpy (dptr `plusPtr` (dstart * size)) (sptr `plusPtr` (sstart * size)) (fromIntegral (count * size)) @@ -286,7 +288,7 @@ removeAt a i = removeHack a undefined let size = sizeOf dummy newLen = oldLen - 1 when (newLen > 0 && i < newLen) . - withForeignPtr fp $ \ptr -> do + unsafeWithForeignPtr fp $ \ptr -> do _ <- memmove (ptr `plusPtr` (size * i)) (ptr `plusPtr` (size * (i+1))) (fromIntegral (size * (newLen-i))) ===================================== libraries/base/GHC/ForeignPtr/Ops.hs ===================================== @@ -0,0 +1,171 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE Unsafe #-} + +{-# OPTIONS_HADDOCK not-home #-} + +----------------------------------------------------------------------------- +-- | +-- Module : GHC.ForeignPtr.Ops +-- Copyright : (c) The University of Glasgow, 1992-2003 +-- License : see libraries/base/LICENSE +-- +-- Maintainer : cvs-ghc at haskell.org +-- Stability : internal +-- Portability : non-portable (GHC extensions) +-- +-- GHC's implementation of the 'ForeignPtr' data type. +-- +----------------------------------------------------------------------------- + +module GHC.ForeignPtr.Ops + ( -- * Reading + peekWord8ForeignPtr + , peekWord16ForeignPtr + , peekWord32ForeignPtr + , peekWord64ForeignPtr + , peekWordForeignPtr + , peekInt8ForeignPtr + , peekInt16ForeignPtr + , peekInt32ForeignPtr + , peekInt64ForeignPtr + , peekIntForeignPtr + , peekCharForeignPtr + -- * Writing + , pokeWord8ForeignPtr + , pokeWord16ForeignPtr + , pokeWord32ForeignPtr + , pokeWord64ForeignPtr + , pokeWordForeignPtr + , pokeInt8ForeignPtr + , pokeInt16ForeignPtr + , pokeInt32ForeignPtr + , pokeInt64ForeignPtr + , pokeIntForeignPtr + , pokeCharForeignPtr + ) where + +import GHC.Word +import GHC.Int +import GHC.Base +import GHC.ForeignPtr +import GHC.Ptr + +withFP :: ForeignPtr a + -> (Addr# -> State# RealWorld -> (# State# RealWorld, b #)) + -> IO b +withFP fp f = + withForeignPtr fp (\(Ptr addr) -> IO (f addr)) + +peekWord8ForeignPtr :: ForeignPtr ty -> Int -> IO Word8 +peekWord8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readWord8OffAddr# addr d s0 of + (# s1, r #) -> (# s1, W8# r #) + +peekWord16ForeignPtr :: ForeignPtr ty -> Int -> IO Word16 +peekWord16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readWord16OffAddr# addr d s0 of + (# s1, r #) -> (# s1, W16# r #) + +peekWord32ForeignPtr :: ForeignPtr ty -> Int -> IO Word32 +peekWord32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readWord32OffAddr# addr d s0 of + (# s1, r #) -> (# s1, W32# r #) + +peekWord64ForeignPtr :: ForeignPtr ty -> Int -> IO Word64 +peekWord64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readWord64OffAddr# addr d s0 of + (# s1, r #) -> (# s1, W64# r #) + +peekWordForeignPtr :: ForeignPtr ty -> Int -> IO Word +peekWordForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readWordOffAddr# addr d s0 of + (# s1, r #) -> (# s1, W# r #) + +peekInt8ForeignPtr :: ForeignPtr ty -> Int -> IO Int8 +peekInt8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readInt8OffAddr# addr d s0 of + (# s1, r #) -> (# s1, I8# r #) + +peekInt16ForeignPtr :: ForeignPtr ty -> Int -> IO Int16 +peekInt16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readInt16OffAddr# addr d s0 of + (# s1, r #) -> (# s1, I16# r #) + +peekInt32ForeignPtr :: ForeignPtr ty -> Int -> IO Int32 +peekInt32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readInt32OffAddr# addr d s0 of + (# s1, r #) -> (# s1, I32# r #) + +peekInt64ForeignPtr :: ForeignPtr ty -> Int -> IO Int64 +peekInt64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readInt64OffAddr# addr d s0 of + (# s1, r #) -> (# s1, I64# r #) + +peekIntForeignPtr :: ForeignPtr ty -> Int -> IO Int +peekIntForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readIntOffAddr# addr d s0 of + (# s1, r #) -> (# s1, I# r #) + +peekCharForeignPtr :: ForeignPtr ty -> Int -> IO Char +peekCharForeignPtr fp (I# d) = withFP fp $ \addr s0 -> + case readCharOffAddr# addr d s0 of + (# s1, r #) -> (# s1, C# r #) + +pokeWord8ForeignPtr :: ForeignPtr ty -> Int -> Word8 -> IO () +pokeWord8ForeignPtr fp (I# d) (W8# n) = withFP fp $ \addr s0 -> + case writeWord8OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeWord16ForeignPtr :: ForeignPtr ty -> Int -> Word16 -> IO () +pokeWord16ForeignPtr fp (I# d) (W16# n) = withFP fp $ \addr s0 -> + case writeWord16OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeWord32ForeignPtr :: ForeignPtr ty -> Int -> Word32 -> IO () +pokeWord32ForeignPtr fp (I# d) (W32# n) = withFP fp $ \addr s0 -> + case writeWord32OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeWord64ForeignPtr :: ForeignPtr ty -> Int -> Word64 -> IO () +pokeWord64ForeignPtr fp (I# d) (W64# n) = withFP fp $ \addr s0 -> + case writeWord64OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeWordForeignPtr :: ForeignPtr ty -> Int -> Word -> IO () +pokeWordForeignPtr fp (I# d) (W# n) = withFP fp $ \addr s0 -> + case writeWord64OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeInt8ForeignPtr :: ForeignPtr ty -> Int -> Int8 -> IO () +pokeInt8ForeignPtr fp (I# d) (I8# n) = withFP fp $ \addr s0 -> + case writeInt8OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeInt16ForeignPtr :: ForeignPtr ty -> Int -> Int16 -> IO () +pokeInt16ForeignPtr fp (I# d) (I16# n) = withFP fp $ \addr s0 -> + case writeInt16OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeInt32ForeignPtr :: ForeignPtr ty -> Int -> Int32 -> IO () +pokeInt32ForeignPtr fp (I# d) (I32# n) = withFP fp $ \addr s0 -> + case writeInt32OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeInt64ForeignPtr :: ForeignPtr ty -> Int -> Int64 -> IO () +pokeInt64ForeignPtr fp (I# d) (I64# n) = withFP fp $ \addr s0 -> + case writeInt64OffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeIntForeignPtr :: ForeignPtr ty -> Int -> Int -> IO () +pokeIntForeignPtr fp (I# d) (I# n) = withFP fp $ \addr s0 -> + case writeIntOffAddr# addr d n s0 of + s1 -> (# s1, () #) + +pokeCharForeignPtr :: ForeignPtr ty -> Int -> Char -> IO () +pokeCharForeignPtr fp (I# d) (C# n) = withFP fp $ \addr s0 -> + case writeCharOffAddr# addr d n s0 of + s1 -> (# s1, () #) + ===================================== libraries/base/GHC/IO/Buffer.hs ===================================== @@ -72,6 +72,8 @@ import GHC.Word import GHC.Show import GHC.Real import GHC.List +import GHC.ForeignPtr.Ops +import GHC.ForeignPtr (unsafeWithForeignPtr) import Foreign.C.Types import Foreign.ForeignPtr import Foreign.Storable @@ -103,10 +105,10 @@ import Foreign.Storable type RawBuffer e = ForeignPtr e readWord8Buf :: RawBuffer Word8 -> Int -> IO Word8 -readWord8Buf arr ix = withForeignPtr arr $ \p -> peekByteOff p ix +readWord8Buf p ix = peekWord8ForeignPtr p ix writeWord8Buf :: RawBuffer Word8 -> Int -> Word8 -> IO () -writeWord8Buf arr ix w = withForeignPtr arr $ \p -> pokeByteOff p ix w +writeWord8Buf p ix w = pokeWord8ForeignPtr p ix w #if defined(CHARBUF_UTF16) type CharBufElem = Word16 @@ -117,17 +119,17 @@ type CharBufElem = Char type RawCharBuffer = RawBuffer CharBufElem peekCharBuf :: RawCharBuffer -> Int -> IO Char -peekCharBuf arr ix = withForeignPtr arr $ \p -> do +peekCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> do (c,_) <- readCharBufPtr p ix return c {-# INLINE readCharBuf #-} readCharBuf :: RawCharBuffer -> Int -> IO (Char, Int) -readCharBuf arr ix = withForeignPtr arr $ \p -> readCharBufPtr p ix +readCharBuf arr ix = unsafeWithForeignPtr arr $ \p -> readCharBufPtr p ix {-# INLINE writeCharBuf #-} writeCharBuf :: RawCharBuffer -> Int -> Char -> IO Int -writeCharBuf arr ix c = withForeignPtr arr $ \p -> writeCharBufPtr p ix c +writeCharBuf arr ix c = unsafeWithForeignPtr arr $ \p -> writeCharBufPtr p ix c {-# INLINE readCharBufPtr #-} readCharBufPtr :: Ptr CharBufElem -> Int -> IO (Char, Int) ===================================== libraries/base/base.cabal ===================================== @@ -214,6 +214,7 @@ Library GHC.Float.RealFracMethods GHC.Foreign GHC.ForeignPtr + GHC.ForeignPtr.Ops GHC.GHCi GHC.GHCi.Helpers GHC.Generics ===================================== libraries/bytestring ===================================== @@ -1 +1 @@ -Subproject commit 8b5d8d0da24aefdc4d950174bf396b32335d7e0f +Subproject commit 36c2df1feaf10fde8d5848ac47b98d6d62c4e1d7 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d8222cfd23767712c9d4e26f84725d94ceee789c...10db1230433d5e8bfac970868849028d8935957f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d8222cfd23767712c9d4e26f84725d94ceee789c...10db1230433d5e8bfac970868849028d8935957f 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 Mon Nov 30 15:15:30 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 30 Nov 2020 10:15:30 -0500 Subject: [Git][ghc/ghc][master] rts/m32: Refactor handling of allocator seeding Message-ID: <5fc50c9228e67_86cfd752bc983358@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8d304a99 by Ben Gamari at 2020-11-30T10:15:22-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - 1 changed file: - rts/linker/M32Alloc.c Changes: ===================================== rts/linker/M32Alloc.c ===================================== @@ -81,6 +81,7 @@ The allocator manages two kinds of allocations: * small allocations, which are allocated into a set of "nursery" pages (recorded in m32_allocator_t.pages; the size of the set is <= M32_MAX_PAGES) + * large allocations are those larger than a page and are mapped directly Each page (or the first page of a large allocation) begins with a m32_page_t @@ -126,7 +127,9 @@ code accordingly). To avoid unnecessary mapping/unmapping we maintain a global list of free pages (which can grow up to M32_MAX_FREE_PAGE_POOL_SIZE long). Pages on this list have the usual m32_page_t header and are linked together with -m32_page_t.free_page.next. +m32_page_t.free_page.next. When run out of free pages we allocate a chunk of +M32_MAP_PAGES to both avoid fragmenting our address space and amortize the +runtime cost of the mapping. The allocator is *not* thread-safe. @@ -139,7 +142,12 @@ The allocator is *not* thread-safe. * M32 ALLOCATOR (see Note [M32 Allocator] ***************************************************************************/ +/* How many open pages each allocator will keep around? */ #define M32_MAX_PAGES 32 +/* How many pages should we map at once when re-filling the free page pool? */ +#define M32_MAP_PAGES 32 +/* Upper bound on the number of pages to keep in the free page pool */ +#define M32_MAX_FREE_PAGE_POOL_SIZE 64 /** * Page header @@ -204,7 +212,6 @@ struct m32_allocator_t { * * We keep a small pool of free pages around to avoid fragmentation. */ -#define M32_MAX_FREE_PAGE_POOL_SIZE 16 struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO @@ -250,18 +257,33 @@ m32_release_page(struct m32_page_t *page) static struct m32_page_t * m32_alloc_page(void) { - if (m32_free_page_pool_size > 0) { - struct m32_page_t *page = m32_free_page_pool; - m32_free_page_pool = page->free_page.next; - m32_free_page_pool_size --; - return page; - } else { - struct m32_page_t *page = mmapForLinker(getPageSize(), PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); - if (page > (struct m32_page_t *) 0xffffffff) { + if (m32_free_page_pool_size == 0) { + /* + * Free page pool is empty; refill it with a new batch of M32_MAP_PAGES + * pages. + */ + const size_t pgsz = getPageSize(); + char *chunk = mmapForLinker(pgsz * M32_MAP_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + if (chunk > (char *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } - return page; + +#define GET_PAGE(i) ((struct m32_page_t *) (chunk + (i) * pgsz)) + for (int i=0; i < M32_MAP_PAGES; i++) { + struct m32_page_t *page = GET_PAGE(i); + page->free_page.next = GET_PAGE(i+1); + } + + GET_PAGE(M32_MAP_PAGES-1)->free_page.next = m32_free_page_pool; + m32_free_page_pool = (struct m32_page_t *) chunk; + m32_free_page_pool_size += M32_MAP_PAGES; +#undef GET_PAGE } + + struct m32_page_t *page = m32_free_page_pool; + m32_free_page_pool = page->free_page.next; + m32_free_page_pool_size --; + return page; } /** @@ -276,19 +298,6 @@ m32_allocator_new(bool executable) stgMallocBytes(sizeof(m32_allocator), "m32_new_allocator"); memset(alloc, 0, sizeof(struct m32_allocator_t)); alloc->executable = executable; - - // Preallocate the initial M32_MAX_PAGES to ensure that they don't - // fragment the memory. - size_t pgsz = getPageSize(); - char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); - if (bigchunk == NULL) - barf("m32_allocator_init: Failed to map"); - - int i; - for (i=0; ipages[i] = (struct m32_page_t *) (bigchunk + i*pgsz); - alloc->pages[i]->current_size = sizeof(struct m32_page_t); - } return alloc; } @@ -350,7 +359,9 @@ m32_allocator_push_filled_list(struct m32_page_t **head, struct m32_page_t *page void m32_allocator_flush(m32_allocator *alloc) { for (int i=0; ipages[i]->current_size == sizeof(struct m32_page_t)) { + if (alloc->pages[i] == NULL) { + continue; + } else if (alloc->pages[i]->current_size == sizeof(struct m32_page_t)) { // the page is empty, free it m32_release_page(alloc->pages[i]); } else { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8d304a99d2d0c17fb49c0589c0525817d515c0d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8d304a99d2d0c17fb49c0589c0525817d515c0d0 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 Mon Nov 30 15:16:07 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 30 Nov 2020 10:16:07 -0500 Subject: [Git][ghc/ghc][master] 2 commits: rts: Use CHECK instead of assert Message-ID: <5fc50cb730b0f_86c113040b09862f7@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b6629289 by Ben Gamari at 2020-11-30T10:15:58-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 9f4efa6a by Ben Gamari at 2020-11-30T10:15:58-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 7 changed files: - rts/Linker.c - rts/linker/Elf.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/elf_got.c - rts/linker/elf_reloc_aarch64.c - rts/win32/veh_excn.c Changes: ===================================== rts/Linker.c ===================================== @@ -49,7 +49,6 @@ #include #include #include -#include #include #if defined(HAVE_SYS_STAT_H) @@ -885,12 +884,11 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) */ IF_DEBUG(linker, debugBelch("lookupSymbol: looking up %s with dlsym\n", lbl)); - ASSERT(lbl[0] == '_'); + CHECK(lbl[0] == '_'); return internal_dlsym(lbl + 1); # else - ASSERT(false); - return NULL; +# error No OBJFORMAT_* macro set # endif } else { if (dependent) { @@ -2112,7 +2110,7 @@ HsInt unloadNativeObj (void *handle) n_unloaded_objects += 1; // dynamic objects have no symbols - ASSERT(nc->symbols == NULL); + CHECK(nc->symbols == NULL); freeOcStablePtrs(nc); // Remove object code from root set ===================================== rts/linker/Elf.c ===================================== @@ -416,7 +416,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) "\nSection header table: start %ld, n_entries %d, ent_size %d\n", (long)ehdr->e_shoff, shnum, ehdr->e_shentsize )); - ASSERT(ehdr->e_shentsize == sizeof(Elf_Shdr)); + CHECK(ehdr->e_shentsize == sizeof(Elf_Shdr)); shdr = (Elf_Shdr*) (ehdrC + ehdr->e_shoff); @@ -537,7 +537,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) #if defined(SHN_XINDEX) /* See Note [Many ELF Sections] */ if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -864,7 +864,7 @@ ocGetNames_ELF ( ObjectCode* oc ) PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); - ASSERT(common_mem != NULL); + CHECK(common_mem != NULL); } //TODO: we ignore local symbols anyway right? So we can use the @@ -893,7 +893,7 @@ ocGetNames_ELF ( ObjectCode* oc ) secno = shndx; #if defined(SHN_XINDEX) if (shndx == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -902,11 +902,11 @@ ocGetNames_ELF ( ObjectCode* oc ) if (shndx == SHN_COMMON) { isLocal = false; - ASSERT(common_used < common_size); - ASSERT(common_mem); + CHECK(common_used < common_size); + CHECK(common_mem); symbol->addr = (void*)((uintptr_t)common_mem + common_used); common_used += symbol->elf_sym->st_size; - ASSERT(common_used <= common_size); + CHECK(common_used <= common_size); IF_DEBUG(linker, debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", @@ -935,7 +935,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ) ) { /* Section 0 is the undefined section, hence > and not >=. */ - ASSERT(secno > 0 && secno < shnum); + CHECK(secno > 0 && secno < shnum); /* if (shdr[secno].sh_type == SHT_NOBITS) { debugBelch(" BSS symbol, size %d off %d name %s\n", @@ -945,7 +945,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - ASSERT(symbol->addr != 0x0); + CHECK(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -962,7 +962,7 @@ ocGetNames_ELF ( ObjectCode* oc ) /* And the decision is ... */ if (symbol->addr != NULL) { - ASSERT(nm != NULL); + CHECK(nm != NULL); /* Acquire! */ if (!isLocal) { @@ -1045,7 +1045,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, break; } } - ASSERT(stab != NULL); + CHECK(stab != NULL); targ = (Elf_Word*)oc->sections[target_shndx].start; IF_DEBUG(linker,debugBelch( @@ -1251,7 +1251,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, result = ((S + A) | T) - P; result &= ~1; // Clear thumb indicator bit - ASSERT(isInt(26, result)); /* X in range */ + CHECK(isInt(26, result)); /* X in range */ } // Update the branch target @@ -1426,7 +1426,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, case COMPAT_R_ARM_GOT_PREL: { int32_t A = *pP; void* GOT_S = symbol->got_addr; - ASSERT(GOT_S); + CHECK(GOT_S); *(uint32_t *)P = (uint32_t) GOT_S + A - P; break; } @@ -1552,21 +1552,21 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, case R_SPARC_WDISP30: w1 = *pP & 0xC0000000; w2 = (Elf_Word)((value - P) >> 2); - ASSERT((w2 & 0xC0000000) == 0); + CHECK((w2 & 0xC0000000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_HI22: w1 = *pP & 0xFFC00000; w2 = (Elf_Word)(value >> 10); - ASSERT((w2 & 0xFFC00000) == 0); + CHECK((w2 & 0xFFC00000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_LO10: w1 = *pP & ~0x3FF; w2 = (Elf_Word)(value & 0x3FF); - ASSERT((w2 & ~0x3FF) == 0); + CHECK((w2 & ~0x3FF) == 0); w1 |= w2; *pP = w1; break; @@ -1866,13 +1866,13 @@ ocResolve_ELF ( ObjectCode* oc ) Elf_Word secno = symbol->elf_sym->st_shndx; #if defined(SHN_XINDEX) if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[i]; } #endif - ASSERT(symbol->elf_sym->st_name == 0); - ASSERT(symbol->elf_sym->st_value == 0); - ASSERT(0x0 != oc->sections[ secno ].start); + CHECK(symbol->elf_sym->st_name == 0); + CHECK(symbol->elf_sym->st_value == 0); + CHECK(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1946,7 +1946,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { - ASSERT(0x0 != *init); + CHECK(0x0 != *init); (*init)(argc, argv, envv); } } ===================================== rts/linker/MachO.c ===================================== @@ -252,7 +252,6 @@ resolveImports( "%s: unknown symbol `%s'", oc->fileName, symbol->name); return 0; } - ASSERT(addr); checkProddableBlock(oc, ((void**)(oc->image + sect->offset)) + i, @@ -847,7 +846,7 @@ relocateSection(ObjectCode* oc, int curSection) IF_DEBUG(linker, debugBelch(" : value = %p\n", (void *)symbol->nlist->n_value)); if ((symbol->nlist->n_type & N_TYPE) == N_SECT) { - ASSERT(symbol->addr != NULL); + CHECK(symbol->addr != NULL); value = (uint64_t) symbol->addr; IF_DEBUG(linker, debugBelch("relocateSection, defined external symbol %s, relocated address %p\n", nm, (void *)value)); @@ -949,29 +948,29 @@ relocateSection(ObjectCode* oc, int curSection) { if((int32_t)(value - baseValue) != (int64_t)(value - baseValue)) { - ASSERT(reloc->r_extern); + CHECK(reloc->r_extern); value = (uint64_t) &makeSymbolExtra(oc, reloc->r_symbolnum, value) -> jumpIsland; } - ASSERT((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); + CHECK((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); type = X86_64_RELOC_SIGNED; } switch(type) { case X86_64_RELOC_UNSIGNED: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing += value; break; case X86_64_RELOC_SIGNED: case X86_64_RELOC_SIGNED_1: case X86_64_RELOC_SIGNED_2: case X86_64_RELOC_SIGNED_4: - ASSERT(reloc->r_pcrel); + CHECK(reloc->r_pcrel); thing += value - baseValue; break; case X86_64_RELOC_SUBTRACTOR: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing -= value; break; default: ===================================== rts/linker/PEi386.c ===================================== @@ -1594,7 +1594,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) barf ("Could not allocate any heap memory from private heap."); } - ASSERT(section.size == 0 || section.info->virtualSize == 0); + CHECK(section.size == 0 || section.info->virtualSize == 0); sz = section.size; if (sz < section.info->virtualSize) sz = section.info->virtualSize; @@ -2032,7 +2032,7 @@ ocRunInit_PEi386 ( ObjectCode *oc ) getProgEnvv(&envc, &envv); Section section = *oc->info->init; - ASSERT(SECTIONKIND_INIT_ARRAY == section.kind); + CHECK(SECTIONKIND_INIT_ARRAY == section.kind); uint8_t *init_startC = section.start; init_t *init_start = (init_t*)init_startC; ===================================== rts/linker/elf_got.c ===================================== @@ -136,10 +136,10 @@ verifyGot(ObjectCode * oc) { for(size_t i=0; i < symTab->n_symbols; i++) { ElfSymbol * symbol = &symTab->symbols[i]; if(symbol->got_addr) { - ASSERT((void*)(*(void**)symbol->got_addr) - == (void*)symbol->addr); + CHECK((void*)(*(void**)symbol->got_addr) + == (void*)symbol->addr); } - ASSERT(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); + CHECK(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); } } return EXIT_SUCCESS; ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -6,7 +6,6 @@ #include "elf_plt.h" #include -#include #if defined(aarch64_HOST_ARCH) @@ -71,15 +70,15 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { *(uint64_t*)P = (uint64_t)addend; break; case COMPAT_R_AARCH64_ABS32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); case COMPAT_R_AARCH64_PREL32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); *(uint32_t*)P = (uint32_t)addend; break; case COMPAT_R_AARCH64_ABS16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); case COMPAT_R_AARCH64_PREL16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); *(uint16_t*)P = (uint16_t)addend; break; /* static aarch64 relocations */ @@ -95,8 +94,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { // imm64 = SignExtend(hi:lo:0x000,64) // Range is 21 bits + the 12 page relative bits // known to be 0. -2^32 <= X < 2^32 - assert(isInt64(21+12, addend)); - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t) (((uint64_t) addend << 17) & 0x60000000) @@ -106,7 +105,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { /* - control flow relocations */ case COMPAT_R_AARCH64_JUMP26: /* relocate b ... */ case COMPAT_R_AARCH64_CALL26: { /* relocate bl ... */ - assert(isInt64(26+2, addend)); /* X in range */ + CHECK(isInt64(26+2, addend)); /* X in range */ *(inst_t *)P = (*(inst_t *)P & 0xfc000000) /* keep upper 6 (32-6) * bits */ | ((uint32_t)(addend >> 2) & 0x03ffffff); @@ -114,8 +113,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { } case COMPAT_R_AARCH64_ADR_GOT_PAGE: { /* range is -2^32 <= X < 2^32 */ - assert(isInt64(21+12, addend)); /* X in range */ - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); /* X in range */ + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t)(((uint64_t)addend << 17) & 0x60000000) // lo @@ -149,10 +148,10 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { FALLTHROUGH; case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { if(exp_shift == -1) { - assert( (addend & 7) == 0 ); + CHECK( (addend & 7) == 0 ); exp_shift = 3; } - assert((addend & 0xfff) == addend); + CHECK((addend & 0xfff) == addend); int shift = 0; if(isLoadStore(P)) { /* bits 31, 30 encode the size. */ @@ -161,7 +160,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { shift = 4; } } - assert(addend == 0 || exp_shift == shift); + CHECK(addend == 0 || exp_shift == shift); *(inst_t *)P = (*(inst_t *)P & 0xffc003ff) | ((inst_t)(addend >> shift << 10) & 0x003ffc00); break; @@ -188,12 +187,12 @@ computeAddend(Section * section, Elf_Rel * rel, /* Position where something is relocated */ addr_t P = (addr_t)((uint8_t*)section->start + rel->r_offset); - assert(0x0 != P); - assert((uint64_t)section->start <= P); - assert(P <= (uint64_t)section->start + section->size); + CHECK(0x0 != P); + CHECK((uint64_t)section->start <= P); + CHECK(P <= (uint64_t)section->start + section->size); /* Address of the symbol */ addr_t S = (addr_t) symbol->addr; - assert(0x0 != S); + CHECK(0x0 != S); /* GOT slot for the symbol */ addr_t GOT_S = (addr_t) symbol->got_addr; @@ -243,16 +242,16 @@ computeAddend(Section * section, Elf_Rel * rel, } } - assert(0 == (0xffff000000000000 & S)); + CHECK(0 == (0xffff000000000000 & S)); V = S + A - P; - assert(isInt64(26+2, V)); /* X in range */ + CHECK(isInt64(26+2, V)); /* X in range */ } return V; } - case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: assert(0 == ((S+A) & 0x0f)); - case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: assert(0 == ((S+A) & 0x07)); - case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: assert(0 == ((S+A) & 0x03)); - case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: assert(0 == ((S+A) & 0x01)); + case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x0f)); + case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x07)); + case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x03)); + case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x01)); case COMPAT_R_AARCH64_LDST8_ABS_LO12_NC: /* type: static, class: aarch64, op: S + A */ return (S + A) & 0xfff; @@ -266,12 +265,12 @@ computeAddend(Section * section, Elf_Rel * rel, // TODO: fix this story proper, so that the transformation // makes sense without resorting to: everyone else // does it like this as well. - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return Page(GOT_S+A) - Page(P); } case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { // G(GDAT(S+A)) - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return (GOT_S + A) & 0xfff; } default: @@ -297,7 +296,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); + CHECK(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -323,8 +322,8 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relaTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); - assert(0x0 != symbol->addr); + CHECK(0x0 != symbol); + CHECK(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== rts/win32/veh_excn.c ===================================== @@ -10,7 +10,6 @@ #include "ghcconfig.h" #include "veh_excn.h" #include "LinkerInternals.h" -#include #include #include #include @@ -195,7 +194,7 @@ void __register_hs_exception_handler( void ) __hs_handle = AddVectoredContinueHandler(CALL_LAST, __hs_exception_handler); // should the handler not be registered this will return a null. - assert(__hs_handle); + CHECK(__hs_handle); // Register for an exception filter to ensure the continue handler gets // hit if no one handled the exception. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8d304a99d2d0c17fb49c0589c0525817d515c0d0...9f4efa6a5e5d43c81d7e61b27f7cd6e3f812b1ea -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8d304a99d2d0c17fb49c0589c0525817d515c0d0...9f4efa6a5e5d43c81d7e61b27f7cd6e3f812b1ea 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 Mon Nov 30 15:16:42 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 30 Nov 2020 10:16:42 -0500 Subject: [Git][ghc/ghc][master] Allow deploy:pages job to fail Message-ID: <5fc50cda4dc94_86c15c5d38898918f@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0f8a4655 by Ryan Scott at 2020-11-30T10:16:34-05:00 Allow deploy:pages job to fail See #18973. - - - - - 1 changed file: - .gitlab-ci.yml Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1237,6 +1237,8 @@ pages: dependencies: - doc-tarball image: ghcci/x86_64-linux-deb9:0.2 + # See #18973 + allow_failure: true tags: - x86_64-linux script: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f8a4655e39bed1ca39820abdd3df9db5706b036 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0f8a4655e39bed1ca39820abdd3df9db5706b036 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 Mon Nov 30 15:47:44 2020 From: gitlab at gitlab.haskell.org (Marge Bot) Date: Mon, 30 Nov 2020 10:47:44 -0500 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: rts/m32: Refactor handling of allocator seeding Message-ID: <5fc51420d8efa_86cf574568995086@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 8d304a99 by Ben Gamari at 2020-11-30T10:15:22-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - b6629289 by Ben Gamari at 2020-11-30T10:15:58-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 9f4efa6a by Ben Gamari at 2020-11-30T10:15:58-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 0f8a4655 by Ryan Scott at 2020-11-30T10:16:34-05:00 Allow deploy:pages job to fail See #18973. - - - - - 1e3997bd by chessai at 2020-11-30T10:47:24-05:00 Optimisations in Data.Foldable (T17867) This PR concerns the following functions from `Data.Foldable`: * minimum * maximum * sum * product * minimumBy * maximumBy - Default implementations of these functions now use `foldl'` or `foldMap'`. - All have been marked with INLINEABLE to make room for further optimisations. - - - - - 644b0cde by chessai at 2020-11-30T10:47:24-05:00 Apply suggestion to libraries/base/Data/Foldable.hs - - - - - 672d9e9f by chessai at 2020-11-30T10:47:24-05:00 Apply suggestion to libraries/base/Data/Foldable.hs - - - - - 9aef8407 by Viktor Dukhovni at 2020-11-30T10:47:26-05:00 dirty MVAR after mutating TSO queue head While the original head and tail of the TSO queue may be in the same generation as the MVAR, interior elements of the queue could be younger after a GC run and may then be exposed by putMVar operation that updates the queue head. Resolves #18919 - - - - - b5daa339 by Ben Gamari at 2020-11-30T10:47:27-05:00 rts/linker: Don't allow shared libraries to be loaded multiple times - - - - - 7f5f9a6d by Ben Gamari at 2020-11-30T10:47:27-05:00 rts/linker: Initialise CCSs from native shared objects - - - - - 4f12907b by Ben Gamari at 2020-11-30T10:47:27-05:00 rts/linker: Move shared library loading logic into Elf.c - - - - - bda568f4 by GHC GitLab CI at 2020-11-30T10:47:27-05:00 rts/linker: Don't declare dynamic objects with image_mapped This previously resulted in warnings due to spurious unmap failures. - - - - - 0b4d3133 by jneira at 2020-11-30T10:47:29-05:00 Include tried paths in findToolDir error - - - - - 17 changed files: - .gitlab-ci.yml - compiler/GHC/SysTools/BaseDir.hs - libraries/base/Data/Foldable.hs - rts/Linker.c - rts/LinkerInternals.h - rts/PrimOps.cmm - rts/Profiling.c - rts/Threads.c - rts/linker/Elf.c - rts/linker/Elf.h - rts/linker/M32Alloc.c - rts/linker/MachO.c - rts/linker/PEi386.c - rts/linker/PEi386Types.h - rts/linker/elf_got.c - rts/linker/elf_reloc_aarch64.c - rts/win32/veh_excn.c Changes: ===================================== .gitlab-ci.yml ===================================== @@ -1237,6 +1237,8 @@ pages: dependencies: - doc-tarball image: ghcci/x86_64-linux-deb9:0.2 + # See #18973 + allow_failure: true tags: - x86_64-linux script: ===================================== compiler/GHC/SysTools/BaseDir.hs ===================================== @@ -185,17 +185,19 @@ findToolDir :: FilePath -- ^ topdir -> IO (Maybe FilePath) #if defined(mingw32_HOST_OS) && !defined(USE_INPLACE_MINGW_TOOLCHAIN) -findToolDir top_dir = go 0 (top_dir "..") +findToolDir top_dir = go 0 (top_dir "..") [] where maxDepth = 3 - go :: Int -> FilePath -> IO (Maybe FilePath) - go k path + go :: Int -> FilePath -> [FilePath] -> IO (Maybe FilePath) + go k path tried | k == maxDepth = throwGhcExceptionIO $ - InstallationError "could not detect mingw toolchain" + InstallationError $ "could not detect mingw toolchain in the following paths: " ++ show tried | otherwise = do - oneLevel <- doesDirectoryExist (path "mingw") + let try = path "mingw" + let tried = tried ++ [try] + oneLevel <- doesDirectoryExist try if oneLevel then return (Just path) - else go (k+1) (path "..") + else go (k+1) (path "..") tried #else findToolDir _ = return Nothing #endif ===================================== libraries/base/Data/Foldable.hs ===================================== @@ -507,7 +507,8 @@ class Foldable t where -- @since 4.8.0.0 maximum :: forall a . Ord a => t a -> a maximum = fromMaybe (errorWithoutStackTrace "maximum: empty structure") . - getMax . foldMap (Max #. (Just :: a -> Maybe a)) + getMax . foldMap' (Max #. (Just :: a -> Maybe a)) + {-# INLINEABLE maximum #-} -- | The least element of a non-empty structure. -- @@ -529,7 +530,8 @@ class Foldable t where -- @since 4.8.0.0 minimum :: forall a . Ord a => t a -> a minimum = fromMaybe (errorWithoutStackTrace "minimum: empty structure") . - getMin . foldMap (Min #. (Just :: a -> Maybe a)) + getMin . foldMap' (Min #. (Just :: a -> Maybe a)) + {-# INLINEABLE minimum #-} -- | The 'sum' function computes the sum of the numbers of a structure. -- @@ -554,7 +556,8 @@ class Foldable t where -- -- @since 4.8.0.0 sum :: Num a => t a -> a - sum = getSum #. foldMap Sum + sum = getSum #. foldMap' Sum + {-# INLINEABLE sum #-} -- | The 'product' function computes the product of the numbers of a -- structure. @@ -580,7 +583,8 @@ class Foldable t where -- -- @since 4.8.0.0 product :: Num a => t a -> a - product = getProduct #. foldMap Product + product = getProduct #. foldMap' Product + {-# INLINEABLE product #-} -- instances for Prelude types @@ -1111,10 +1115,15 @@ all p = getAll #. foldMap (All #. p) -- See Note [maximumBy/minimumBy space usage] maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -maximumBy cmp = foldl1 max' - where max' x y = case cmp x y of - GT -> x - _ -> y +maximumBy cmp = fromMaybe (errorWithoutStackTrace "maximumBy: empty structure") + . foldl' max' Nothing + where + max' mx y = Just $! case mx of + Nothing -> y + Just x -> case cmp x y of + GT -> x + _ -> y +{-# INLINEABLE maximumBy #-} -- | The least element of a non-empty structure with respect to the -- given comparison function. @@ -1128,10 +1137,15 @@ maximumBy cmp = foldl1 max' -- See Note [maximumBy/minimumBy space usage] minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -minimumBy cmp = foldl1 min' - where min' x y = case cmp x y of - GT -> y - _ -> x +minimumBy cmp = fromMaybe (errorWithoutStackTrace "minimumBy: empty structure") + . foldl' min' Nothing + where + min' mx y = Just $! case mx of + Nothing -> y + Just x -> case cmp x y of + GT -> y + _ -> x +{-# INLINEABLE minimumBy #-} -- | 'notElem' is the negation of 'elem'. -- @@ -1268,12 +1282,6 @@ proportional to the size of the data structure. For the common case of lists, this could be particularly bad (see #10830). For the common case of lists, switching the implementations of maximumBy and -minimumBy to foldl1 solves the issue, as GHC's strictness analysis can then -make these functions only use O(1) stack space. It is perhaps not the optimal -way to fix this problem, as there are other conceivable data structures -(besides lists) which might benefit from specialized implementations for -maximumBy and minimumBy (see -https://gitlab.haskell.org/ghc/ghc/issues/10830#note_129843 for a further -discussion). But using foldl1 is at least always better than using foldr1, so -GHC has chosen to adopt that approach for now. +minimumBy to foldl1 solves the issue, assuming GHC's strictness analysis can then +make these functions only use O(1) stack space. As of base 4.16, we have switched to employing foldl' over foldl1, not relying on GHC's optimiser. See https://gitlab.haskell.org/ghc/ghc/-/issues/17867 for more context. -} ===================================== rts/Linker.c ===================================== @@ -49,7 +49,6 @@ #include #include #include -#include #include #if defined(HAVE_SYS_STAT_H) @@ -64,7 +63,6 @@ # include "linker/Elf.h" # include // regex is already used by dlopen() so this is OK // to use here without requiring an additional lib -# include #elif defined(OBJFORMAT_PEi386) # include "linker/PEi386.h" # include @@ -171,8 +169,6 @@ Mutex linker_mutex; /* Generic wrapper function to try and Resolve and RunInit oc files */ int ocTryLoad( ObjectCode* oc ); -static void freeNativeCode_ELF (ObjectCode *nc); - /* Link objects into the lower 2Gb on x86_64 and AArch64. GHC assumes the * small memory model on this architecture (see gcc docs, * -mcmodel=small). @@ -399,7 +395,7 @@ static void *dl_prog_handle; static regex_t re_invalid; static regex_t re_realso; #if defined(THREADED_RTS) -static Mutex dl_mutex; // mutex to protect dlopen/dlerror critical section +Mutex dl_mutex; // mutex to protect dlopen/dlerror critical section #endif #endif @@ -885,12 +881,11 @@ SymbolAddr* lookupDependentSymbol (SymbolName* lbl, ObjectCode *dependent) */ IF_DEBUG(linker, debugBelch("lookupSymbol: looking up %s with dlsym\n", lbl)); - ASSERT(lbl[0] == '_'); + CHECK(lbl[0] == '_'); return internal_dlsym(lbl + 1); # else - ASSERT(false); - return NULL; +# error No OBJFORMAT_* macro set # endif } else { if (dependent) { @@ -1871,7 +1866,7 @@ HsInt purgeObj (pathchar *path) return r; } -static OStatus getObjectLoadStatus_ (pathchar *path) +OStatus getObjectLoadStatus_ (pathchar *path) { for (ObjectCode *o = objects; o; o = o->next) { if (0 == pathcmp(o->fileName, path)) { @@ -1961,126 +1956,6 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc, size, kind )); } - -# if defined(OBJFORMAT_ELF) -static int loadNativeObjCb_(struct dl_phdr_info *info, - size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { - ObjectCode* nc = (ObjectCode*) data; - - // This logic mimicks _dl_addr_inside_object from glibc - // For reference: - // int - // internal_function - // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) - // { - // int n = l->l_phnum; - // const ElfW(Addr) reladdr = addr - l->l_addr; - // - // while (--n >= 0) - // if (l->l_phdr[n].p_type == PT_LOAD - // && reladdr - l->l_phdr[n].p_vaddr >= 0 - // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) - // return 1; - // return 0; - // } - - if ((void*) info->dlpi_addr == nc->l_addr) { - int n = info->dlpi_phnum; - while (--n >= 0) { - if (info->dlpi_phdr[n].p_type == PT_LOAD) { - NativeCodeRange* ncr = - stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); - ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); - ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); - - ncr->next = nc->nc_ranges; - nc->nc_ranges = ncr; - } - } - } - return 0; -} - -static void copyErrmsg(char** errmsg_dest, char* errmsg) { - if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; - *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); - strcpy(*errmsg_dest, errmsg); -} - -// need dl_mutex -static void freeNativeCode_ELF (ObjectCode *nc) { - dlclose(nc->dlopen_handle); - - NativeCodeRange *ncr = nc->nc_ranges; - while (ncr) { - NativeCodeRange* last_ncr = ncr; - ncr = ncr->next; - stgFree(last_ncr); - } -} - -static void * loadNativeObj_ELF (pathchar *path, char **errmsg) -{ - ObjectCode* nc; - void *hdl, *retval; - - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); - - retval = NULL; - ACQUIRE_LOCK(&dl_mutex); - - nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, true, NULL, 0); - - foreignExportsLoadingObject(nc); - hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); - foreignExportsFinishedLoadingObject(); - if (hdl == NULL) { - /* dlopen failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlopen_fail; - } - - struct link_map *map; - if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { - /* dlinfo failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlinfo_fail; - } - - nc->l_addr = (void*) map->l_addr; - nc->dlopen_handle = hdl; - hdl = NULL; // pass handle ownership to nc - - dl_iterate_phdr(loadNativeObjCb_, nc); - if (!nc->nc_ranges) { - copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); - goto dl_iterate_phdr_fail; - } - - insertOCSectionIndices(nc); - - nc->next_loaded_object = loaded_objects; - loaded_objects = nc; - - retval = nc->dlopen_handle; - goto success; - -dl_iterate_phdr_fail: - // already have dl_mutex - freeNativeCode_ELF(nc); -dlinfo_fail: - if (hdl) dlclose(hdl); -dlopen_fail: -success: - - RELEASE_LOCK(&dl_mutex); - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); - - return retval; -} - -# endif - #define UNUSED(x) (void)(x) void * loadNativeObj (pathchar *path, char **errmsg) @@ -2112,7 +1987,7 @@ HsInt unloadNativeObj (void *handle) n_unloaded_objects += 1; // dynamic objects have no symbols - ASSERT(nc->symbols == NULL); + CHECK(nc->symbols == NULL); freeOcStablePtrs(nc); // Remove object code from root set ===================================== rts/LinkerInternals.h ===================================== @@ -20,8 +20,34 @@ void printLoadedObjects(void); #include "BeginPrivate.h" +/* Which object file format are we targeting? */ +#if defined(linux_HOST_OS) || defined(solaris2_HOST_OS) \ +|| defined(linux_android_HOST_OS) \ +|| defined(freebsd_HOST_OS) || defined(kfreebsdgnu_HOST_OS) \ +|| defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS) \ +|| defined(openbsd_HOST_OS) || defined(gnu_HOST_OS) +# define OBJFORMAT_ELF +#elif defined(mingw32_HOST_OS) +# define OBJFORMAT_PEi386 +#elif defined(darwin_HOST_OS) || defined(ios_HOST_OS) +# define OBJFORMAT_MACHO +#endif + typedef void SymbolAddr; typedef char SymbolName; +typedef struct _ObjectCode ObjectCode; +typedef struct _Section Section; + +#if defined(OBJFORMAT_ELF) +# include "linker/ElfTypes.h" +#elif defined(OBJFORMAT_PEi386) +# include "linker/PEi386Types.h" +#elif defined(OBJFORMAT_MACHO) +# include "linker/MachOTypes.h" +#else +# error "Unknown OBJECT_FORMAT for HOST_OS" +#endif + /* Hold extended information about a symbol in case we need to resolve it at a late stage. */ @@ -102,26 +128,24 @@ typedef enum { * and always refer to it with the 'struct' qualifier. */ -typedef - struct _Section { - void* start; /* actual start of section in memory */ - StgWord size; /* actual size of section in memory */ - SectionKind kind; - SectionAlloc alloc; - - /* - * The following fields are relevant for SECTION_MMAP sections only - */ - StgWord mapped_offset; /* offset from the image of mapped_start */ - void* mapped_start; /* start of mmap() block */ - StgWord mapped_size; /* size of mmap() block */ - - /* A customizable type to augment the Section type. - * See Note [No typedefs for customizable types] - */ - struct SectionFormatInfo* info; - } - Section; +struct _Section { + void* start; /* actual start of section in memory */ + StgWord size; /* actual size of section in memory */ + SectionKind kind; + SectionAlloc alloc; + + /* + * The following fields are relevant for SECTION_MMAP sections only + */ + StgWord mapped_offset; /* offset from the image of mapped_start */ + void* mapped_start; /* start of mmap() block */ + StgWord mapped_size; /* size of mmap() block */ + + /* A customizable type to augment the Section type. + * See Note [No typedefs for customizable types] + */ + struct SectionFormatInfo* info; +}; typedef struct _ProddableBlock { @@ -175,7 +199,7 @@ typedef enum { /* Top-level structure for an object module. One of these is allocated * for each object file in use. */ -typedef struct _ObjectCode { +struct _ObjectCode { OStatus status; pathchar *fileName; int fileSize; /* also mapped image size when using mmap() */ @@ -295,7 +319,7 @@ typedef struct _ObjectCode { /* virtual memory ranges of loaded code */ NativeCodeRange *nc_ranges; -} ObjectCode; +}; #define OC_INFORMATIVE_FILENAME(OC) \ ( (OC)->archiveMemberName ? \ @@ -306,6 +330,10 @@ typedef struct _ObjectCode { #if defined(THREADED_RTS) extern Mutex linker_mutex; + +#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) +extern Mutex dl_mutex; +#endif #endif /* Type of the initializer */ @@ -388,6 +416,7 @@ resolveSymbolAddr (pathchar* buffer, int size, #endif HsInt isAlreadyLoaded( pathchar *path ); +OStatus getObjectLoadStatus_ (pathchar *path); HsInt loadOc( ObjectCode* oc ); ObjectCode* mkOc( ObjectType type, pathchar *path, char *image, int imageSize, bool mapped, pathchar *archiveMemberName, @@ -403,24 +432,6 @@ void freeSegments(ObjectCode *oc); #define MAP_ANONYMOUS MAP_ANON #endif -/* Which object file format are we targeting? */ -#if defined(linux_HOST_OS) || defined(solaris2_HOST_OS) \ -|| defined(linux_android_HOST_OS) \ -|| defined(freebsd_HOST_OS) || defined(kfreebsdgnu_HOST_OS) \ -|| defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS) \ -|| defined(openbsd_HOST_OS) || defined(gnu_HOST_OS) -# define OBJFORMAT_ELF -# include "linker/ElfTypes.h" -#elif defined(mingw32_HOST_OS) -# define OBJFORMAT_PEi386 -# include "linker/PEi386Types.h" -#elif defined(darwin_HOST_OS) || defined(ios_HOST_OS) -# define OBJFORMAT_MACHO -# include "linker/MachOTypes.h" -#else -#error "Unknown OBJECT_FORMAT for HOST_OS" -#endif - /* In order to simplify control flow a bit, some references to mmap-related definitions are blocked off by a C-level if statement rather than a CPP-level #if statement. Since those are dead branches when !RTS_LINKER_USE_MMAP, we ===================================== rts/PrimOps.cmm ===================================== @@ -1827,9 +1827,16 @@ loop: // There are readMVar/takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1854,10 +1861,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); @@ -1912,9 +1917,16 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = StgMVarTSOQueue_tso(q); - StgMVar_head(mvar) = StgMVarTSOQueue_link(q); - if (StgMVar_head(mvar) == stg_END_TSO_QUEUE_closure) { + q = StgMVarTSOQueue_link(q); + StgMVar_head(mvar) = q; + if (q == stg_END_TSO_QUEUE_closure) { StgMVar_tail(mvar) = stg_END_TSO_QUEUE_closure; + } else { + if (info == stg_MVAR_CLEAN_info) { + // Resolve #18919. + ccall dirty_MVAR(BaseReg "ptr", mvar "ptr", + StgMVar_value(mvar) "ptr"); + } } ASSERT(StgTSO_block_info(tso) == mvar); @@ -1939,10 +1951,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = StgMVarTSOQueue_link(q); + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/Profiling.c ===================================== @@ -54,7 +54,7 @@ FILE *prof_file; // List of all cost centres. Used for reporting. CostCentre *CC_LIST = NULL; // All cost centre stacks temporarily appear here, to be able to make CCS_MAIN a -// parent of all cost centres stacks (done in initProfiling2()). +// parent of all cost centres stacks (done in refreshProfilingCCSs()). static CostCentreStack *CCS_LIST = NULL; #if defined(THREADED_RTS) ===================================== rts/Threads.c ===================================== @@ -803,9 +803,14 @@ loop: // There are takeMVar(s) waiting: wake up the first one tso = q->tso; - mvar->head = q->link; - if (mvar->head == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { + mvar->head = q = q->link; + if (q == (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure) { mvar->tail = (StgMVarTSOQueue*)&stg_END_TSO_QUEUE_closure; + } else { + if (info == &stg_MVAR_CLEAN_info) { + // Resolve #18919. + dirty_MVAR(&cap->r, (StgClosure*)mvar, mvar->value); + } } ASSERT(tso->block_info.closure == (StgClosure*)mvar); @@ -829,10 +834,8 @@ loop: // If it was a readMVar, then we can still do work, // so loop back. (XXX: This could take a while) - if (why_blocked == BlockedOnMVarRead) { - q = ((StgMVarTSOQueue*)q)->link; + if (why_blocked == BlockedOnMVarRead) goto loop; - } ASSERT(why_blocked == BlockedOnMVar); ===================================== rts/linker/Elf.c ===================================== @@ -15,15 +15,20 @@ #include "RtsUtils.h" #include "RtsSymbolInfo.h" +#include "CheckUnload.h" +#include "LinkerInternals.h" #include "linker/Elf.h" #include "linker/CacheFlush.h" #include "linker/M32Alloc.h" #include "linker/SymbolExtras.h" +#include "ForeignExports.h" +#include "Profiling.h" #include "sm/OSMem.h" #include "GetEnv.h" #include "linker/util.h" #include "linker/elf_util.h" +#include #include #include #if defined(HAVE_SYS_STAT_H) @@ -416,7 +421,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) "\nSection header table: start %ld, n_entries %d, ent_size %d\n", (long)ehdr->e_shoff, shnum, ehdr->e_shentsize )); - ASSERT(ehdr->e_shentsize == sizeof(Elf_Shdr)); + CHECK(ehdr->e_shentsize == sizeof(Elf_Shdr)); shdr = (Elf_Shdr*) (ehdrC + ehdr->e_shoff); @@ -537,7 +542,7 @@ ocVerifyImage_ELF ( ObjectCode* oc ) #if defined(SHN_XINDEX) /* See Note [Many ELF Sections] */ if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -864,7 +869,7 @@ ocGetNames_ELF ( ObjectCode* oc ) PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); - ASSERT(common_mem != NULL); + CHECK(common_mem != NULL); } //TODO: we ignore local symbols anyway right? So we can use the @@ -893,7 +898,7 @@ ocGetNames_ELF ( ObjectCode* oc ) secno = shndx; #if defined(SHN_XINDEX) if (shndx == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[j]; } #endif @@ -902,11 +907,11 @@ ocGetNames_ELF ( ObjectCode* oc ) if (shndx == SHN_COMMON) { isLocal = false; - ASSERT(common_used < common_size); - ASSERT(common_mem); + CHECK(common_used < common_size); + CHECK(common_mem); symbol->addr = (void*)((uintptr_t)common_mem + common_used); common_used += symbol->elf_sym->st_size; - ASSERT(common_used <= common_size); + CHECK(common_used <= common_size); IF_DEBUG(linker, debugBelch("COMMON symbol, size %ld name %s allocated at %p\n", @@ -935,7 +940,7 @@ ocGetNames_ELF ( ObjectCode* oc ) ) ) { /* Section 0 is the undefined section, hence > and not >=. */ - ASSERT(secno > 0 && secno < shnum); + CHECK(secno > 0 && secno < shnum); /* if (shdr[secno].sh_type == SHT_NOBITS) { debugBelch(" BSS symbol, size %d off %d name %s\n", @@ -945,7 +950,7 @@ ocGetNames_ELF ( ObjectCode* oc ) symbol->addr = (SymbolAddr*)( (intptr_t) oc->sections[secno].start + (intptr_t) symbol->elf_sym->st_value); - ASSERT(symbol->addr != 0x0); + CHECK(symbol->addr != 0x0); if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) { isLocal = true; isWeak = false; @@ -962,7 +967,7 @@ ocGetNames_ELF ( ObjectCode* oc ) /* And the decision is ... */ if (symbol->addr != NULL) { - ASSERT(nm != NULL); + CHECK(nm != NULL); /* Acquire! */ if (!isLocal) { @@ -1045,7 +1050,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, break; } } - ASSERT(stab != NULL); + CHECK(stab != NULL); targ = (Elf_Word*)oc->sections[target_shndx].start; IF_DEBUG(linker,debugBelch( @@ -1251,7 +1256,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, result = ((S + A) | T) - P; result &= ~1; // Clear thumb indicator bit - ASSERT(isInt(26, result)); /* X in range */ + CHECK(isInt(26, result)); /* X in range */ } // Update the branch target @@ -1426,7 +1431,7 @@ do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC, case COMPAT_R_ARM_GOT_PREL: { int32_t A = *pP; void* GOT_S = symbol->got_addr; - ASSERT(GOT_S); + CHECK(GOT_S); *(uint32_t *)P = (uint32_t) GOT_S + A - P; break; } @@ -1552,21 +1557,21 @@ do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC, case R_SPARC_WDISP30: w1 = *pP & 0xC0000000; w2 = (Elf_Word)((value - P) >> 2); - ASSERT((w2 & 0xC0000000) == 0); + CHECK((w2 & 0xC0000000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_HI22: w1 = *pP & 0xFFC00000; w2 = (Elf_Word)(value >> 10); - ASSERT((w2 & 0xFFC00000) == 0); + CHECK((w2 & 0xFFC00000) == 0); w1 |= w2; *pP = w1; break; case R_SPARC_LO10: w1 = *pP & ~0x3FF; w2 = (Elf_Word)(value & 0x3FF); - ASSERT((w2 & ~0x3FF) == 0); + CHECK((w2 & ~0x3FF) == 0); w1 |= w2; *pP = w1; break; @@ -1866,13 +1871,13 @@ ocResolve_ELF ( ObjectCode* oc ) Elf_Word secno = symbol->elf_sym->st_shndx; #if defined(SHN_XINDEX) if (secno == SHN_XINDEX) { - ASSERT(shndxTable); + CHECK(shndxTable); secno = shndxTable[i]; } #endif - ASSERT(symbol->elf_sym->st_name == 0); - ASSERT(symbol->elf_sym->st_value == 0); - ASSERT(0x0 != oc->sections[ secno ].start); + CHECK(symbol->elf_sym->st_name == 0); + CHECK(symbol->elf_sym->st_value == 0); + CHECK(0x0 != oc->sections[ secno ].start); symbol->addr = oc->sections[ secno ].start; } } @@ -1946,7 +1951,7 @@ int ocRunInit_ELF( ObjectCode *oc ) init_start = (init_t*)init_startC; init_end = (init_t*)(init_startC + shdr[i].sh_size); for (init = init_start; init < init_end; init++) { - ASSERT(0x0 != *init); + CHECK(0x0 != *init); (*init)(argc, argv, envv); } } @@ -1969,6 +1974,143 @@ int ocRunInit_ELF( ObjectCode *oc ) return 1; } +/* + * Shared object loading + */ + +static int loadNativeObjCb_(struct dl_phdr_info *info, + size_t _size GNUC3_ATTRIBUTE(__unused__), void *data) { + ObjectCode* nc = (ObjectCode*) data; + + // This logic mimicks _dl_addr_inside_object from glibc + // For reference: + // int + // internal_function + // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) + // { + // int n = l->l_phnum; + // const ElfW(Addr) reladdr = addr - l->l_addr; + // + // while (--n >= 0) + // if (l->l_phdr[n].p_type == PT_LOAD + // && reladdr - l->l_phdr[n].p_vaddr >= 0 + // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) + // return 1; + // return 0; + // } + + if ((void*) info->dlpi_addr == nc->l_addr) { + int n = info->dlpi_phnum; + while (--n >= 0) { + if (info->dlpi_phdr[n].p_type == PT_LOAD) { + NativeCodeRange* ncr = + stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); + ncr->start = (void*) ((char*) nc->l_addr + info->dlpi_phdr[n].p_vaddr); + ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); + + ncr->next = nc->nc_ranges; + nc->nc_ranges = ncr; + } + } + } + return 0; +} + +static void copyErrmsg(char** errmsg_dest, char* errmsg) { + if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; + *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); + strcpy(*errmsg_dest, errmsg); +} + +// need dl_mutex +void freeNativeCode_ELF (ObjectCode *nc) { + dlclose(nc->dlopen_handle); + + NativeCodeRange *ncr = nc->nc_ranges; + while (ncr) { + NativeCodeRange* last_ncr = ncr; + ncr = ncr->next; + stgFree(last_ncr); + } +} + +void * loadNativeObj_ELF (pathchar *path, char **errmsg) +{ + ObjectCode* nc; + void *hdl, *retval; + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); + + retval = NULL; + ACQUIRE_LOCK(&dl_mutex); + + /* Loading the same object multiple times will lead to chaos + * as we will have two ObjectCodes but one underlying dlopen + * handle. Fail if this happens. + */ + if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { + copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); + goto dlopen_fail; + } + + nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, false, NULL, 0); + + foreignExportsLoadingObject(nc); + hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); + foreignExportsFinishedLoadingObject(); + if (hdl == NULL) { + /* dlopen failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlopen_fail; + } + + struct link_map *map; + if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { + /* dlinfo failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlinfo_fail; + } + + nc->l_addr = (void*) map->l_addr; + nc->dlopen_handle = hdl; + hdl = NULL; // pass handle ownership to nc + + dl_iterate_phdr(loadNativeObjCb_, nc); + if (!nc->nc_ranges) { + copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); + goto dl_iterate_phdr_fail; + } + + insertOCSectionIndices(nc); + + nc->next_loaded_object = loaded_objects; + loaded_objects = nc; + + retval = nc->dlopen_handle; + +#if defined(PROFILING) + // collect any new cost centres that were defined in the loaded object. + refreshProfilingCCSs(); +#endif + + goto success; + +dl_iterate_phdr_fail: + // already have dl_mutex + freeNativeCode_ELF(nc); +dlinfo_fail: + if (hdl) dlclose(hdl); +dlopen_fail: +success: + + RELEASE_LOCK(&dl_mutex); + + IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); + + return retval; +} + + /* * PowerPC & X86_64 ELF specifics */ ===================================== rts/linker/Elf.h ===================================== @@ -14,5 +14,7 @@ int ocGetNames_ELF ( ObjectCode* oc ); int ocResolve_ELF ( ObjectCode* oc ); int ocRunInit_ELF ( ObjectCode* oc ); int ocAllocateExtras_ELF ( ObjectCode *oc ); +void freeNativeCode_ELF ( ObjectCode *nc ); +void *loadNativeObj_ELF ( pathchar *path, char **errmsg ); #include "EndPrivate.h" ===================================== rts/linker/M32Alloc.c ===================================== @@ -81,6 +81,7 @@ The allocator manages two kinds of allocations: * small allocations, which are allocated into a set of "nursery" pages (recorded in m32_allocator_t.pages; the size of the set is <= M32_MAX_PAGES) + * large allocations are those larger than a page and are mapped directly Each page (or the first page of a large allocation) begins with a m32_page_t @@ -126,7 +127,9 @@ code accordingly). To avoid unnecessary mapping/unmapping we maintain a global list of free pages (which can grow up to M32_MAX_FREE_PAGE_POOL_SIZE long). Pages on this list have the usual m32_page_t header and are linked together with -m32_page_t.free_page.next. +m32_page_t.free_page.next. When run out of free pages we allocate a chunk of +M32_MAP_PAGES to both avoid fragmenting our address space and amortize the +runtime cost of the mapping. The allocator is *not* thread-safe. @@ -139,7 +142,12 @@ The allocator is *not* thread-safe. * M32 ALLOCATOR (see Note [M32 Allocator] ***************************************************************************/ +/* How many open pages each allocator will keep around? */ #define M32_MAX_PAGES 32 +/* How many pages should we map at once when re-filling the free page pool? */ +#define M32_MAP_PAGES 32 +/* Upper bound on the number of pages to keep in the free page pool */ +#define M32_MAX_FREE_PAGE_POOL_SIZE 64 /** * Page header @@ -204,7 +212,6 @@ struct m32_allocator_t { * * We keep a small pool of free pages around to avoid fragmentation. */ -#define M32_MAX_FREE_PAGE_POOL_SIZE 16 struct m32_page_t *m32_free_page_pool = NULL; unsigned int m32_free_page_pool_size = 0; // TODO @@ -250,18 +257,33 @@ m32_release_page(struct m32_page_t *page) static struct m32_page_t * m32_alloc_page(void) { - if (m32_free_page_pool_size > 0) { - struct m32_page_t *page = m32_free_page_pool; - m32_free_page_pool = page->free_page.next; - m32_free_page_pool_size --; - return page; - } else { - struct m32_page_t *page = mmapForLinker(getPageSize(), PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); - if (page > (struct m32_page_t *) 0xffffffff) { + if (m32_free_page_pool_size == 0) { + /* + * Free page pool is empty; refill it with a new batch of M32_MAP_PAGES + * pages. + */ + const size_t pgsz = getPageSize(); + char *chunk = mmapForLinker(pgsz * M32_MAP_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS, -1, 0); + if (chunk > (char *) 0xffffffff) { barf("m32_alloc_page: failed to get allocation in lower 32-bits"); } - return page; + +#define GET_PAGE(i) ((struct m32_page_t *) (chunk + (i) * pgsz)) + for (int i=0; i < M32_MAP_PAGES; i++) { + struct m32_page_t *page = GET_PAGE(i); + page->free_page.next = GET_PAGE(i+1); + } + + GET_PAGE(M32_MAP_PAGES-1)->free_page.next = m32_free_page_pool; + m32_free_page_pool = (struct m32_page_t *) chunk; + m32_free_page_pool_size += M32_MAP_PAGES; +#undef GET_PAGE } + + struct m32_page_t *page = m32_free_page_pool; + m32_free_page_pool = page->free_page.next; + m32_free_page_pool_size --; + return page; } /** @@ -276,19 +298,6 @@ m32_allocator_new(bool executable) stgMallocBytes(sizeof(m32_allocator), "m32_new_allocator"); memset(alloc, 0, sizeof(struct m32_allocator_t)); alloc->executable = executable; - - // Preallocate the initial M32_MAX_PAGES to ensure that they don't - // fragment the memory. - size_t pgsz = getPageSize(); - char* bigchunk = mmapForLinker(pgsz * M32_MAX_PAGES, PROT_READ | PROT_WRITE, MAP_ANONYMOUS,-1,0); - if (bigchunk == NULL) - barf("m32_allocator_init: Failed to map"); - - int i; - for (i=0; ipages[i] = (struct m32_page_t *) (bigchunk + i*pgsz); - alloc->pages[i]->current_size = sizeof(struct m32_page_t); - } return alloc; } @@ -350,7 +359,9 @@ m32_allocator_push_filled_list(struct m32_page_t **head, struct m32_page_t *page void m32_allocator_flush(m32_allocator *alloc) { for (int i=0; ipages[i]->current_size == sizeof(struct m32_page_t)) { + if (alloc->pages[i] == NULL) { + continue; + } else if (alloc->pages[i]->current_size == sizeof(struct m32_page_t)) { // the page is empty, free it m32_release_page(alloc->pages[i]); } else { ===================================== rts/linker/MachO.c ===================================== @@ -252,7 +252,6 @@ resolveImports( "%s: unknown symbol `%s'", oc->fileName, symbol->name); return 0; } - ASSERT(addr); checkProddableBlock(oc, ((void**)(oc->image + sect->offset)) + i, @@ -847,7 +846,7 @@ relocateSection(ObjectCode* oc, int curSection) IF_DEBUG(linker, debugBelch(" : value = %p\n", (void *)symbol->nlist->n_value)); if ((symbol->nlist->n_type & N_TYPE) == N_SECT) { - ASSERT(symbol->addr != NULL); + CHECK(symbol->addr != NULL); value = (uint64_t) symbol->addr; IF_DEBUG(linker, debugBelch("relocateSection, defined external symbol %s, relocated address %p\n", nm, (void *)value)); @@ -949,29 +948,29 @@ relocateSection(ObjectCode* oc, int curSection) { if((int32_t)(value - baseValue) != (int64_t)(value - baseValue)) { - ASSERT(reloc->r_extern); + CHECK(reloc->r_extern); value = (uint64_t) &makeSymbolExtra(oc, reloc->r_symbolnum, value) -> jumpIsland; } - ASSERT((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); + CHECK((int32_t)(value - baseValue) == (int64_t)(value - baseValue)); type = X86_64_RELOC_SIGNED; } switch(type) { case X86_64_RELOC_UNSIGNED: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing += value; break; case X86_64_RELOC_SIGNED: case X86_64_RELOC_SIGNED_1: case X86_64_RELOC_SIGNED_2: case X86_64_RELOC_SIGNED_4: - ASSERT(reloc->r_pcrel); + CHECK(reloc->r_pcrel); thing += value - baseValue; break; case X86_64_RELOC_SUBTRACTOR: - ASSERT(!reloc->r_pcrel); + CHECK(!reloc->r_pcrel); thing -= value; break; default: ===================================== rts/linker/PEi386.c ===================================== @@ -1594,7 +1594,7 @@ ocGetNames_PEi386 ( ObjectCode* oc ) barf ("Could not allocate any heap memory from private heap."); } - ASSERT(section.size == 0 || section.info->virtualSize == 0); + CHECK(section.size == 0 || section.info->virtualSize == 0); sz = section.size; if (sz < section.info->virtualSize) sz = section.info->virtualSize; @@ -2032,7 +2032,7 @@ ocRunInit_PEi386 ( ObjectCode *oc ) getProgEnvv(&envc, &envv); Section section = *oc->info->init; - ASSERT(SECTIONKIND_INIT_ARRAY == section.kind); + CHECK(SECTIONKIND_INIT_ARRAY == section.kind); uint8_t *init_startC = section.start; init_t *init_start = (init_t*)init_startC; ===================================== rts/linker/PEi386Types.h ===================================== @@ -7,10 +7,6 @@ #include #include -/* Some forward declares. */ -struct Section; - - struct SectionFormatInfo { char* name; size_t alignment; ===================================== rts/linker/elf_got.c ===================================== @@ -136,10 +136,10 @@ verifyGot(ObjectCode * oc) { for(size_t i=0; i < symTab->n_symbols; i++) { ElfSymbol * symbol = &symTab->symbols[i]; if(symbol->got_addr) { - ASSERT((void*)(*(void**)symbol->got_addr) - == (void*)symbol->addr); + CHECK((void*)(*(void**)symbol->got_addr) + == (void*)symbol->addr); } - ASSERT(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); + CHECK(0 == ((uintptr_t)symbol->addr & 0xffff000000000000)); } } return EXIT_SUCCESS; ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -6,7 +6,6 @@ #include "elf_plt.h" #include -#include #if defined(aarch64_HOST_ARCH) @@ -71,15 +70,15 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { *(uint64_t*)P = (uint64_t)addend; break; case COMPAT_R_AARCH64_ABS32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); case COMPAT_R_AARCH64_PREL32: - assert(isInt64(32, addend)); + CHECK(isInt64(32, addend)); *(uint32_t*)P = (uint32_t)addend; break; case COMPAT_R_AARCH64_ABS16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); case COMPAT_R_AARCH64_PREL16: - assert(isInt64(16, addend)); + CHECK(isInt64(16, addend)); *(uint16_t*)P = (uint16_t)addend; break; /* static aarch64 relocations */ @@ -95,8 +94,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { // imm64 = SignExtend(hi:lo:0x000,64) // Range is 21 bits + the 12 page relative bits // known to be 0. -2^32 <= X < 2^32 - assert(isInt64(21+12, addend)); - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t) (((uint64_t) addend << 17) & 0x60000000) @@ -106,7 +105,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { /* - control flow relocations */ case COMPAT_R_AARCH64_JUMP26: /* relocate b ... */ case COMPAT_R_AARCH64_CALL26: { /* relocate bl ... */ - assert(isInt64(26+2, addend)); /* X in range */ + CHECK(isInt64(26+2, addend)); /* X in range */ *(inst_t *)P = (*(inst_t *)P & 0xfc000000) /* keep upper 6 (32-6) * bits */ | ((uint32_t)(addend >> 2) & 0x03ffffff); @@ -114,8 +113,8 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { } case COMPAT_R_AARCH64_ADR_GOT_PAGE: { /* range is -2^32 <= X < 2^32 */ - assert(isInt64(21+12, addend)); /* X in range */ - assert((addend & 0xfff) == 0); /* page relative */ + CHECK(isInt64(21+12, addend)); /* X in range */ + CHECK((addend & 0xfff) == 0); /* page relative */ *(inst_t *)P = (*(inst_t *)P & 0x9f00001f) | (inst_t)(((uint64_t)addend << 17) & 0x60000000) // lo @@ -149,10 +148,10 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { FALLTHROUGH; case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { if(exp_shift == -1) { - assert( (addend & 7) == 0 ); + CHECK( (addend & 7) == 0 ); exp_shift = 3; } - assert((addend & 0xfff) == addend); + CHECK((addend & 0xfff) == addend); int shift = 0; if(isLoadStore(P)) { /* bits 31, 30 encode the size. */ @@ -161,7 +160,7 @@ encodeAddendAarch64(Section * section, Elf_Rel * rel, int64_t addend) { shift = 4; } } - assert(addend == 0 || exp_shift == shift); + CHECK(addend == 0 || exp_shift == shift); *(inst_t *)P = (*(inst_t *)P & 0xffc003ff) | ((inst_t)(addend >> shift << 10) & 0x003ffc00); break; @@ -188,12 +187,12 @@ computeAddend(Section * section, Elf_Rel * rel, /* Position where something is relocated */ addr_t P = (addr_t)((uint8_t*)section->start + rel->r_offset); - assert(0x0 != P); - assert((uint64_t)section->start <= P); - assert(P <= (uint64_t)section->start + section->size); + CHECK(0x0 != P); + CHECK((uint64_t)section->start <= P); + CHECK(P <= (uint64_t)section->start + section->size); /* Address of the symbol */ addr_t S = (addr_t) symbol->addr; - assert(0x0 != S); + CHECK(0x0 != S); /* GOT slot for the symbol */ addr_t GOT_S = (addr_t) symbol->got_addr; @@ -243,16 +242,16 @@ computeAddend(Section * section, Elf_Rel * rel, } } - assert(0 == (0xffff000000000000 & S)); + CHECK(0 == (0xffff000000000000 & S)); V = S + A - P; - assert(isInt64(26+2, V)); /* X in range */ + CHECK(isInt64(26+2, V)); /* X in range */ } return V; } - case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: assert(0 == ((S+A) & 0x0f)); - case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: assert(0 == ((S+A) & 0x07)); - case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: assert(0 == ((S+A) & 0x03)); - case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: assert(0 == ((S+A) & 0x01)); + case COMPAT_R_AARCH64_LDST128_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x0f)); + case COMPAT_R_AARCH64_LDST64_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x07)); + case COMPAT_R_AARCH64_LDST32_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x03)); + case COMPAT_R_AARCH64_LDST16_ABS_LO12_NC: CHECK(0 == ((S+A) & 0x01)); case COMPAT_R_AARCH64_LDST8_ABS_LO12_NC: /* type: static, class: aarch64, op: S + A */ return (S + A) & 0xfff; @@ -266,12 +265,12 @@ computeAddend(Section * section, Elf_Rel * rel, // TODO: fix this story proper, so that the transformation // makes sense without resorting to: everyone else // does it like this as well. - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return Page(GOT_S+A) - Page(P); } case COMPAT_R_AARCH64_LD64_GOT_LO12_NC: { // G(GDAT(S+A)) - assert(0x0 != GOT_S); + CHECK(0x0 != GOT_S); return (GOT_S + A) & 0xfff; } default: @@ -297,7 +296,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); + CHECK(0x0 != symbol); /* decode implicit addend */ int64_t addend = decodeAddendAarch64(targetSection, rel); @@ -323,8 +322,8 @@ relocateObjectCodeAarch64(ObjectCode * oc) { relaTab->sectionHeader->sh_link, ELF64_R_SYM((Elf64_Xword)rel->r_info)); - assert(0x0 != symbol); - assert(0x0 != symbol->addr); + CHECK(0x0 != symbol); + CHECK(0x0 != symbol->addr); /* take explicit addend */ int64_t addend = rel->r_addend; ===================================== rts/win32/veh_excn.c ===================================== @@ -10,7 +10,6 @@ #include "ghcconfig.h" #include "veh_excn.h" #include "LinkerInternals.h" -#include #include #include #include @@ -195,7 +194,7 @@ void __register_hs_exception_handler( void ) __hs_handle = AddVectoredContinueHandler(CALL_LAST, __hs_exception_handler); // should the handler not be registered this will return a null. - assert(__hs_handle); + CHECK(__hs_handle); // Register for an exception filter to ensure the continue handler gets // hit if no one handled the exception. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be04dc9b63621f4500d31126df1701d14f3abf83...0b4d31339aff7f0a60fbf409a2637de8809a6572 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/be04dc9b63621f4500d31126df1701d14f3abf83...0b4d31339aff7f0a60fbf409a2637de8809a6572 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 Mon Nov 30 16:47:03 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Mon, 30 Nov 2020 11:47:03 -0500 Subject: [Git][ghc/ghc][wip/cfuneqcan-refactor] 36 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc52207a4d85_86c113040b010191c0@gitlab.mail> Richard Eisenberg pushed to branch wip/cfuneqcan-refactor at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 1bc104b0 by Ben Gamari at 2020-11-29T15:33:18-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - e992ea84 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - e82cd140 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 35a5207e by GHC GitLab CI at 2020-11-29T15:33:54-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 0120829f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 8a4d8fb6 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 2793cfdc by GHC GitLab CI at 2020-11-29T15:33:54-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - e391a16f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 60d088ab by Ben Gamari at 2020-11-29T15:33:54-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 3aa60362 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 8d304a99 by Ben Gamari at 2020-11-30T10:15:22-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - b6629289 by Ben Gamari at 2020-11-30T10:15:58-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 9f4efa6a by Ben Gamari at 2020-11-30T10:15:58-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 0f8a4655 by Ryan Scott at 2020-11-30T10:16:34-05:00 Allow deploy:pages job to fail See #18973. - - - - - 636db9ef by Richard Eisenberg at 2020-11-30T11:42:40-05:00 Move core flattening algorithm to Core.Unify This sets the stage for a later change, where this algorithm will be needed from GHC.Core.InstEnv. This commit also splits GHC.Core.Map into GHC.Core.Map.Type and GHC.Core.Map.Expr, in order to avoid module import cycles with GHC.Core. - - - - - da912d0a by Richard Eisenberg at 2020-11-30T11:42:40-05:00 Bump the # of commits searched for perf baseline The previous value of 75 meant that a feature branch with more than 75 commits would get spurious CI passes. This affects #18692, but does not fix that ticket, because if a baseline cannot be found, we should fail, not succeed. - - - - - 50b22545 by Richard Eisenberg at 2020-11-30T11:42:41-05:00 Remove flattening variables This patch redesigns the flattener to simplify type family applications directly instead of using flattening meta-variables and skolems. The key new innovation is the CanEqLHS type and the new CEqCan constraint (Ct). A CanEqLHS is either a type variable or exactly-saturated type family application; either can now be rewritten using a CEqCan constraint in the inert set. Because the flattener no longer reduces all type family applications to variables, there was some performance degradation if a lengthy type family application is now flattened over and over (not making progress). To compensate, this patch contains some extra optimizations in the flattener, leading to a number of performance improvements. Close #18875. Close #18910. There are many extra parts of the compiler that had to be affected in writing this patch: * The family-application cache (formerly the flat-cache) sometimes stores coercions built from Given inerts. When these inerts get kicked out, we must kick out from the cache as well. (This was, I believe, true previously, but somehow never caused trouble.) Kicking out from the cache requires adding a filterTM function to TrieMap. * This patch obviates the need to distinguish "blocking" coercion holes from non-blocking ones (which, previously, arose from CFunEqCans). There is thus some simplification around coercion holes. * Extra commentary throughout parts of the code I read through, to preserve the knowledge I gained while working. * A change in the pure unifier around unifying skolems with other types. Unifying a skolem now leads to SurelyApart, not MaybeApart, as documented in Note [Binding when looking up instances] in GHC.Core.InstEnv. * Some more use of MCoercion where appropriate. * Previously, class-instance lookup automatically noticed that e.g. C Int was a "unifier" to a target [W] C (F Bool), because the F Bool was flattened to a variable. Now, a little more care must be taken around checking for unifying instances. * Previously, tcSplitTyConApp_maybe would split (Eq a => a). This is silly, because (=>) is not a tycon in Haskell. Fixed now, but there are some knock-on changes in e.g. TrieMap code and in the canonicaliser. * New function anyFreeVarsOf{Type,Co} to check whether a free variable satisfies a certain predicate. * Type synonyms now remember whether or not they are "forgetful"; a forgetful synonym drops at least one argument. This is useful when flattening; see flattenView. * The pattern-match completeness checker invokes the solver. This invocation might need to look through newtypes when checking representational equality. Thus, the desugarer needs to keep track of the in-scope variables to know what newtype constructors are in scope. I bet this bug was around before but never noticed. * Extra-constraints wildcards are no longer simplified before printing. See Note [Do not simplify ConstraintHoles] in GHC.Tc.Solver. * Whether or not there are Given equalities has become slightly subtler. See the new HasGivenEqs datatype. * Note [Type variable cycles in Givens] in GHC.Tc.Solver.Canonical explains a significant new wrinkle in the new approach. * See Note [What might match later?] in GHC.Tc.Solver.Interact, which explains the fix to #18910. * The inert_count field of InertCans wasn't actually used, so I removed it. Though I (Richard) did the implementation, Simon PJ was very involved in design and review. This updates the Haddock submodule to avoid #18932 by adding a type signature. ------------------------- Metric Decrease: T12227 T5030 T9872a T9872b T9872c Metric Increase: T9872d ------------------------- - - - - - 973fb509 by Richard Eisenberg at 2020-11-30T11:42:41-05:00 Rename the flattener to become the rewriter. Now that flattening doesn't produce flattening variables, it's not really flattening anything: it's rewriting. This change also means that the rewriter can no longer be confused the core flattener (in GHC.Core.Unify), which is sometimes used during type-checking. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/FamInstEnv.hs - compiler/GHC/Core/InstEnv.hs - + compiler/GHC/Core/Map/Expr.hs - compiler/GHC/Core/Map.hs → compiler/GHC/Core/Map/Type.hs - compiler/GHC/Core/Opt/CSE.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbdf67348305ec61714e974a1e8980a2be0947af...973fb5098dfe197456bc1670f6ce62265ab6f6aa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cbdf67348305ec61714e974a1e8980a2be0947af...973fb5098dfe197456bc1670f6ce62265ab6f6aa 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 Mon Nov 30 16:55:12 2020 From: gitlab at gitlab.haskell.org (Richard Eisenberg) Date: Mon, 30 Nov 2020 11:55:12 -0500 Subject: [Git][ghc/ghc] Pushed new branch wip/T19000 Message-ID: <5fc523f0e737f_86cf7c522c1028918@gitlab.mail> Richard Eisenberg pushed new branch wip/T19000 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T19000 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 Mon Nov 30 17:22:03 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 12:22:03 -0500 Subject: [Git][ghc/ghc][wip/no-fptr] Sized Message-ID: <5fc52a3b51664_86c15c5d38810414d1@gitlab.mail> Ben Gamari pushed to branch wip/no-fptr at Glasgow Haskell Compiler / GHC Commits: 29bb4fd6 by Ben Gamari at 2020-11-30T12:21:50-05:00 Sized - - - - - 1 changed file: - libraries/base/GHC/ForeignPtr/Ops.hs Changes: ===================================== libraries/base/GHC/ForeignPtr/Ops.hs ===================================== @@ -62,17 +62,17 @@ withFP fp f = peekWord8ForeignPtr :: ForeignPtr ty -> Int -> IO Word8 peekWord8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readWord8OffAddr# addr d s0 of - (# s1, r #) -> (# s1, W8# r #) + (# s1, r #) -> (# s1, W8# (narrowWord8# r) #) peekWord16ForeignPtr :: ForeignPtr ty -> Int -> IO Word16 peekWord16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readWord16OffAddr# addr d s0 of - (# s1, r #) -> (# s1, W16# r #) + (# s1, r #) -> (# s1, W16# (narrowWord16# r) #) peekWord32ForeignPtr :: ForeignPtr ty -> Int -> IO Word32 peekWord32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readWord32OffAddr# addr d s0 of - (# s1, r #) -> (# s1, W32# r #) + (# s1, r #) -> (# s1, W32# (narrowWord32# r) #) peekWord64ForeignPtr :: ForeignPtr ty -> Int -> IO Word64 peekWord64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> @@ -87,17 +87,17 @@ peekWordForeignPtr fp (I# d) = withFP fp $ \addr s0 -> peekInt8ForeignPtr :: ForeignPtr ty -> Int -> IO Int8 peekInt8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readInt8OffAddr# addr d s0 of - (# s1, r #) -> (# s1, I8# r #) + (# s1, r #) -> (# s1, I8# (narrowInt8# r) #) peekInt16ForeignPtr :: ForeignPtr ty -> Int -> IO Int16 peekInt16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readInt16OffAddr# addr d s0 of - (# s1, r #) -> (# s1, I16# r #) + (# s1, r #) -> (# s1, I16# (narrowInt16# r) #) peekInt32ForeignPtr :: ForeignPtr ty -> Int -> IO Int32 peekInt32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readInt32OffAddr# addr d s0 of - (# s1, r #) -> (# s1, I32# r #) + (# s1, r #) -> (# s1, I32# (narrowInt32# r) #) peekInt64ForeignPtr :: ForeignPtr ty -> Int -> IO Int64 peekInt64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> @@ -116,17 +116,17 @@ peekCharForeignPtr fp (I# d) = withFP fp $ \addr s0 -> pokeWord8ForeignPtr :: ForeignPtr ty -> Int -> Word8 -> IO () pokeWord8ForeignPtr fp (I# d) (W8# n) = withFP fp $ \addr s0 -> - case writeWord8OffAddr# addr d n s0 of + case writeWord8OffAddr# addr d (extendWord8# n) s0 of s1 -> (# s1, () #) pokeWord16ForeignPtr :: ForeignPtr ty -> Int -> Word16 -> IO () pokeWord16ForeignPtr fp (I# d) (W16# n) = withFP fp $ \addr s0 -> - case writeWord16OffAddr# addr d n s0 of + case writeWord16OffAddr# addr d (extendWord16# n) s0 of s1 -> (# s1, () #) pokeWord32ForeignPtr :: ForeignPtr ty -> Int -> Word32 -> IO () pokeWord32ForeignPtr fp (I# d) (W32# n) = withFP fp $ \addr s0 -> - case writeWord32OffAddr# addr d n s0 of + case writeWord32OffAddr# addr d (extendWord32# n) s0 of s1 -> (# s1, () #) pokeWord64ForeignPtr :: ForeignPtr ty -> Int -> Word64 -> IO () @@ -141,17 +141,17 @@ pokeWordForeignPtr fp (I# d) (W# n) = withFP fp $ \addr s0 -> pokeInt8ForeignPtr :: ForeignPtr ty -> Int -> Int8 -> IO () pokeInt8ForeignPtr fp (I# d) (I8# n) = withFP fp $ \addr s0 -> - case writeInt8OffAddr# addr d n s0 of + case writeInt8OffAddr# addr d (extendInt8# n) s0 of s1 -> (# s1, () #) pokeInt16ForeignPtr :: ForeignPtr ty -> Int -> Int16 -> IO () pokeInt16ForeignPtr fp (I# d) (I16# n) = withFP fp $ \addr s0 -> - case writeInt16OffAddr# addr d n s0 of + case writeInt16OffAddr# addr d (extendInt16# n) s0 of s1 -> (# s1, () #) pokeInt32ForeignPtr :: ForeignPtr ty -> Int -> Int32 -> IO () pokeInt32ForeignPtr fp (I# d) (I32# n) = withFP fp $ \addr s0 -> - case writeInt32OffAddr# addr d n s0 of + case writeInt32OffAddr# addr d (extendInt32# n) s0 of s1 -> (# s1, () #) pokeInt64ForeignPtr :: ForeignPtr ty -> Int -> Int64 -> IO () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/29bb4fd63ea808ab848afa08fab95f9cdac0df85 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/29bb4fd63ea808ab848afa08fab95f9cdac0df85 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 Mon Nov 30 17:27:15 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 12:27:15 -0500 Subject: [Git][ghc/ghc][wip/tsan-ghc-8.10] 79 commits: CmmToLlvm: Declare signature for memcmp Message-ID: <5fc52b738a4ee_86c111d4a0010421fa@gitlab.mail> Ben Gamari pushed to branch wip/tsan-ghc-8.10 at Glasgow Haskell Compiler / GHC Commits: 70ac4ed8 by Moritz Angermann at 2020-11-25T10:41:34+08:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - 7b8856f6 by Ben Gamari at 2020-11-30T12:21:35-05:00 SMP.h: Add C11-style atomic operations - - - - - 15116c24 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - 6f51dabf by Ben Gamari at 2020-11-30T12:21:35-05:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - d1b8cb4f by Ben Gamari at 2020-11-30T12:21:35-05:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - 88eb3e67 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts/Task: Make comments proper Notes - - - - - a4e20e6d by Ben Gamari at 2020-11-30T12:21:35-05:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - 3e979160 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 70d00e09 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts/ClosureMaros: Use relaxed atomics - - - - - f065898a by Ben Gamari at 2020-11-30T12:21:35-05:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - 51f48fd2 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 9316c4a4 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 53f24b8a by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Annotate benign race in waitForCapability - - - - - 4a3597b4 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 1de8c691 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Add assertions for task ownership of capabilities - - - - - b7d9eb41 by Ben Gamari at 2020-11-30T12:21:35-05:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 47423a5d by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Mitigate races in capability interruption logic - - - - - c858edad by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - c2a64f77 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 86598ea5 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 7111ed98 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - d1667414 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Eliminate data races on pending_sync - - - - - c7085820 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - 7b479a36 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Avoid data races in message handling - - - - - 367df852 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - 2e3c82f3 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/ThreadPaused: Avoid data races - - - - - fae4a32d by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Schedule: Eliminate data races in run queue management - - - - - 4f3ad188 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Eliminate shutdown data race on task counters - - - - - 3e595d5a by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 5099274d by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Messages: Annotate benign race - - - - - 1236fbe0 by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/RaiseAsync: Synchronize what_next read - - - - - 476c4a8a by Ben Gamari at 2020-11-30T12:21:36-05:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - 8e8c7adf by Ben Gamari at 2020-11-30T12:21:36-05:00 Disable flawed assertion - - - - - 3eebe524 by Ben Gamari at 2020-11-30T12:21:36-05:00 Document schedulePushWork race - - - - - cb1eb0e8 by Ben Gamari at 2020-11-30T12:21:36-05:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - 9863350a by Ben Gamari at 2020-11-30T12:21:36-05:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - f81c1b02 by Ben Gamari at 2020-11-30T12:21:36-05:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - b5855f96 by GHC GitLab CI at 2020-11-30T12:21:36-05:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - 21130520 by GHC GitLab CI at 2020-11-30T12:21:36-05:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - 227dc381 by Ben Gamari at 2020-11-30T12:21:36-05:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - 3930c9fe by Ben Gamari at 2020-11-30T12:21:36-05:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - c7424362 by Ben Gamari at 2020-11-30T12:21:36-05:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - 8b418d39 by Ben Gamari at 2020-11-30T12:21:36-05:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - cd0e033b by Ben Gamari at 2020-11-30T12:21:36-05:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 12bf63a7 by Ben Gamari at 2020-11-30T12:21:36-05:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f70cab90 by Ben Gamari at 2020-11-30T12:27:05-05:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 398f1ea9 by Ben Gamari at 2020-11-30T12:27:05-05:00 rts/BlockAlloc: Use relaxed operations - - - - - a3d1f39b by Ben Gamari at 2020-11-30T12:27:05-05:00 rts: Rework handling of mutlist scavenging statistics - - - - - e3526565 by Ben Gamari at 2020-11-30T12:27:05-05:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - e1c1552f by Ben Gamari at 2020-11-30T12:27:05-05:00 rts/Storage: Use atomics - - - - - 5182aac5 by Ben Gamari at 2020-11-30T12:27:05-05:00 rts/Updates: Use proper atomic operations - - - - - 72481992 by Ben Gamari at 2020-11-30T12:27:05-05:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - 199419f6 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/GC: Use atomics - - - - - d7cd64b9 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Use RELEASE ordering in unlockClosure - - - - - 26638062 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/Storage: Accept races on heap size counters - - - - - 5d82ecd1 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - 3f519f3f by GHC GitLab CI at 2020-11-30T12:27:06-05:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - a6938732 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - 120a1fba by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Use relaxed ordering on spinlock counters - - - - - dcc0916a by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 2131a961 by Ben Gamari at 2020-11-30T12:27:06-05:00 Strengthen ordering in releaseGCThreads - - - - - e90d9cfa by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - e52ab4fa by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Use relaxed atomics for whitehole spin stats - - - - - e8705f29 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - 2af2f0be by GHC GitLab CI at 2020-11-30T12:27:06-05:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 469872ec by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 5948bc76 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - 311b0184 by Ben Gamari at 2020-11-30T12:27:06-05:00 Mitigate data races in event manager startup/shutdown - - - - - 513e9fe6 by Ben Gamari at 2020-11-30T12:27:06-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - 899c985c by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Accept benign races in Proftimer - - - - - 270ad47f by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 37601b97 by Ben Gamari at 2020-11-30T12:27:06-05:00 Fix #17289 - - - - - 4718c285 by Ben Gamari at 2020-11-30T12:27:06-05:00 suppress #17289 (ticker) race - - - - - 982993ad by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - 95a8bd76 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 4b5f3764 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - e7b0b74f by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 1fed9ab5 by Ben Gamari at 2020-11-30T12:27:06-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - f6f0343b by Ben Gamari at 2020-11-30T12:27:06-05:00 rts/Stats: Reintroduce mut_user_time Fix the previous backport; this function was dead code in master but is still needed due to ProfHeap.c in ghc-8.10. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/llvmGen/LlvmCodeGen/Base.hs - hadrian/hadrian.cabal - hadrian/src/Flavour.hs - hadrian/src/Settings.hs - + hadrian/src/Settings/Flavours/ThreadSanitizer.hs - includes/Rts.h - includes/rts/OSThreads.h - includes/rts/SpinLock.h - includes/rts/StablePtr.h - + includes/rts/TSANUtils.h - includes/rts/storage/ClosureMacros.h - includes/rts/storage/Closures.h - includes/rts/storage/GC.h - includes/stg/SMP.h - libraries/base/GHC/Event/Control.hs - + rts/.tsan-suppressions - rts/Capability.c - rts/Capability.h - rts/Messages.c - rts/Proftimer.c - rts/RaiseAsync.c - rts/RtsStartup.c - rts/SMPClosureOps.h - rts/STM.c - rts/Schedule.c - rts/Schedule.h - rts/Sparks.c - + rts/SpinLock.c - rts/StablePtr.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3152aa057644dac7b8df4c30c3034d3ab180748...f6f0343bd8dc1ea5d8085ed551bcb3400b72b694 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a3152aa057644dac7b8df4c30c3034d3ab180748...f6f0343bd8dc1ea5d8085ed551bcb3400b72b694 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 Mon Nov 30 19:05:50 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 14:05:50 -0500 Subject: [Git][ghc/ghc][wip/win32-m32] 28 commits: Hadrian: fix detection of ghc-pkg for cross-compilers Message-ID: <5fc5428e4c84e_86cbee25901057694@gitlab.mail> Ben Gamari pushed to branch wip/win32-m32 at Glasgow Haskell Compiler / GHC Commits: 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 1bc104b0 by Ben Gamari at 2020-11-29T15:33:18-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - e992ea84 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - e82cd140 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 35a5207e by GHC GitLab CI at 2020-11-29T15:33:54-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 0120829f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 8a4d8fb6 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 2793cfdc by GHC GitLab CI at 2020-11-29T15:33:54-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - e391a16f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 60d088ab by Ben Gamari at 2020-11-29T15:33:54-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 3aa60362 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 8d304a99 by Ben Gamari at 2020-11-30T10:15:22-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - b6629289 by Ben Gamari at 2020-11-30T10:15:58-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 9f4efa6a by Ben Gamari at 2020-11-30T10:15:58-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 0f8a4655 by Ryan Scott at 2020-11-30T10:16:34-05:00 Allow deploy:pages job to fail See #18973. - - - - - 401d8656 by Ben Gamari at 2020-11-30T14:05:37-05:00 rts: Introduce mmapAnonForLinker Previously most of the uses of mmapForLinker were mapping anonymous memory, resulting in a great deal of unnecessary repetition. Factor this out into a new helper. Also fixes a few places where error checking was missing or suboptimal. - - - - - fa3ea183 by Ben Gamari at 2020-11-30T14:05:39-05:00 rts/linker: Introduce munmapForLinker Consolidates munmap calls to ensure consistent error handling. - - - - - d08f24f4 by Ben Gamari at 2020-11-30T14:05:39-05:00 rts/Linker: Introduce Windows implementations for mmapForLinker, et al. - - - - - e08deacd by Ben Gamari at 2020-11-30T14:05:39-05:00 rts/m32: Introduce NEEDS_M32 macro Instead of relying on RTS_LINKER_USE_MMAP - - - - - 61c3b2c8 by Ben Gamari at 2020-11-30T14:05:39-05:00 rts/linker: Use m32 to allocate symbol extras in PEi386 - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Utils/Error.hs - hadrian/src/Hadrian/Oracles/Cabal/Rules.hs - hadrian/src/Settings/Builders/GhcPkg.hs - includes/rts/storage/ClosureMacros.h - libraries/ghc-heap/GHC/Exts/Heap.hs - libraries/ghc-heap/GHC/Exts/Heap/Closures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures.hs - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/FFIClosures_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo.hs - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingDisabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/PeekProfInfo_ProfilingEnabled.hsc - + libraries/ghc-heap/GHC/Exts/Heap/ProfInfo/Types.hs - libraries/ghc-heap/ghc-heap.cabal.in - + libraries/ghc-heap/tests/TestUtils.hs - libraries/ghc-heap/tests/all.T - + libraries/ghc-heap/tests/create_tso.c - + libraries/ghc-heap/tests/create_tso.h - + libraries/ghc-heap/tests/parse_tso_flags.hs - + libraries/ghc-heap/tests/tso_and_stack_closures.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/Run.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b70fa768dfcf58cbd67e9e2224791be1839c6945...61c3b2c8586eb299f95ea053fcf08e0548ff2a55 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b70fa768dfcf58cbd67e9e2224791be1839c6945...61c3b2c8586eb299f95ea053fcf08e0548ff2a55 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 Mon Nov 30 23:15:05 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 18:15:05 -0500 Subject: [Git][ghc/ghc][wip/keepAlive-the-return-of-the-primop] 37 commits: [Sized Cmm] properly retain sizes. Message-ID: <5fc57cf93a2ed_86c111d4a001064992@gitlab.mail> Ben Gamari pushed to branch wip/keepAlive-the-return-of-the-primop at Glasgow Haskell Compiler / GHC Commits: be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 373741f9 by Ben Gamari at 2020-11-30T10:08:57-05:00 base: Add unsafeWithForeignPtr - - - - - a32c5a10 by Ben Gamari at 2020-11-30T10:12:52-05:00 base: Introduce GHC.ForeignPtr.Ops module This contains a variety of peek/poke operations for ForeignPtr accesses. - - - - - 38766e93 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.IO.Buffer: Use ForeignPtr-specialised peek/poke - - - - - 24cd42a2 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.Data.ByteArray: Initial commit - - - - - 39cd7b51 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.Utils.Binary: Eliminate allocating withForeignPtr uses - - - - - 4c30f373 by Ben Gamari at 2020-11-30T10:12:52-05:00 base: Eliminate allocating withForeignPtrs from GHC.Event.Array - - - - - 46b45be9 by Ben Gamari at 2020-11-30T10:12:52-05:00 base: Use unsafeWithForeignPtr in GHC.IO.Buffer - - - - - 29d2bb26 by Ben Gamari at 2020-11-30T10:12:52-05:00 GHC.Event.Array: Use unsafeWithForeignPtr - - - - - 10db1230 by Ben Gamari at 2020-11-30T10:12:52-05:00 Bump bytestring submodule Teach it to use unsafeWithForeignPtr where appropriate. - - - - - 29bb4fd6 by Ben Gamari at 2020-11-30T12:21:50-05:00 Sized - - - - - 55c2f2d5 by Ben Gamari at 2020-11-30T12:23:52-05:00 genprimopcode: Add a second levity-polymorphic tyvar This will be needed shortly. - - - - - b865b43b by GHC GitLab CI at 2020-11-30T12:23:52-05:00 Introduce keepAlive primop - - - - - 7f9ff897 by Ben Gamari at 2020-11-30T12:23:52-05:00 base: Use keepAlive# in withForeignPtr - - - - - 7713e437 by Ben Gamari at 2020-11-30T12:23:52-05:00 Implement withByteArrayContents in terms of keepAlive# - - - - - 67aa197b by Ben Gamari at 2020-11-30T12:25:20-05:00 base: Implement GHC.ForeignPtr.Ops in terms of keepAlive# - - - - - 77819ff2 by Ben Gamari at 2020-11-30T12:25:20-05:00 base: Use keepAlive# in Foreign.Marshal.Alloc - - - - - 008e8eb5 by Ben Gamari at 2020-11-30T12:25:20-05:00 ghc-compact: Use keepAlive# in GHC.Compact.Serialized - - - - - 1720937c by Ben Gamari at 2020-11-30T12:25:20-05:00 testsuite: Accept - - - - - e88f492b by Ben Gamari at 2020-11-30T14:00:07-05:00 iFix it - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Expr.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Core.hs - compiler/GHC/Core/Opt/ConstantFold.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToByteCode.hs - compiler/GHC/CoreToStg/Prep.hs - + compiler/GHC/Data/ByteArray.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Runtime/Heap/Inspect.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Stg/Lift/Analysis.hs - compiler/GHC/StgToCmm/ArgRep.hs - compiler/GHC/StgToCmm/DataCon.hs - compiler/GHC/StgToCmm/Layout.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b7910e3fa09c1e9c0ce42bb600dd007bd1e79297...e88f492b462149616ca4a157f3b871247a575a07 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b7910e3fa09c1e9c0ce42bb600dd007bd1e79297...e88f492b462149616ca4a157f3b871247a575a07 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 Mon Nov 30 23:54:46 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 18:54:46 -0500 Subject: [Git][ghc/ghc][wip/no-fptr] Sized Message-ID: <5fc58646e544c_86cfd752bc10712ec@gitlab.mail> Ben Gamari pushed to branch wip/no-fptr at Glasgow Haskell Compiler / GHC Commits: 5e5f48e8 by Ben Gamari at 2020-11-30T18:54:39-05:00 Sized - - - - - 1 changed file: - libraries/base/GHC/ForeignPtr/Ops.hs Changes: ===================================== libraries/base/GHC/ForeignPtr/Ops.hs ===================================== @@ -62,17 +62,17 @@ withFP fp f = peekWord8ForeignPtr :: ForeignPtr ty -> Int -> IO Word8 peekWord8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readWord8OffAddr# addr d s0 of - (# s1, r #) -> (# s1, W8# r #) + (# s1, r #) -> (# s1, W8# (narrowWord8# r) #) peekWord16ForeignPtr :: ForeignPtr ty -> Int -> IO Word16 peekWord16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readWord16OffAddr# addr d s0 of - (# s1, r #) -> (# s1, W16# r #) + (# s1, r #) -> (# s1, W16# (narrowWord16# r) #) peekWord32ForeignPtr :: ForeignPtr ty -> Int -> IO Word32 peekWord32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readWord32OffAddr# addr d s0 of - (# s1, r #) -> (# s1, W32# r #) + (# s1, r #) -> (# s1, W32# (narrowWord32# r) #) peekWord64ForeignPtr :: ForeignPtr ty -> Int -> IO Word64 peekWord64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> @@ -87,17 +87,17 @@ peekWordForeignPtr fp (I# d) = withFP fp $ \addr s0 -> peekInt8ForeignPtr :: ForeignPtr ty -> Int -> IO Int8 peekInt8ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readInt8OffAddr# addr d s0 of - (# s1, r #) -> (# s1, I8# r #) + (# s1, r #) -> (# s1, I8# (narrowInt8# r) #) peekInt16ForeignPtr :: ForeignPtr ty -> Int -> IO Int16 peekInt16ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readInt16OffAddr# addr d s0 of - (# s1, r #) -> (# s1, I16# r #) + (# s1, r #) -> (# s1, I16# (narrowInt16# r) #) peekInt32ForeignPtr :: ForeignPtr ty -> Int -> IO Int32 peekInt32ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> case readInt32OffAddr# addr d s0 of - (# s1, r #) -> (# s1, I32# r #) + (# s1, r #) -> (# s1, I32# (narrowInt32# r) #) peekInt64ForeignPtr :: ForeignPtr ty -> Int -> IO Int64 peekInt64ForeignPtr fp (I# d) = withFP fp $ \addr s0 -> @@ -116,17 +116,17 @@ peekCharForeignPtr fp (I# d) = withFP fp $ \addr s0 -> pokeWord8ForeignPtr :: ForeignPtr ty -> Int -> Word8 -> IO () pokeWord8ForeignPtr fp (I# d) (W8# n) = withFP fp $ \addr s0 -> - case writeWord8OffAddr# addr d n s0 of + case writeWord8OffAddr# addr d (extendWord8# n) s0 of s1 -> (# s1, () #) pokeWord16ForeignPtr :: ForeignPtr ty -> Int -> Word16 -> IO () pokeWord16ForeignPtr fp (I# d) (W16# n) = withFP fp $ \addr s0 -> - case writeWord16OffAddr# addr d n s0 of + case writeWord16OffAddr# addr d (extendWord16# n) s0 of s1 -> (# s1, () #) pokeWord32ForeignPtr :: ForeignPtr ty -> Int -> Word32 -> IO () pokeWord32ForeignPtr fp (I# d) (W32# n) = withFP fp $ \addr s0 -> - case writeWord32OffAddr# addr d n s0 of + case writeWord32OffAddr# addr d (extendWord32# n) s0 of s1 -> (# s1, () #) pokeWord64ForeignPtr :: ForeignPtr ty -> Int -> Word64 -> IO () @@ -136,22 +136,22 @@ pokeWord64ForeignPtr fp (I# d) (W64# n) = withFP fp $ \addr s0 -> pokeWordForeignPtr :: ForeignPtr ty -> Int -> Word -> IO () pokeWordForeignPtr fp (I# d) (W# n) = withFP fp $ \addr s0 -> - case writeWord64OffAddr# addr d n s0 of + case writeWordOffAddr# addr d n s0 of s1 -> (# s1, () #) pokeInt8ForeignPtr :: ForeignPtr ty -> Int -> Int8 -> IO () pokeInt8ForeignPtr fp (I# d) (I8# n) = withFP fp $ \addr s0 -> - case writeInt8OffAddr# addr d n s0 of + case writeInt8OffAddr# addr d (extendInt8# n) s0 of s1 -> (# s1, () #) pokeInt16ForeignPtr :: ForeignPtr ty -> Int -> Int16 -> IO () pokeInt16ForeignPtr fp (I# d) (I16# n) = withFP fp $ \addr s0 -> - case writeInt16OffAddr# addr d n s0 of + case writeInt16OffAddr# addr d (extendInt16# n) s0 of s1 -> (# s1, () #) pokeInt32ForeignPtr :: ForeignPtr ty -> Int -> Int32 -> IO () pokeInt32ForeignPtr fp (I# d) (I32# n) = withFP fp $ \addr s0 -> - case writeInt32OffAddr# addr d n s0 of + case writeInt32OffAddr# addr d (extendInt32# n) s0 of s1 -> (# s1, () #) pokeInt64ForeignPtr :: ForeignPtr ty -> Int -> Int64 -> IO () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e5f48e8b7ff3574bcfce4c788827209caf37de0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e5f48e8b7ff3574bcfce4c788827209caf37de0 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 Mon Nov 30 23:56:42 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 18:56:42 -0500 Subject: [Git][ghc/ghc][wip/backports-9.0] 14 commits: WinIO: Small changes related to atomic request swaps. Message-ID: <5fc586baa0518_86c111d4a0010719b7@gitlab.mail> Ben Gamari pushed to branch wip/backports-9.0 at Glasgow Haskell Compiler / GHC Commits: 824332c4 by Andreas Klebinger at 2020-11-30T18:56:35-05:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. (cherry picked from commit 401a64b80fb210fa1b403afe5b28d16f961f21bc) - - - - - 7cb92dec by Krzysztof Gogolewski at 2020-11-30T18:56:35-05:00 Force argument in setIdMult (#18925) (cherry picked from commit 5506f1342e51bad71a7525ddad0650d1ac63afeb) - - - - - 77a239ec by Moritz Angermann at 2020-11-30T18:56:35-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. (cherry picked from commit 8887102fc4ed8ed1089c1aafd19bab424ad706f3) - - - - - 7da4e588 by Krzysztof Gogolewski at 2020-11-30T18:56:35-05:00 Export indexError from GHC.Ix (#18579) (cherry picked from commit 165352a2d163537afb01a835bccc7cd0a667410a) - - - - - 4b83b6a8 by Ben Gamari at 2020-11-30T18:56:35-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. (cherry picked from commit 9f40cf6ca9fb24dbc55f7eae43e2b89aa12bf251) - - - - - e0d7563a by Ben Gamari at 2020-11-30T18:56:35-05:00 testsuite: Add testcase for #18733 (cherry picked from commit 787e93ae141ae0f33bc36895494d48a2a5e49e08) - - - - - 3d59089b by Ben Gamari at 2020-11-30T18:56:35-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. (cherry picked from commit 5353fd500b1e92636cd9d45274585fd88a915ff6) - - - - - eaa632ba by Ben Gamari at 2020-11-30T18:56:35-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. (cherry picked from commit a1a75aa9be2c133dd1372a08eeb6a92c31688df7) - - - - - 0bba6516 by Ben Gamari at 2020-11-30T18:56:35-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label (cherry picked from commit 7c03cc5010999d0f0f9dfc549984023b3a1f2c8d) - - - - - be408b86 by Ben Gamari at 2020-11-30T18:56:35-05:00 rts/linker: Ensure that .rodata is aligned to 16 bytes Pulled out of !4310. - - - - - 3a09acdc by Ömer Sinan Ağacan at 2020-11-30T18:56:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. (cherry picked from commit c34a4b98b1f09ea3096d39a839a86f2d7185c796) - - - - - 01f5126b by Ray Shih at 2020-11-30T18:56:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. (cherry picked from commit 2782487f5f6ad9df4dc8725226a47f07fec77f9f) - - - - - a1a0ec33 by GHC GitLab CI at 2020-11-30T18:56:35-05:00 rts: Introduce highMemDynamic (cherry picked from commit 7a65f9e140906087273ce95f062775f18f6a708d) - - - - - cae06fc4 by GHC GitLab CI at 2020-11-30T18:56:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. (cherry picked from commit e9e1b2e75de17be47ab887a26943f5517a8463ac) - - - - - 30 changed files: - .gitlab-ci.yml - aclocal.m4 - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/Driver/Pipeline.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Platform/ARM64.hs → compiler/GHC/Platform/AArch64.hs - compiler/GHC/Platform/Regs.hs - compiler/GHC/Runtime/Linker.hs - compiler/GHC/Types/Var.hs - compiler/ghc.cabal.in - config.sub - includes/CodeGen.Platform.hs - includes/rts/Flags.h - includes/rts/Linker.h - includes/rts/storage/GC.h - libraries/base/GHC/Event/Internal.hs - libraries/base/GHC/Event/Windows.hsc - libraries/base/GHC/Ix.hs - libraries/base/GHC/Ptr.hs - libraries/ghc-boot/GHC/Platform.hs - libraries/ghci/GHCi/InfoTable.hsc - llvm-targets - rts/Adjustor.c The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65ea34e932a8b42c94228bebc636730aeac1b32e...cae06fc404b8be27bf0bab2b51e4343b23b896e9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65ea34e932a8b42c94228bebc636730aeac1b32e...cae06fc404b8be27bf0bab2b51e4343b23b896e9 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 Mon Nov 30 23:59:46 2020 From: gitlab at gitlab.haskell.org (Ben Gamari) Date: Mon, 30 Nov 2020 18:59:46 -0500 Subject: [Git][ghc/ghc][wip/ci-fixes] 326 commits: Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Message-ID: <5fc58772f1c2a_86c111d4a0010725b7@gitlab.mail> Ben Gamari pushed to branch wip/ci-fixes at Glasgow Haskell Compiler / GHC Commits: bc5de347 by Sebastian Graf at 2020-10-05T13:59:24-04:00 Inline `integerDecodeDouble#` and constant-fold `decodeDouble_Int64#` instead Currently, `integerDecodeDouble#` is known-key so that it can be recognised in constant folding. But that is very brittle and doesn't survive worker/wrapper, which we even do for `NOINLINE` things since #13143. Also it is a trade-off: The implementation of `integerDecodeDouble#` allocates an `Integer` box that never cancels aways if we don't inline it. Hence we recognise the `decodeDouble_Int64#` primop instead in constant folding, so that we can inline `integerDecodeDouble#`. As a result, `integerDecodeDouble#` no longer needs to be known-key. While doing so, I realised that we don't constant-fold `decodeFloat_Int#` either, so I also added a RULE for it. `integerDecodeDouble` is dead, so I deleted it. Part of #18092. This improves the 32-bit `realToFrac`/`toRational`: Metric Decrease: T10359 - - - - - 802b5e6f by Krzysztof Gogolewski at 2020-10-05T13:59:33-04:00 Fix linear types in TH splices (#18465) - - - - - 18a3ddf7 by Ben Gamari at 2020-10-05T13:59:33-04:00 rts: Fix integer width in TICK_BUMP_BY Previously `TICK_BUMP_BY` was defined as ```c #define TICK_BUMP_BY(ctr,n) CLong[ctr] = CLong[ctr] + n ``` Yet the tickers themselves were defined as `StgInt`s. This happened to work out correctly on Linux, where `CLong` is 64-bits. However, it failed on Windows, where `CLong` is 32-bits, resulting in #18782. Fixes #18783. - - - - - 5fc4243b by Rachel at 2020-10-07T14:59:45-04:00 Document profiling flags, warning flags, and no-pie - - - - - b41f7c38 by Andreas Klebinger at 2020-10-07T15:00:20-04:00 WinIO: Small changes related to atomic request swaps. Move the atomix exchange over the Ptr type to an internal module. Fix a bug caused by us passing ptr-to-ptr instead of ptr to atomic exchange. Renamed interlockedExchange to exchangePtr. I've also added an cas primitive. It turned out we don't need it for WinIO but I'm leaving it in as it's useful for other things. - - - - - 948a14e1 by Ben Gamari at 2020-10-07T15:00:55-04:00 gitlab-ci: Fix name of Ubuntu 20.04 image - - - - - 74d4017b by Sylvain Henry at 2020-10-07T15:01:35-04:00 Fix -flink-rts (#18651) Before this patch -flink-rts could link with GHC's rts instead of the selected one. - - - - - 0e8b923d by Sylvain Henry at 2020-10-07T15:01:35-04:00 Apply suggestion to compiler/GHC/SysTools.hs - - - - - d6dff830 by Alan Zimmerman at 2020-10-07T15:02:10-04:00 Preserve as-parsed arrow type for HsUnrestrictedArrow When linear types are disabled, HsUnrestrictedArrow is treated as HslinearArrow. Move this adjustment into the type checking phase, so that the parsed source accurately represents the source as parsed. Closes #18791 - - - - - 030c5ce0 by Karel Gardas at 2020-10-07T15:02:48-04:00 hadrian: use stage0 linker to merge objects when done during the stage0 Fixes #18800. - - - - - a94db588 by Ben Gamari at 2020-10-07T15:03:23-04:00 testsuite: Allow whitespace before "Metric (in|de)crease" Several people have struggled with metric change annotations in their commit messages not being recognized due to the fact that GitLab's job log inserts a space at the beginning of each line. Teach the regular expression to accept this whitespace. - - - - - e91ddddd by Krzysztof Gogolewski at 2020-10-07T15:04:07-04:00 Misc cleanup * Include funTyCon in exposedPrimTyCons. Every single place using exposedPrimTyCons was adding funTyCon manually. * Remove unused synTyConResKind and ieLWrappedName * Add recordSelectorTyCon_maybe * In exprType, panic instead of giving a trace message and dummy output. This prevents #18767 reoccurring. * Fix compilation error in fragile concprog001 test (part of #18732) - - - - - 386c2d7f by Sylvain Henry at 2020-10-09T08:40:33-04:00 Use UnitId in the backend instead of Unit In Cmm we can only have real units identified with an UnitId. Other units (on-the-fly instantiated units and holes) are only used in type-checking backpack sessions that don't produce Cmm. - - - - - a566c83d by Simon Jakobi at 2020-10-09T08:41:09-04:00 Update containers to v0.6.4.1 Updates containers submodule. - - - - - fd984d68 by Tamar Christina at 2020-10-09T08:41:50-04:00 rts: fix race condition in StgCRun On windows the stack has to be allocated 4k at a time, otherwise we get a segfault. This is done by using a helper ___chkstk_ms that is provided by libgcc. The Haskell side already knows how to handle this but we need to do the same from STG. Previously we would drop the stack in StgRun but would only make it valid whenever the scheduler loop ran. This approach was fundamentally broken in that it falls apart when you take a signal from the OS. We see it less often because you initially get allocated a 1MB stack block which you have to blow past first. Concretely this means we must always keep the stack valid. Fixes #18601. - - - - - accdb24a by Sylvain Henry at 2020-10-09T08:42:31-04:00 Expose RTS-only ways (#18651) Some RTS ways are exposed via settings (ghcThreaded, ghcDebugged) but not all. It's simpler if the RTS exposes them all itself. - - - - - d360f343 by MaxGabriel at 2020-10-09T08:43:11-04:00 Document -Wderiving-typeable Tracking: #18641 - - - - - e48cab2a by Krzysztof Gogolewski at 2020-10-09T08:43:49-04:00 Add a flag to indicate that gcc supports -no-pie Fixes #17919. - - - - - f7e2fff9 by Hécate at 2020-10-09T08:44:26-04:00 Add linting of `base` to the CI - - - - - 45a1d493 by Andreas Klebinger at 2020-10-09T08:45:05-04:00 Use proper RTS flags when collecting residency in perf tests. Replace options like collect_stats(['peak_megabytes_allocated'],4) with collect_runtime_residency(4) and so forth. Reason being that the later also supplies some default RTS arguments which make sure residency does not fluctuate too much. The new flags mean we get new (hopefully more accurate) baselines so accept the stat changes. ------------------------- Metric Decrease: T4029 T4334 T7850 Metric Increase: T13218 T7436 ------------------------- - - - - - ef65b154 by Andreas Klebinger at 2020-10-09T08:45:42-04:00 testsuite/timeout: Fix windows specific errors. We now seem to use -Werror there. Which caused some long standing warnings to become errors. I applied changes to remove the warnings allowing the testsuite to run on windows as well. - - - - - e691a5a0 by Sylvain Henry at 2020-10-09T08:46:22-04:00 Hadrian: add quick-debug flavour - - - - - 12191a99 by Sylvain Henry at 2020-10-09T08:47:00-04:00 Bignum: match on small Integer/Natural Previously we only matched on *variables* whose unfoldings were a ConApp of the form `IS lit#` or `NS lit##`. But we forgot to match on the ConApp directly... As a consequence, constant folding only worked after the FloatOut pass which creates bindings for most sub-expressions. With this patch, matching on bignums works even with -O0 (see bignumMatch test). - - - - - 36787bba by Alan Zimmerman at 2020-10-09T08:47:36-04:00 ApiAnnotations : preserve parens in GADTs A cleanup in 7f418acf61e accidentally discarded some parens in ConDeclGADT. Make sure these stay in the AST in a usable format. Also ensure the AnnLolly does not get lost in a GADT. - - - - - 32dc7698 by Krzysztof Gogolewski at 2020-10-09T08:48:15-04:00 Linear types: fix roles in GADTs (#18799) - - - - - 9657f6f3 by Ben Gamari at 2020-10-09T08:48:52-04:00 sdist: Include hadrian sources in source distribution Previously the make build system's source distribution rules neglected to include Hadrian's sources. Fixes #18794. - - - - - c832f7e2 by Tamar Christina at 2020-10-09T08:49:33-04:00 winio: fixed timeouts non-threaded. - - - - - 6f0243ae by Tamar Christina at 2020-10-09T08:50:13-04:00 winio: fix array splat - - - - - 0fd3d360 by Tamar Christina at 2020-10-09T08:50:51-04:00 winio: fixed bytestring reading interface. - - - - - dfaef1ca by Tamar Christina at 2020-10-09T08:51:30-04:00 winio: fixed more data error. - - - - - bfdccac6 by Simon Peyton Jones at 2020-10-09T08:52:07-04:00 Fix desugaring of record updates on data families This fixes a long-standing bug in the desugaring of record updates for data families, when the latter involves a GADT. It's all explained in Note [Update for GADTs] in GHC.HsToCore.Expr. Building the correct cast is surprisingly tricky, as that Note explains. Fixes #18809. The test case (in indexed-types/should_compile/T18809) contains several examples that exercise the dark corners. - - - - - e5c7c9c8 by Ben Gamari at 2020-10-09T08:52:43-04:00 Bump win32-tarballs version to 0.3 This should fix #18774. - - - - - ef950b19 by Andreas Klebinger at 2020-10-09T08:53:21-04:00 Add TyCon Set/Env and use them in a few places. Firstly this improves code clarity. But it also has performance benefits as we no longer go through the name of the TyCon to get at it's unique. In order to make this work the recursion check for TyCon has been moved into it's own module in order to avoid import cycles. - - - - - fd302e93 by Krzysztof Gogolewski at 2020-10-09T08:54:02-04:00 Add -pgmlm and -optlm flags !3798 added documentation and semantics for the flags, but not parsing. - - - - - db236ffc by Sylvain Henry at 2020-10-09T08:54:41-04:00 Testsuite: increase timeout for T18223 (#18795) - - - - - 6a243e9d by Sylvain Henry at 2020-10-09T08:55:21-04:00 Cache HomeUnit in HscEnv (#17957) Instead of recreating the HomeUnit from the DynFlags every time we need it, we store it in the HscEnv. - - - - - 5884fd32 by Fendor at 2020-10-09T19:46:28+02:00 Move File Target parser to library #18596 - - - - - ea59fd4d by Hécate at 2020-10-10T14:49:59-04:00 Lint the compiler for extraneous LANGUAGE pragmas - - - - - 22f218b7 by Krzysztof Gogolewski at 2020-10-10T14:50:42-04:00 Linear types: fix quantification in GADTs (#18790) - - - - - 74ee1237 by Sylvain Henry at 2020-10-10T14:51:20-04:00 Bignum: fix bigNatCompareWord# bug (#18813) - - - - - 274e21f0 by Hécate at 2020-10-11T10:55:56+02:00 Remove the dependency on the ghc-linters stage - - - - - 990ea991 by Daniel Rogozin at 2020-10-11T22:20:04+03:00 Fall back to types when looking up data constructors (#18740) Before this patch, referring to a data constructor in a term-level context led to a scoping error: ghci> id Int <interactive>:1:4: error: Data constructor not in scope: Int After this patch, the renamer falls back to the type namespace and successfully finds the Int. It is then rejected in the type checker with a more useful error message: <interactive>:1:4: error: • Illegal term-level use of the type constructor ‘Int’ imported from ‘Prelude’ (and originally defined in ‘GHC.Types’) • In the first argument of ‘id’, namely ‘Int’ In the expression: id Int We also do this for type variables. - - - - - 9bbc84d2 by Sylvain Henry at 2020-10-12T18:21:51-04:00 DynFlags: refactor DmdAnal Make demand analysis usable without having to provide DynFlags. - - - - - 7fdcce6d by Wander Hillen at 2020-10-13T00:12:47-04:00 Initial ShortText code and conversion of package db code Metric Decrease: Naperian T10421 T10421a T10547 T12150 T12234 T12425 T13035 T18140 T18304 T5837 T6048 T13253-spj T18282 T18223 T3064 T9961 Metric Increase T13701 HFSKJH - - - - - 0a5f2918 by Sylvain Henry at 2020-10-13T00:13:28-04:00 Parser: don't require the HomeUnitId The HomeUnitId is only used by the Cmm parser and this one has access to the DynFlags, so it can grab the UnitId of the HomeUnit from them. Bump haddock submodule - - - - - 8f4f5794 by HaskellMouse at 2020-10-13T13:05:49+03:00 Unification of Nat and Naturals This commit removes the separate kind 'Nat' and enables promotion of type 'Natural' for using as type literal. It partially solves #10776 Now the following code will be successfully typechecked: data C = MkC Natural type CC = MkC 1 Before this change we had to create the separate type for promotion data C = MkC Natural data CP = MkCP Nat type CC = MkCP 1 But CP is uninhabited in terms. For backward compatibility type synonym `Nat` has been made: type Nat = Natural The user's documentation and tests have been updated. The haddock submodule also have been updated. - - - - - 0fc1cb54 by Ben Gamari at 2020-10-14T03:42:50-04:00 gitlab-ci: Verify that Hadrian builds with Stack As noted in #18726, this regularly breaks. Let's test it. Note that we don't actually perform a build of GHC itself; we merely test that the Hadrian executable builds and works (by invoking `hadrian --version`). - - - - - 89f4d8e9 by Ben Gamari at 2020-10-14T12:03:57-04:00 Bump LLVM version to 10.0 Fixes #18267. - - - - - 716385c9 by Ryan Scott at 2020-10-14T12:04:34-04:00 Make DataKinds the sole arbiter of kind-level literals (and friends) Previously, the use of kind-level literals, promoted tuples, and promoted lists required enabling both `DataKinds` and `PolyKinds`. This made sense back in a `TypeInType` world, but not so much now that `TypeInType`'s role has been superseded. Nowadays, `PolyKinds` only controls kind polymorphism, so let's make `DataKinds` the thing that controls the other aspects of `TypeInType`, which include literals, promoted tuples and promoted lists. There are some other things that overzealously required `PolyKinds`, which this patch fixes as well: * Previously, using constraints in kinds (e.g., `data T :: () -> Type`) required `PolyKinds`, despite the fact that this is orthogonal to kind polymorphism. This now requires `DataKinds` instead. * Previously, using kind annotations in kinds (e.g., `data T :: (Type :: Type) -> Type`) required both `KindSignatures` and `PolyKinds`. This doesn't make much sense, so it only requires `KindSignatures` now. Fixes #18831. - - - - - ac300a0d by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Remove "Operator sections" from docs/users_guide/bugs.rst The issue described in that section was fixed by 2b89ca5b850b4097447cc4908cbb0631011ce979 - - - - - bf2411a3 by Vladislav Zavialov at 2020-10-14T12:05:11-04:00 Fix PostfixOperators (#18151) This fixes a regression introduced in 2b89ca5b850b4097447cc4908cbb0631011ce979 See the new T18151x test case. - - - - - e60ae8a3 by Fumiaki Kinoshita at 2020-10-14T18:06:12-04:00 Add -Wnoncanonical-{monad,monoid}-instances to standardWarnings ------------------------- Metric Decrease: T12425 Metric Increase: T17516 ------------------------- - - - - - 15d2340c by Simon Peyton Jones at 2020-10-14T18:06:48-04:00 Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 - - - - - 0c4bfed8 by Ben Gamari at 2020-10-14T18:07:25-04:00 users-guide: Add missing :ghc-flag: directive - - - - - 51c4b851 by Krzysztof Gogolewski at 2020-10-15T04:30:27-04:00 Remove Proxy# argument in Data.Typeable.Internal No longer neccessary - TypeRep is now indexed, there is no ambiguity. Also fix a comment in Evidence.hs, IsLabel no longer takes a Proxy#. - - - - - 809f09e8 by Sylvain Henry at 2020-10-15T04:31:07-04:00 Fix parsing of PIE flags -fPIE and -fno-PIE flags were (un)setting Opt_PIC instead of Opt_PIE. Original commit: 3625728a0e3a9b56c2b85ae7ea8bcabdd83ece6a - - - - - 3d7db148 by Ben Gamari at 2020-10-15T04:31:42-04:00 testsuite: Add missing #include on <stdlib.h> This otherwise fails on newer Clangs, which warn more aggressively on undeclared symbols. - - - - - 998803dc by Andrzej Rybczak at 2020-10-15T11:40:32+02:00 Add flags for annotating Generic{,1} methods INLINE[1] (#11068) Makes it possible for GHC to optimize away intermediate Generic representation for more types. Metric Increase: T12227 - - - - - 6b14c418 by GHC GitLab CI at 2020-10-15T21:57:50-04:00 Extend mAX_TUPLE_SIZE to 64 As well a ctuples and sums. - - - - - d495f36a by Ben Gamari at 2020-10-15T21:58:27-04:00 rts: Clean-up whitespace in Interpreter - - - - - cf10becd by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Use strict Maps in bytecode assembler - - - - - ae146b53 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Make LocalLabel a newtype - - - - - cc536288 by Ben Gamari at 2020-10-15T21:58:27-04:00 compiler/ByteCode: Allow 2^32 local labels This widens LocalLabel to 2^16, avoiding the crash observed in #14334. Closes #14334. - - - - - 1bb0512f by Ben Gamari at 2020-10-16T00:15:31-04:00 mingw: Extract zst toolchain archives This should have been done when the toolchain was bumped. - - - - - bf7c5b6d by Ben Gamari at 2020-10-16T00:15:31-04:00 base: Reintroduce necessary LANGUAGE pragmas These were incorrectly removed in a recent cleanup commit. - - - - - c6b4be4b by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Sort metrics by metric type Closes #18838. - - - - - c7989c93 by Ben Gamari at 2020-10-16T00:15:31-04:00 testsuite: Account for -Wnoncanonical-monoid-instances changes on Windows - - - - - 330a5433 by Ben Gamari at 2020-10-16T00:15:31-04:00 rts: Add __mingw_vfprintf to RtsSymbols.c Following the model of the other printf symbols. See Note [Symbols for MinGW's printf]. - - - - - c4a69f37 by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Remove allow_failure from Windows jobs - - - - - 9a9679db by Ben Gamari at 2020-10-16T00:15:31-04:00 gitlab-ci: Fix Hadrian bindist names - - - - - 07b0db86 by f-a at 2020-10-16T10:14:39-04:00 Clarify Eq documentation #18713 - - - - - aca0e63b by Ben Gamari at 2020-10-17T10:20:31-04:00 gitlab-ci: Allow doc-tarball job to fail Currently the Hadrian build appears not to package documentation correctly, causing doc-tarball to fail due to the Windows build. - - - - - b02a9ea7 by Ben Gamari at 2020-10-17T13:26:24-04:00 gitlab-ci: s/allow_newer/allow_failure Silly mistake on my part. - - - - - 59d7c9f4 by John Ericson at 2020-10-17T22:01:38-04:00 Skip type family defaults with hs-boot and hsig files Works around #17190, possible resolution for #17224. New design is is according to accepted [GHC Propoal 320]. Instances in signatures currently unconditionally opt into associated family defaults if no explicit instance is given. This is bad for two reasons: 1. It constrains possible instantiations to use the default, rather than possibly define the associated family differently. 2. It breaks compilation as type families are unsupported in signatures. This PR simply turns off the filling in of defaults in those cases. Additionally, it squelches a missing definition warning for hs-boot too that was only squelched for hsig before. The downsides are: 1. There is no way to opt into the default, other than copying its definition. 2. If we fixed type classes in signatures, and wanted instances to have to explicitly *out of* rather than into the default, that would now be a breaking change. The change that is most unambiguously goood is harmonizing the warning squelching between hs-boot or hsig. Maybe they should have the warning (opt out of default) maybe they shouldn't (opt in to default), but surely it should be the same for both. Add hs-boot version of a backpack test regarding class-specified defaults in instances that appear in an hs-boot file. The metrics increase is very slight and makes no sense --- at least no one has figured anything out after this languishing for a while, so I'm just going to accept it. Metric Increase: T10421a [GHC proposal 320]: https://github.com/ghc-proposals/ghc-proposals/pull/320 - - - - - 7eb46a09 by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Refactor fixed-point iteration in GHC.Core.Opt.Arity Arity analysis used to propagate optimistic arity types during fixed-point interation through the `ArityEnv`'s `ae_cheap_fun` field, which is like `GHC.Core.Utils.exprIsCheap`, but also considers the current iteration's optimistic arity, for the binder in question only. In #18793, we have seen that this is a problematic design, because it doesn't allow us to look through PAP bindings of that binder. Hence this patch refactors to a more traditional form with an explicit signature environment, in which we record the optimistic `ArityType` of the binder in question (and at the moment is the *only* binder that is recorded in the arity environment). - - - - - 6b3eb06a by Sebastian Graf at 2020-10-17T22:02:13-04:00 Arity: Record arity types for non-recursive lets In #18793, we saw a compelling example which requires us to look at non-recursive let-bindings during arity analysis and unleash their arity types at use sites. After the refactoring in the previous patch, the needed change is quite simple and very local to `arityType`'s defn for non-recurisve `Let`. Apart from that, we had to get rid of the second item of `Note [Dealing with bottoms]`, which was entirely a safety measure and hindered optimistic fixed-point iteration. Fixes #18793. The following metric increases are all caused by this commit and a result of the fact that we just do more work now: Metric Increase: T3294 T12545 T12707 - - - - - 451455fd by Sebastian Graf at 2020-10-17T22:02:13-04:00 Testsuite: Add dead arity analysis tests We didn't seem to test these old tests at all, judging from their expected output. - - - - - 50e9df49 by Dylan Yudaken at 2020-10-17T22:02:50-04:00 When using rts_setInCallCapability, lock incall threads This diff makes sure that incall threads, when using `rts_setInCallCapability`, will be created as locked. If the thread is not locked, the thread might end up being scheduled to a different capability. While this is mentioned in the docs for `rts_setInCallCapability,`, it makes the method significantly less useful as there is no guarantees on the capability being used. This commit also adds a test to make sure things stay on the correct capability. - - - - - 0b995759 by DylanZA at 2020-10-17T22:02:50-04:00 Apply suggestion to testsuite/tests/ffi/should_run/all.T - - - - - a91dcb66 by Sylvain Henry at 2020-10-17T22:04:02-04:00 Don't get host RTS ways via settings (#18651) To correctly perform a linking hack for Windows we need to link with the RTS GHC is currently using. We used to query the RTS ways via the "settings" file but it is fragile (#18651). The hack hasn't been fixed to take into account all the ways (Tracing) and it makes linking of GHC with another RTS more difficult (we need to link with another RTS and to regenerate the settings file). So this patch uses the ways reported by the RTS itself (GHC.Platform.Ways.hostWays) instead of the "settings" file. - - - - - d858a3ae by Hécate at 2020-10-17T22:04:38-04:00 Linting corrections * Bring back LANGUAGE pragmas in GHC.IO.Handle.Lock.Windows * Exclude some modules that are wrongfully reported - - - - - b5b3e34e by Vladislav Zavialov at 2020-10-19T18:16:20-04:00 Implement -Woperator-whitespace (#18834) This patch implements two related warnings: -Woperator-whitespace-ext-conflict warns on uses of infix operators that would be parsed differently were a particular GHC extension enabled -Woperator-whitespace warns on prefix, suffix, and tight infix uses of infix operators Updates submodules: haddock, containers. - - - - - 9648d680 by Sylvain Henry at 2020-10-19T18:16:58-04:00 Remove pdocPrec pdocPrec was only used in GHC.Cmm.DebugBlock.pprUnwindExpr, so remove it. OutputableP becomes a one-function class which might be better for performance. - - - - - ee5dcdf9 by Ben Gamari at 2020-10-20T00:47:54-04:00 testsuite: Add test for #18346 This was fixed by 4291bddaea3148908c55f235ee8978e1d9aa6f20. - - - - - 6c7a5c0c by Krzysztof Gogolewski at 2020-10-20T00:48:29-04:00 Minor comments, update linear types docs - Update comments: placeHolderTypeTc no longer exists "another level check problem" was a temporary comment from linear types - Use Mult type synonym (reported in #18676) - Mention multiplicity-polymorphic fields in linear types docs - - - - - 58a1ca38 by nineonine at 2020-10-20T00:49:07-04:00 Compile modules with `-fobject-code` enabled to byte-code when loaded with `*` prefix in ghci (#8042) The documentation states that when using :add and :load, the `*` prefix forces a module to be loaded as byte-code. However, this seems to be ignored when -fobject-code has been enabled. In that case, the compiled code is always used, regardless of whether the *-form is used. The idea is to consult the Targets in HscEnv and check the 'targetAllowObjCode' flag. If the flag for given module is set, then patch up DynFlags and select compilation backend accordingly. This would require a linear scan of course, but that shouldn't be too costly. - - - - - 59b08a5d by Ben Gamari at 2020-10-20T00:49:41-04:00 gitlab-ci: Rename FLAVOUR -> BUILD_FLAVOUR Previously the Hadrian jobs used the `FLAVOUR` environment variable to communicate which flavour `ci.sh` should build whereas `make` used `BUILD_FLAVOUR`. This caused unnecessary confusion. Consolidate these two. - - - - - ea736839 by Alan Zimmerman at 2020-10-20T08:35:34+01:00 API Annotations: Keep track of unicode for linear arrow notation The linear arrow can be parsed as `%1 ->` or a direct single token unicode equivalent. Make sure that this distinction is captured in the parsed AST by using IsUnicodeSyntax where it appears, and introduce a new API Annotation, AnnMult to represent its location when unicode is not used. Updated haddock submodule - - - - - cf3c3bcd by Ben Gamari at 2020-10-20T22:56:31-04:00 testsuite: Mark T12971 as fragile on Windows Due to #17945. - - - - - e2c4a947 by Vladislav Zavialov at 2020-10-21T16:00:30+03:00 Parser regression tests, close #12862 #12446 These issues were fixed by earlier parser changes, most likely related to whitespace-sensitive parsing. - - - - - 711929e6 by Simon Peyton Jones at 2020-10-23T02:42:59-04:00 Fix error message location in tcCheckPatSynDecl Ticket #18856 showed that we were failing to set the right location for an error message. Easy to fix, happily. Turns out that this also improves the error location in test T11010, which was bogus before but we had never noticed. - - - - - 730bb590 by Ben Gamari at 2020-10-23T02:43:33-04:00 cmm: Add Note reference to ForeignHint - - - - - b9d4dd9c by Ben Gamari at 2020-10-24T20:44:17-04:00 SMP.h: Add C11-style atomic operations - - - - - ccf2d4b0 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Infrastructure for testing with ThreadSanitizer - - - - - a61f66d6 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/CNF: Initialize all bdescrs in group It seems wise and cheap to ensure that the whole bdescr of all blocks of a compact group is valid, even if most cases only look at the flags field. - - - - - 65136c13 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Capability: Intialize interrupt field Previously this was left uninitialized. Also clarify some comments. - - - - - b3ce6aca by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/Task: Make comments proper Notes - - - - - d3890ac7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/SpinLock: Move to proper atomics This is fairly straightforward; we just needed to use relaxed operations for the PROF_SPIN counters and a release store instead of a write barrier. - - - - - ef88712f by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/OSThreads: Fix data race Previously we would race on the cached processor count. Avoiding this is straightforward; just use relaxed operations. - - - - - 33a719c3 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts/ClosureMaros: Use relaxed atomics - - - - - f08951fd by Ben Gamari at 2020-10-24T20:59:39-04:00 configure: Bump minimum-supported gcc version to 4.7 Since the __atomic_* builtins are not supported until gcc 4.7. Given that this version was released in 2012 I think this is acceptable. - - - - - d584923a by Ben Gamari at 2020-10-24T20:59:39-04:00 testsuite: Fix thread leak in hs_try_putmvar00[13] - - - - - bf1b0bc7 by Ben Gamari at 2020-10-24T20:59:39-04:00 rts: Introduce SET_HDR_RELEASE Also ensure that we also store the info table pointer last to ensure that the synchronization covers all stores. - - - - - 1a2e9f5e by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Add nightly-x86_64-linux-deb9-tsan job - - - - - 58a5b0e5 by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Mark setnumcapabilities001 as broken with TSAN Due to #18808. - - - - - d9bc7dea by GHC GitLab CI at 2020-10-24T21:00:19-04:00 testsuite: Skip divbyzero and derefnull under TSAN ThreadSanitizer changes the output of these tests. - - - - - fcc42a10 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Skip high memory usage tests with TSAN ThreadSanitizer significantly increases the memory footprint of tests, so much so that it can send machines into OOM. - - - - - cae4bb3e by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark hie002 as high_memory_usage This test has a peak residency of 1GByte; this is large enough to classify as "high" in my book. - - - - - dae1b86a by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T9872[abc] as high_memory_usage These all have a maximum residency of over 2 GB. - - - - - c5a0bb22 by Ben Gamari at 2020-10-24T21:00:19-04:00 gitlab-ci: Disable documentation in TSAN build Haddock chews through enough memory to cause the CI builders to OOM and there's frankly no reason to build documentation in this job anyways. - - - - - 4cb1232e by Ben Gamari at 2020-10-24T21:00:19-04:00 TSANUtils: Ensure that C11 atomics are supported - - - - - 7ed15f7f by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T3807 as broken with TSAN Due to #18883. - - - - - f7e6f012 by Ben Gamari at 2020-10-24T21:00:19-04:00 testsuite: Mark T13702 as broken with TSAN due to #18884 - - - - - 16b136b0 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Factor out logic to identify a good capability for running a task Not only does this make the control flow a bit clearer but it also allows us to add a TSAN suppression on this logic, which requires (harmless) data races. - - - - - 2781d68c by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Annotate benign race in waitForCapability - - - - - f6b4b492 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Clarify locking behavior of releaseCapability_ - - - - - 65219810 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Add assertions for task ownership of capabilities - - - - - 31fa87ec by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Use relaxed atomics on n_returning_tasks This mitigates the warning of a benign race on n_returning_tasks in shouldYieldCapability. See #17261. - - - - - 6517a2ea by Ben Gamari at 2020-10-24T21:00:36-04:00 rts: Mitigate races in capability interruption logic - - - - - 2e9ba3f2 by Ben Gamari at 2020-10-24T21:00:36-04:00 rts/Capability: Use relaxed operations for last_free_capability - - - - - e10dde37 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Use relaxed operations for cap->running_task (TODO) This shouldn't be necessary since only the owning thread of the capability should be touching this. - - - - - 855325cd by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Use relaxed operations for sched_state - - - - - 811f915d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Accept data race in work-stealing implementation This race is okay since the task is owned by the capability pushing it. By Note [Ownership of Task] this means that the capability is free to write to `task->cap` without taking `task->lock`. Fixes #17276. - - - - - 8d2b3c3d by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Eliminate data races on pending_sync - - - - - f8871018 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Schedule: Eliminate data races on recent_activity We cannot safely use relaxed atomics here. - - - - - d079b943 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts: Avoid data races in message handling - - - - - 06f80497 by Ben Gamari at 2020-10-24T21:00:37-04:00 rts/Messages: Drop incredibly fishy write barrier executeMessage previously had a write barrier at the beginning of its loop apparently in an attempt to synchronize with another thread's writes to the Message. I would guess that the author had intended to use a load barrier here given that there are no globally-visible writes done in executeMessage. I've removed the redundant barrier since the necessary load barrier is now provided by the ACQUIRE_LOAD. - - - - - d4a87779 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/ThreadPaused: Avoid data races - - - - - 56778ab3 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Schedule: Eliminate data races in run queue management - - - - - 086521f7 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts: Eliminate shutdown data race on task counters - - - - - abad9778 by Ben Gamari at 2020-10-24T21:00:38-04:00 rts/Threads: Avoid data races (TODO) Replace barriers with appropriate ordering. Drop redundant barrier in tryWakeupThread (the RELEASE barrier will be provided by sendMessage's mutex release). We use relaxed operations on why_blocked and the stack although it's not clear to me why this is necessary. - - - - - 2f56be8a by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Messages: Annotate benign race - - - - - 7c0cdab1 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/RaiseAsync: Synchronize what_next read - - - - - 6cc2a8a5 by Ben Gamari at 2020-10-24T21:00:39-04:00 rts/Task: Move debugTrace to avoid data race Specifically, we need to hold all_tasks_mutex to read taskCount. - - - - - bbaec97d by Ben Gamari at 2020-10-24T21:00:39-04:00 Disable flawed assertion - - - - - dd175a92 by Ben Gamari at 2020-10-24T21:00:39-04:00 Document schedulePushWork race - - - - - 3416244b by Ben Gamari at 2020-10-24T21:00:40-04:00 Capabiliity: Properly fix data race on n_returning_tasks There is a real data race but can be made safe by using proper atomic (but relaxed) accesses. - - - - - dffd9432 by Ben Gamari at 2020-10-24T21:00:40-04:00 rts: Make write of to_cap->inbox atomic This is necessary since emptyInbox may read from to_cap->inbox without taking cap->lock. - - - - - 1f4cbc29 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/BlockAlloc: Use relaxed operations - - - - - d0d07cff by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Rework handling of mutlist scavenging statistics - - - - - 9e5c7f6d by Ben Gamari at 2020-10-24T21:00:57-04:00 rts: Avoid data races in StablePtr implementation This fixes two potentially problematic data races in the StablePtr implementation: * We would fail to RELEASE the stable pointer table when enlarging it, causing other cores to potentially see uninitialized memory. * We would fail to ACQUIRE when dereferencing a stable pointer. - - - - - 316add67 by Ben Gamari at 2020-10-24T21:00:57-04:00 rts/Storage: Use atomics - - - - - 5c23bc4c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Updates: Use proper atomic operations - - - - - 3d0f033c by Ben Gamari at 2020-10-24T21:00:58-04:00 rts/Weak: Eliminate data races By taking all_tasks_mutex in stat_exit. Also better-document the fact that the task statistics are protected by all_tasks_mutex. - - - - - edb4b92b by Ben Gamari at 2020-10-24T21:01:18-04:00 rts/WSDeque: Rewrite with proper atomics After a few attempts at shoring up the previous implementation, I ended up turning to the literature and now use the proven implementation, > N.M. Lê, A. Pop, A.Cohen, and F.Z. Nardelli. "Correct and Efficient > Work-Stealing for Weak Memory Models". PPoPP'13, February 2013, > ACM 978-1-4503-1922/13/02. Note only is this approach formally proven correct under C11 semantics but it is also proved to be a bit faster in practice. - - - - - d39bbd3d by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Use relaxed atomics for whitehole spin stats - - - - - 8f802f38 by Ben Gamari at 2020-10-24T21:01:33-04:00 rts: Avoid lock order inversion during fork Fixes #17275. - - - - - cef667b0 by GHC GitLab CI at 2020-10-24T21:01:34-04:00 rts: Use proper relaxe operations in getCurrentThreadCPUTime Here we are doing lazy initialization; it's okay if we do the check more than once, hence relaxed operation is fine. - - - - - 8cf50eb1 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/STM: Use atomics This fixes a potentially harmful race where we failed to synchronize before looking at a TVar's current_value. Also did a bit of refactoring to avoid abstract over management of max_commits. - - - - - 88a7ce38 by Ben Gamari at 2020-10-24T21:01:54-04:00 rts/stm: Strengthen orderings to SEQ_CST instead of volatile Previously the `current_value`, `first_watch_queue_entry`, and `num_updates` fields of `StgTVar` were marked as `volatile` in an attempt to provide strong ordering. Of course, this isn't sufficient. We now use proper atomic operations. In most of these cases I strengthen the ordering all the way to SEQ_CST although it's possible that some could be weakened with some thought. - - - - - f97c59ce by Ben Gamari at 2020-10-24T21:02:11-04:00 Mitigate data races in event manager startup/shutdown - - - - - c7c3f8aa by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Accept benign races in Proftimer - - - - - 5a98dfca by Ben Gamari at 2020-10-24T21:02:22-04:00 rts: Pause timer while changing capability count This avoids #17289. - - - - - 01d95525 by Ben Gamari at 2020-10-24T21:02:22-04:00 Fix #17289 - - - - - 9a528985 by Ben Gamari at 2020-10-24T21:02:23-04:00 suppress #17289 (ticker) race - - - - - 1726ec41 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix timer initialization Previously `initScheduler` would attempt to pause the ticker and in so doing acquire the ticker mutex. However, initTicker, which is responsible for initializing said mutex, hadn't been called yet. - - - - - bfbe4366 by Ben Gamari at 2020-10-24T21:02:23-04:00 rts: Fix races in Pthread timer backend shudown We can generally be pretty relaxed in the barriers here since the timer thread is a loop. - - - - - 297acc71 by Ben Gamari at 2020-10-24T21:02:44-04:00 rts/Stats: Hide a few unused unnecessarily global functions - - - - - 9ad51bc9 by David Beacham at 2020-10-27T13:59:35-04:00 Fix `instance Bounded a => Bounded (Down a)` (#18716) * Flip `minBound` and `maxBound` to respect the change in ordering * Remove awkward `Enum` (and hence `Integral`) instances for `Data.Ord.Down` * Update changelog - - - - - eedec53d by Vladislav Zavialov at 2020-10-27T14:00:11-04:00 Version bump: base-4.16 (#18712) Also bumps upper bounds on base in boot libraries (incl. submodules). - - - - - 412018c1 by Tamar Christina at 2020-10-27T14:00:49-04:00 winio: simplify logic remove optimization step. - - - - - 4950dd07 by Ben Gamari at 2020-10-27T14:01:24-04:00 hadrian: Suppress xelatex output unless it fails As noted in #18835, xelatex produces an absurd amount of output, nearly all of which is meaningless. Silence this. Fixes #18835. - - - - - f3d8ab2e by Ben Gamari at 2020-10-27T14:02:00-04:00 build system: Clean mingw tarballs Tamar noticed in !4293 that the build systems fail to clean up the mingw tarballs directory (`ghc-tarballs`). Fix this in both the make build system and Hadrian. - - - - - 0b3d23af by Simon Peyton Jones at 2020-10-27T14:02:34-04:00 Fix two constraint solving problems This patch fixes two problems in the constraint solver. * An actual bug #18555: we were floating out a constraint to eagerly, and that was ultimately fatal. It's explained in Note [Do not float blocked constraints] in GHC.Core.Constraint. This is all very delicate, but it's all going to become irrelevant when we stop floating constraints (#17656). * A major performance infelicity in the flattener. When flattening (ty |> co) we *never* generated Refl, even when there was nothing at all to do. Result: we would gratuitously rewrite the constraint to exactly the same thing, wasting work. Described in #18413, and came up again in #18855. Solution: exploit the special case by calling the new function castCoercionKind1. See Note [castCoercionKind1] in GHC.Core.Coercion - - - - - f76c5a08 by Sergei Trofimovich at 2020-10-27T14:03:14-04:00 ghc.mk: amend 'make sdist' Noticed 'make sdist' failure seen as: ``` "rm" -rf sdistprep/ghc/ghc-9.1.0.20201020/hadrian/_build/ (SRC_DIST_GHC_DIR)/hadrian/dist-newstyle/ /bin/sh: -c: line 0: syntax error near unexpected token `(' ``` commit 9657f6f34 ("sdist: Include hadrian sources in source distribution") added a new cleanup path without a variable expantion. The change adds variable reference. While at it move directory cleanup to a separate statement. Amends #18794 Signed-off-by: Sergei Trofimovich <slyfox at gentoo.org> - - - - - 78b52c88 by David Eichmann at 2020-10-27T14:03:51-04:00 Use config.run_ways for multi_compile_and_run tests - - - - - e3fdd419 by Alan Zimmerman at 2020-10-27T14:04:26-04:00 Api Annotations: Introduce AnnPercent for HsExplicitMult For the case foo :: a %p -> b The location of the '%' is captured, separate from the 'p' - - - - - d2a25f42 by Ben Gamari at 2020-10-27T14:05:02-04:00 gitlab-ci: Bump ci-images Bumps bootstrap compiler to 8.10.1. - - - - - 28f98b01 by Sebastian Graf at 2020-10-27T14:05:37-04:00 DmdAnal: Kill `is_thunk` case in `splitFV` The `splitFV` function implements the highly dubious hack described in `Note [Lazy und unleashable free variables]` in GHC.Core.Opt.DmdAnal. It arranges it so that demand signatures only carry strictness info on free variables. Usage info is released through other means, see the Note. It's purely for analysis performance reasons. It turns out that `splitFV` has a quite involved case for thunks that produces slightly different usage signatures and it's not clear why we need it: `splitFV` is only relevant in the LetDown case and the only time we call it on thunks is for top-level or local recursive thunks. Since usage signatures of top-level thunks can only reference other top-level bindings and we completely discard demand info we have on top-level things (see the lack of `setIdDemandInfo` in `dmdAnalTopBind`), the `is_thunk` case is completely irrelevant here. For local, recursive thunks, the added benefit of the `is_thunk` test is marginal: We get used-multiple-times in some cases where previously we had used-once if a recursive thunk has multiple call sites. It's very unlikely and not a case to optimise for. So we kill the `is_thunk` case and inline `splitFV` at its call site, exposing `isWeakDmd` from `GHC.Types.Demand` instead. The NoFib summary supports this decision: ``` Min 0.0% -0.0% Max 0.0% +0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 60322f93 by Ben Gamari at 2020-10-28T21:11:39-04:00 hadrian: Don't quote metric baseline argument Previously this was quoted inappropriately. - - - - - c85eb372 by Alan Zimmerman at 2020-10-28T21:12:15-04:00 API Annotations: put constructors in alphabetical order - - - - - 795908dc by John Ericson at 2020-10-29T03:53:14-04:00 Widen acceptance threshold for T10421a Progress towards #18842. As @sgraf812 points out, widening the window is dangerous until the exponential described in #17658 is fixed. But this test has caused enough misery and is low stakes enough that we and @bgamari think it's worth it in this one case for the time being. - - - - - 0e9f6def by Sylvain Henry at 2020-10-29T03:53:52-04:00 Split GHC.Driver.Types I was working on making DynFlags stateless (#17957), especially by storing loaded plugins into HscEnv instead of DynFlags. It turned out to be complicated because HscEnv is in GHC.Driver.Types but LoadedPlugin isn't: it is in GHC.Driver.Plugins which depends on GHC.Driver.Types. I didn't feel like introducing yet another hs-boot file to break the loop. Additionally I remember that while we introduced the module hierarchy (#13009) we talked about splitting GHC.Driver.Types because it contained various unrelated types and functions, but we never executed. I didn't feel like making GHC.Driver.Types bigger with more unrelated Plugins related types, so finally I bit the bullet and split GHC.Driver.Types. As a consequence this patch moves a lot of things. I've tried to put them into appropriate modules but nothing is set in stone. Several other things moved to avoid loops. * Removed Binary instances from GHC.Utils.Binary for random compiler things * Moved Typeable Binary instances into GHC.Utils.Binary.Typeable: they import a lot of things that users of GHC.Utils.Binary don't want to depend on. * put everything related to Units/Modules under GHC.Unit: GHC.Unit.Finder, GHC.Unit.Module.{ModGuts,ModIface,Deps,etc.} * Created several modules under GHC.Types: GHC.Types.Fixity, SourceText, etc. * Split GHC.Utils.Error (into GHC.Types.Error) * Finally removed GHC.Driver.Types Note that this patch doesn't put loaded plugins into HscEnv. It's left for another patch. Bump haddock submodule - - - - - 22f5d9a9 by Sylvain Henry at 2020-10-29T03:53:52-04:00 GC: Avoid data race (#18717, #17964) - - - - - 2ef2fac4 by Ryan Scott at 2020-10-29T04:18:52-04:00 Check for large tuples more thoroughly This fixes #18723 by: * Moving the existing `GHC.Tc.Gen.HsType.bigConstraintTuple` validity check to `GHC.Rename.Utils.checkCTupSize` for consistency with `GHC.Rename.Utils.checkTupSize`, and * Using `check(C)TupSize` when checking tuple _types_, in addition to checking names, expressions, and patterns. Note that I put as many of these checks as possible in the typechecker so that GHC can properly distinguish between boxed and constraint tuples. The exception to this rule is checking names, which I perform in the renamer (in `GHC.Rename.Env`) so that we can rule out `(,, ... ,,)` and `''(,, ... ,,)` alike in one fell swoop. While I was in town, I also removed the `HsConstraintTuple` and `HsBoxedTuple` constructors of `HsTupleSort`, which are functionally unused. This requires a `haddock` submodule bump. - - - - - 7f8be3eb by Richard Eisenberg at 2020-10-29T22:08:13-04:00 Remove unnecessary gender from comments/docs While, say, alternating "he" and "she" in sequential writing may be nicer than always using "they", reading code/documentation is almost never sequential. If this small change makes individuals feel more welcome in GHC's codebase, that's a good thing. - - - - - aad1f803 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/GC: Use atomics - - - - - d0bc0517 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Use RELEASE ordering in unlockClosure - - - - - d44f5232 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts/Storage: Accept races on heap size counters - - - - - 4e4a7386 by Ben Gamari at 2020-10-30T00:41:14-04:00 rts: Join to concurrent mark thread during shutdown Previously we would take all capabilities but fail to join on the thread itself, potentially resulting in a leaked thread. - - - - - a80cc857 by GHC GitLab CI at 2020-10-30T00:41:14-04:00 rts: Fix race in GC CPU time accounting Ensure that the GC leader synchronizes with workers before calling stat_endGC. - - - - - 9902d9ec by Viktor Dukhovni at 2020-10-30T05:28:30-04:00 [skip ci] Fix typo in `callocBytes` haddock. - - - - - 105d43db by Ben Gamari at 2020-10-30T14:02:19-04:00 rts/SpinLock: Separate out slow path Not only is this in general a good idea, but it turns out that GCC unrolls the retry loop, resulting is massive code bloat in critical parts of the RTS (e.g. `evacuate`). - - - - - f7b45cde by Ben Gamari at 2020-10-30T14:02:19-04:00 rts: Use relaxed ordering on spinlock counters - - - - - 31fcb55f by Ryan Scott at 2020-10-30T18:52:50-04:00 Split HsConDecl{H98,GADT}Details Haskell98 and GADT constructors both use `HsConDeclDetails`, which includes `InfixCon`. But `InfixCon` is never used for GADT constructors, which results in an awkward unrepresentable state. This removes the unrepresentable state by: * Renaming the existing `HsConDeclDetails` synonym to `HsConDeclH98Details`, which emphasizes the fact that it is now only used for Haskell98-style data constructors, and * Creating a new `HsConDeclGADTDetails` data type with `PrefixConGADT` and `RecConGADT` constructors that closely resemble `PrefixCon` and `InfixCon` in `HsConDeclH98Details`. The key difference is that `HsConDeclGADTDetails` lacks any way to represent infix constructors. The rest of the patch is refactoring to accommodate the new structure of `HsConDecl{H98,GADT}Details`. Some highlights: * The `getConArgs` and `hsConDeclArgTys` functions have been removed, as there is no way to implement these functions uniformly for all `ConDecl`s. For the most part, their previous call sites now pattern match on the `ConDecl`s directly and do different things for `ConDeclH98`s and `ConDeclGADT`s. I did introduce one new function to make the transition easier: `getRecConArgs_maybe`, which extracts the arguments from a `RecCon(GADT)`. This is still possible since `RecCon(GADT)`s still use the same representation in both `HsConDeclH98Details` and `HsConDeclGADTDetails`, and since the pattern that `getRecConArgs_maybe` implements is used in several places, I thought it worthwhile to factor it out into its own function. * Previously, the `con_args` fields in `ConDeclH98` and `ConDeclGADT` were both of type `HsConDeclDetails`. Now, the former is of type `HsConDeclH98Details`, and the latter is of type `HsConDeclGADTDetails`, which are distinct types. As a result, I had to rename the `con_args` field in `ConDeclGADT` to `con_g_args` to make it typecheck. A consequence of all this is that the `con_args` field is now partial, so using `con_args` as a top-level field selector is dangerous. (Indeed, Haddock was using `con_args` at the top-level, which caused it to crash at runtime before I noticed what was wrong!) I decided to add a disclaimer in the 9.2.1 release notes to advertise this pitfall. Fixes #18844. Bumps the `haddock` submodule. - - - - - 57c3db96 by Ryan Scott at 2020-10-31T02:53:55-04:00 Make typechecker equality consider visibility in ForAllTys Previously, `can_eq_nc'` would equate `ForAllTy`s regardless of their `ArgFlag`, including `forall i -> i -> Type` and `forall i. i -> Type`! To fix this, `can_eq_nc'` now uses the `sameVis` function to first check if the `ArgFlag`s are equal modulo specificity. I have also updated `tcEqType`'s implementation to match this behavior. For more explanation on the "modulo specificity" part, see the new `Note [ForAllTy and typechecker equality]` in `GHC.Tc.Solver.Canonical`. While I was in town, I fixed some related documentation issues: * I added `Note [Typechecker equality]` to `GHC.Tc.Utils.TcType` to describe what exactly distinguishes `can_eq_nc'` and `tcEqType` (which implement typechecker equality) from `eqType` (which implements definitional equality, which does not care about the `ArgFlags` of `ForAllTy`s at all). * The User's Guide had some outdated prose on the specified/inferred distinction being different for types and kinds, a holdover from #15079. This is no longer the case on today's GHC, so I removed this prose, added some new prose to take its place, and added a regression test for the programs in #15079. * The User's Guide had some _more_ outdated prose on inferred type variables not being allowed in `default` type signatures for class methods, which is no longer true as of the resolution of #18432. * The related `Note [Deferred Unification]` was being referenced as `Note [Deferred unification]` elsewhere, which made it harder to `grep` for. I decided to change the name of the Note to `Deferred unification` for consistency with the capitalization style used for most other Notes. Fixes #18863. - - - - - a98593f0 by Sylvain Henry at 2020-10-31T02:54:34-04:00 Refactor numeric constant folding rules Avoid the use of global pattern synonyms. 1) I think it's going to be helpful to implement constant folding for other numeric types, especially Natural which doesn't have a wrapping behavior. We'll have to refactor these rules even more so we'd better make them less cryptic. 2) It should also be slightly faster because global pattern synonyms matched operations for every numeric types instead of the current one: e.g., ":**:" pattern was matching multiplication for both Int# and Word# types. As we will probably want to implement constant folding for other numeric types (Int8#, Int16#, etc.), it is more efficient to only match primops for a given type as we do now. - - - - - 730ef38f by Sylvain Henry at 2020-10-31T02:54:34-04:00 Simplify constant-folding (#18032) See #18032 for the details. * Use `Lit (LitNumber _ i)` instead of `isLitValue_maybe` which does more work but that is not needed for constant-folding * Don't export `GHC.Types.Literal.isLitValue_maybe` * Kill `GHC.Types.Literal.isLitValue` which isn't used - - - - - d5a53c1a by Ben Gamari at 2020-10-31T02:55:10-04:00 primops.txt.pp: Move ByteArray# primops to separate file This file will be generated. - - - - - b4278a41 by Ben Gamari at 2020-10-31T02:55:10-04:00 primops: Generate ByteArray# index/read/write primops Previously these were mostly undocumented and was ripe for potential inconsistencies. - - - - - 08e6993a by Sylvain Henry at 2020-10-31T02:55:50-04:00 Move loadDecl into IfaceToCore - - - - - cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00 winio: Fix unused variables warnings - - - - - eb368078 by Andrzej Rybczak at 2020-10-31T09:27:34-04:00 Add testcase for #816 - - - - - bd4abdc9 by Ben Gamari at 2020-11-01T01:10:31-04:00 testsuite: Add performance test for #18698 - - - - - dfd27445 by Hécate at 2020-11-01T01:11:09-04:00 Add the proper HLint rules and remove redundant keywords from compiler - - - - - ce1bb995 by Hécate at 2020-11-01T08:52:08-05:00 Fix a leak in `transpose` This patch was authored by David Feuer <david.feuer at gmail.com> - - - - - e63db32c by Ben Gamari at 2020-11-01T08:52:44-05:00 Scav: Use bd->gen_no instead of bd->gen->no This potentially saves a cache miss per scavenge. - - - - - b1dda153 by Ben Gamari at 2020-11-01T12:58:36-05:00 rts/Stats: Protect with mutex While on face value this seems a bit heavy, I think it's far better than enforcing ordering on every access. - - - - - 5c2e6bce by Ben Gamari at 2020-11-01T12:58:36-05:00 rts: Tear down stats_mutex after exitHeapProfiling Since the latter wants to call getRTSStats. - - - - - ef25aaa1 by Ben Gamari at 2020-11-01T13:02:11-05:00 rts: Annotate hopefully "benign" races in freeGroup - - - - - 3a181553 by Ben Gamari at 2020-11-01T13:02:18-05:00 Strengthen ordering in releaseGCThreads - - - - - af474f62 by Ben Gamari at 2020-11-01T13:05:38-05:00 Suppress data race due to close This suppresses the other side of a race during shutdown. - - - - - b4686bff by Ben Gamari at 2020-11-01T13:09:59-05:00 Merge branch 'wip/tsan/ci' into wip/tsan/all - - - - - b8e66e0e by Ben Gamari at 2020-11-01T13:10:01-05:00 Merge branch 'wip/tsan/storage' into wip/tsan/all - - - - - 375512cf by Ben Gamari at 2020-11-01T13:10:02-05:00 Merge branch 'wip/tsan/wsdeque' into wip/tsan/all - - - - - 65ebf07e by Ben Gamari at 2020-11-01T13:10:03-05:00 Merge branch 'wip/tsan/misc' into wip/tsan/all - - - - - 55c375d0 by Ben Gamari at 2020-11-01T13:10:04-05:00 Merge branch 'wip/tsan/stm' into wip/tsan/all - - - - - a9f75fe2 by Ben Gamari at 2020-11-01T13:10:06-05:00 Merge branch 'wip/tsan/event-mgr' into wip/tsan/all - - - - - 8325d658 by Ben Gamari at 2020-11-01T13:10:24-05:00 Merge branch 'wip/tsan/timer' into wip/tsan/all - - - - - 07e82ba5 by Ben Gamari at 2020-11-01T13:10:35-05:00 Merge branch 'wip/tsan/stats' into wip/tsan/all - - - - - 4ce2f7d6 by GHC GitLab CI at 2020-11-02T23:45:06-05:00 testsuite: Add --top flag to driver This allows us to make `config.top` a proper Path. Previously it was a str, which caused the Ghostscript detection logic to break. - - - - - 0b772221 by Ben Gamari at 2020-11-02T23:45:42-05:00 Document that ccall convention doesn't support varargs We do not support foreign "C" imports of varargs functions. While this works on amd64, in general the platform's calling convention may need more type information that our Cmm representation can currently provide. For instance, this is the case with Darwin's AArch64 calling convention. Document this fact in the users guide and fix T5423 which makes use of a disallowed foreign import. Closes #18854. - - - - - 81006a06 by David Eichmann at 2020-11-02T23:46:19-05:00 RtsAPI: pause and resume the RTS The `rts_pause` and `rts_resume` functions have been added to `RtsAPI.h` and allow an external process to completely pause and resume the RTS. Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - bfb1e272 by Ryan Scott at 2020-11-02T23:46:55-05:00 Display results of GHC.Core.Lint.lint* functions consistently Previously, the functions in `GHC.Core.Lint` used a patchwork of different ways to display Core Lint errors: * `lintPassResult` (which is the source of most Core Lint errors) renders Core Lint errors with a distinctive banner (e.g., `*** Core Lint errors : in result of ... ***`) that sets them apart from ordinary GHC error messages. * `lintAxioms`, in contrast, uses a completely different code path that displays Core Lint errors in a rather confusing manner. For example, the program in #18770 would give these results: ``` Bug.hs:1:1: error: Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r] In the coercion axiom Bug.N:T :: []. Bug.T ~_R Any Substitution: [TCvSubst In scope: InScope {r} Type env: [axl :-> r] Co env: []] | 1 | {-# LANGUAGE DataKinds #-} | ^ ``` * Further digging reveals that `GHC.IfaceToCore` displays Core Lint errors for iface unfoldings as though they were a GHC panic. See, for example, this excerpt from #17723: ``` ghc: panic! (the 'impossible' happened) (GHC version 8.8.2 for x86_64-unknown-linux): Iface Lint failure In interface for Lib ... ``` This patch makes all of these code paths display Core Lint errors and warnings consistently. I decided to adopt the conventions that `lintPassResult` currently uses, as they appear to have been around the longest (and look the best, in my subjective opinion). We now use the `displayLintResult` function for all three scenarios mentioned above. For example, here is what the Core Lint error for the program in #18770 looks like after this patch: ``` [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) *** Core Lint errors : in result of TcGblEnv axioms *** Bug.hs:12:1: warning: Non-*-like kind when *-like expected: RuntimeRep when checking the body of forall: 'TupleRep '[r_axn] In the coercion axiom N:T :: []. T ~_R Any Substitution: [TCvSubst In scope: InScope {r_axn} Type env: [axn :-> r_axn] Co env: []] *** Offending Program *** axiom N:T :: T = Any -- Defined at Bug.hs:12:1 *** End of Offense *** <no location info>: error: Compilation had errors ``` Fixes #18770. - - - - - a9e5f52c by Simon Peyton Jones at 2020-11-02T23:47:31-05:00 Expand type synonyms with :kind! The User's Guide claims that `:kind!` should expand type synonyms, but GHCi wasn't doing this in practice. Let's just update the implementation to match the specification in the User's Guide. Fixes #13795. Fixes #18828. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - 1370eda7 by Ben Gamari at 2020-11-02T23:48:06-05:00 hadrian: Don't capture RunTest output There are a few reasons why capturing the output of the RunTest builder is undesirable: * there is a large amount of output which then gets unnecessarily duplicated by Hadrian if the builder fails * the output may contain codepoints which are unrepresentable in the current codepage on Windows, causing Hadrian to crash * capturing the output causes the testsuite driver to disable its colorisation logic, making the output less legible. - - - - - 78f2767d by Matthew Pickering at 2020-11-03T17:39:53-05:00 Update inlining flags documentation - - - - - 14ce454f by Sylvain Henry at 2020-11-03T17:40:34-05:00 Linker: reorganize linker related code Move linker related code into GHC.Linker. Previously it was scattered into GHC.Unit.State, GHC.Driver.Pipeline, GHC.Runtime.Linker, etc. Add documentation in GHC.Linker - - - - - 616bec0d by Alan Zimmerman at 2020-11-03T17:41:10-05:00 Restrict Linear arrow %1 to exactly literal 1 only This disallows `a %001 -> b`, and makes sure the type literal is printed from its SourceText so it is clear why. Closes #18888 - - - - - 3486ebe6 by Sylvain Henry at 2020-11-03T17:41:48-05:00 Hadrian: don't fail if ghc-tarballs dir doesn't exist - - - - - 37f0434d by Sylvain Henry at 2020-11-03T17:42:26-05:00 Constant-folding: don't pass through GHC's Int/Word (fix #11704) Constant-folding rules for integerToWord/integerToInt were performing the following coercions at compilation time: integerToWord: target's Integer -> ghc's Word -> target's Word integerToInt : target's Integer -> ghc's Int -> target's Int 1) It was wrong for cross-compilers when GHC's word size is smaller than the target one. This patch avoids passing through GHC's word-sized types: integerToWord: target's Integer -> ghc's Integer -> target's Word integerToInt : target's Integer -> ghc's Integer -> target's Int 2) Additionally we didn't wrap the target word/int literal to make it fit into the target's range! This broke the invariant of literals only containing values in range. The existing code is wrong only with a 64-bit cross-compiling GHC, targeting a 32-bit platform, and performing constant folding on a literal that doesn't fit in a 32-bit word. If GHC was built with DEBUG, the assertion in GHC.Types.Literal.mkLitWord would fail. Otherwise the bad transformation would go unnoticed. - - - - - bff74de7 by Sylvain Henry at 2020-11-03T17:43:03-05:00 Bignum: make GMP's bignat_add not recursive bignat_add was a loopbreaker with an INLINE pragma (spotted by @mpickering). This patch makes it non recursive to avoid the issue. - - - - - bb100805 by Andreas Klebinger at 2020-11-04T16:47:24-05:00 NCG: Fix 64bit int comparisons on 32bit x86 We no compare these by doing 64bit subtraction and checking the resulting flags. We used to do this differently but the old approach was broken when the high bits compared equal and the comparison was one of >= or <=. The new approach should be both correct and faster. - - - - - b790b7f9 by Andreas Klebinger at 2020-11-04T16:47:59-05:00 Testsuite: Support for user supplied package dbs We can now supply additional package dbs to the testsuite. For make the package db can be supplied by passing PACKAGE_DB=/path/to/db. In the testsuite driver it's passed via the --test-package-db argument. - - - - - 81560981 by Sylvain Henry at 2020-11-04T16:48:42-05:00 Don't use LEA with 8-bit registers (#18614) - - - - - 17d5c518 by Viktor Dukhovni at 2020-11-05T00:50:23-05:00 Naming, value types and tests for Addr# atomics The atomic Exchange and CAS operations on integral types are updated to take and return more natural `Word#` rather than `Int#` values. These are bit-block not arithmetic operations, and the sign bit plays no special role. Standardises the names to `atomic<OpType><ValType>Addr#`, where `OpType` is one of `Cas` or `Exchange` and `ValType` is presently either `Word` or `Addr`. Eventually, variants for `Word32` and `Word64` can and should be added, once #11953 and related issues (e.g. #13825) are resolved. Adds tests for `Addr#` CAS that mirror existing tests for `MutableByteArray#`. - - - - - 2125b1d6 by Ryan Scott at 2020-11-05T00:51:01-05:00 Add a regression test for #18920 Commit f594a68a5500696d94ae36425bbf4d4073aca3b2 (`Use level numbers for generalisation`) ended up fixing #18920. Let's add a regression test to ensure that it stays fixed. Fixes #18920. - - - - - e07e383a by Ryan Scott at 2020-11-06T03:45:28-05:00 Replace HsImplicitBndrs with HsOuterTyVarBndrs This refactors the GHC AST to remove `HsImplicitBndrs` and replace it with `HsOuterTyVarBndrs`, a type which records whether the outermost quantification in a type is explicit (i.e., with an outermost, invisible `forall`) or implicit. As a result of this refactoring, it is now evident in the AST where the `forall`-or-nothing rule applies: it's all the places that use `HsOuterTyVarBndrs`. See the revamped `Note [forall-or-nothing rule]` in `GHC.Hs.Type` (previously in `GHC.Rename.HsType`). Moreover, the places where `ScopedTypeVariables` brings lexically scoped type variables into scope are a subset of the places that adhere to the `forall`-or-nothing rule, so this also makes places that interact with `ScopedTypeVariables` easier to find. See the revamped `Note [Lexically scoped type variables]` in `GHC.Hs.Type` (previously in `GHC.Tc.Gen.Sig`). `HsOuterTyVarBndrs` are used in type signatures (see `HsOuterSigTyVarBndrs`) and type family equations (see `HsOuterFamEqnTyVarBndrs`). The main difference between the former and the latter is that the former cares about specificity but the latter does not. There are a number of knock-on consequences: * There is now a dedicated `HsSigType` type, which is the combination of `HsOuterSigTyVarBndrs` and `HsType`. `LHsSigType` is now an alias for an `XRec` of `HsSigType`. * Working out the details led us to a substantial refactoring of the handling of explicit (user-written) and implicit type-variable bindings in `GHC.Tc.Gen.HsType`. Instead of a confusing family of higher order functions, we now have a local data type, `SkolemInfo`, that controls how these binders are kind-checked. It remains very fiddly, not fully satisfying. But it's better than it was. Fixes #16762. Bumps the Haddock submodule. Co-authored-by: Simon Peyton Jones <simonpj at microsoft.com> Co-authored-by: Richard Eisenberg <rae at richarde.dev> Co-authored-by: Zubin Duggal <zubin at cmi.ac.in> - - - - - c85f4928 by Sylvain Henry at 2020-11-06T03:46:08-05:00 Refactor -dynamic-too handling 1) Don't modify DynFlags (too much) for -dynamic-too: now when we generate dynamic outputs for "-dynamic-too", we only set "dynamicNow" boolean field in DynFlags instead of modifying several other fields. These fields now have accessors that take dynamicNow into account. 2) Use DynamicTooState ADT to represent -dynamic-too state. It's much clearer than the undocumented "DynamicTooConditional" that was used before. As a result, we can finally remove the hscs_iface_dflags field in HscRecomp. There was a comment on this field saying: "FIXME (osa): I don't understand why this is necessary, but I spent almost two days trying to figure this out and I couldn't .. perhaps someone who understands this code better will remove this later." I don't fully understand the details, but it was needed because of the changes made to the DynFlags for -dynamic-too. There is still something very dubious in GHC.Iface.Recomp: we have to disable the "dynamicNow" flag at some point for some Backpack's "heinous hack" to continue to work. It may be because interfaces for indefinite units are always non-dynamic, or because we mix and match dynamic and non-dynamic interfaces (#9176), or something else, who knows? - - - - - 2cb87909 by Moritz Angermann at 2020-11-06T03:46:44-05:00 [AArch64] Aarch64 Always PIC - - - - - b1d2c1f3 by Ben Gamari at 2020-11-06T03:47:19-05:00 rts/Sanity: Avoid nasty race in weak pointer sanity-checking See Note [Racing weak pointer evacuation] for all of the gory details. - - - - - 638f38c5 by Ben Gamari at 2020-11-08T09:29:16-05:00 Merge remote-tracking branch 'origin/wip/tsan/all' - - - - - 22888798 by Ben Gamari at 2020-11-08T12:08:40-05:00 Fix haddock submodule The previous merge mistakenly reverted it. - - - - - d445cf05 by Ben Gamari at 2020-11-10T10:26:20-05:00 rts/linker: Fix relocation overflow in PE linker Previously the overflow check for the IMAGE_REL_AMD64_ADDR32NB relocation failed to account for the signed nature of the value. Specifically, the overflow check was: uint64_t v; v = S + A; if (v >> 32) { ... } However, `v` ultimately needs to fit into 32-bits as a signed value. Consequently, values `v > 2^31` in fact overflow yet this is not caught by the existing overflow check. Here we rewrite the overflow check to rather ensure that `INT32_MIN <= v <= INT32_MAX`. There is now quite a bit of repetition between the `IMAGE_REL_AMD64_REL32` and `IMAGE_REL_AMD64_ADDR32` cases but I am leaving fixing this for future work. This bug was first noticed by @awson. Fixes #15808. - - - - - 4c407f6e by Sylvain Henry at 2020-11-10T10:27:00-05:00 Export SPEC from GHC.Exts (#13681) - - - - - 7814cd5b by David Eichmann at 2020-11-10T10:27:35-05:00 ghc-heap: expose decoding from heap representation Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - fa344d33 by Richard Eisenberg at 2020-11-10T10:28:10-05:00 Add test case for #17186. This got fixed sometime recently; not worth it trying to figure out which commit. - - - - - 2e63a0fb by David Eichmann at 2020-11-10T10:28:46-05:00 Add code comments for StgInfoTable and StgStack structs - - - - - fcfda909 by Ben Gamari at 2020-11-11T03:19:59-05:00 nativeGen: Make makeImportsDoc take an NCGConfig rather than DynFlags It appears this was an oversight as there is no reason the full DynFlags is necessary. - - - - - 6e23695e by Ben Gamari at 2020-11-11T03:19:59-05:00 Move this_module into NCGConfig In various places in the NCG we need the Module currently being compiled. Let's move this into the environment instead of chewing threw another register. - - - - - c6264a2d by Ben Gamari at 2020-11-11T03:20:00-05:00 codeGen: Produce local symbols for module-internal functions It turns out that some important native debugging/profiling tools (e.g. perf) rely only on symbol tables for function name resolution (as opposed to using DWARF DIEs). However, previously GHC would emit temporary symbols (e.g. `.La42b`) to identify module-internal entities. Such symbols are dropped during linking and therefore not visible to runtime tools (in addition to having rather un-helpful unique names). For instance, `perf report` would often end up attributing all cost to the libc `frame_dummy` symbol since Haskell code was no covered by any proper symbol (see #17605). We now rather follow the model of C compilers and emit descriptively-named local symbols for module internal things. Since this will increase object file size this behavior can be disabled with the `-fno-expose-internal-symbols` flag. With this `perf record` can finally be used against Haskell executables. Even more, with `-g3` `perf annotate` provides inline source code. - - - - - 584058dd by Ben Gamari at 2020-11-11T03:20:00-05:00 Enable -fexpose-internal-symbols when debug level >=2 This seems like a reasonable default as the object file size increases by around 5%. - - - - - c34a4b98 by Ömer Sinan Ağacan at 2020-11-11T03:20:35-05:00 Fix and enable object unloading in GHCi Fixes #16525 by tracking dependencies between object file symbols and marking symbol liveness during garbage collection See Note [Object unloading] in CheckUnload.c for details. - - - - - 2782487f by Ray Shih at 2020-11-11T03:20:35-05:00 Add loadNativeObj and unloadNativeObj (This change is originally written by niteria) This adds two functions: * `loadNativeObj` * `unloadNativeObj` and implements them for Linux. They are useful if you want to load a shared object with Haskell code using the system linker and have GHC call dlclose() after the code is no longer referenced from the heap. Using the system linker allows you to load the shared object above outside the low-mem region. It also loads the DWARF sections in a way that `perf` understands. `dl_iterate_phdr` is what makes this implementation Linux specific. - - - - - 7a65f9e1 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 rts: Introduce highMemDynamic - - - - - e9e1b2e7 by GHC GitLab CI at 2020-11-11T03:20:35-05:00 Introduce test for dynamic library unloading This uses the highMemDynamic flag introduced earlier to verify that dynamic objects are properly unloaded. - - - - - 5506f134 by Krzysztof Gogolewski at 2020-11-11T03:21:14-05:00 Force argument in setIdMult (#18925) - - - - - 787e93ae by Ben Gamari at 2020-11-11T23:14:11-05:00 testsuite: Add testcase for #18733 - - - - - 5353fd50 by Ben Gamari at 2020-11-12T10:05:30-05:00 compiler: Fix recompilation checking In ticket #18733 we noticed a rather serious deficiency in the current fingerprinting logic for recursive groups. I have described the old fingerprinting story and its problems in Note [Fingerprinting recursive groups] and have reworked the story accordingly to avoid these issues. Fixes #18733. - - - - - 63fa3997 by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Rework `ArityType` to fix monotonicity (#18870) As we found out in #18870, `andArityType` is not monotone, with potentially severe consequences for termination of fixed-point iteration. That showed in an abundance of "Exciting arity" DEBUG messages that are emitted whenever we do more than one step in fixed-point iteration. The solution necessitates also recording `OneShotInfo` info for `ABot` arity type. Thus we get the following definition for `ArityType`: ``` data ArityType = AT [OneShotInfo] Divergence ``` The majority of changes in this patch are the result of refactoring use sites of `ArityType` to match the new definition. The regression test `T18870` asserts that we indeed don't emit any DEBUG output anymore for a function where we previously would have. Similarly, there's a regression test `T18937` for #18937, which we expect to be broken for now. Fixes #18870. - - - - - 197d59fa by Sebastian Graf at 2020-11-13T14:29:39-05:00 Arity: Emit "Exciting arity" warning only after second iteration (#18937) See Note [Exciting arity] why we emit the warning at all and why we only do after the second iteration now. Fixes #18937. - - - - - de7ec9dd by David Eichmann at 2020-11-13T14:30:16-05:00 Add rts_listThreads and rts_listMiscRoots to RtsAPI.h These are used to find the current roots of the garbage collector. Co-authored-by: Sven Tennie's avatarSven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering's avatarMatthew Pickering <matthewtpickering at gmail.com> Co-authored-by: default avatarBen Gamari <bgamari.foss at gmail.com> - - - - - 24a86f09 by Ben Gamari at 2020-11-13T14:30:51-05:00 gitlab-ci: Cache cabal store in linting job - - - - - 0a7e592c by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Fix procedure end addresses Previously the `.debug_aranges` and `.debug_info` (DIE) DWARF information would claim that procedures (represented with a `DW_TAG_subprogram` DIE) would only span the range covered by their entry block. This omitted all of the continuation blocks (represented by `DW_TAG_lexical_block` DIEs), confusing `perf`. Fix this by introducing a end-of-procedure label and using this as the `DW_AT_high_pc` of procedure `DW_TAG_subprogram` DIEs Fixes #17605. - - - - - 1e19183d by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Only produce DW_AT_source_note DIEs in -g3 Standard debugging tools don't know how to understand these so let's not produce them unless asked. - - - - - ad73370f by Ben Gamari at 2020-11-15T03:35:45-05:00 nativeGen/dwarf: Use DW_AT_linkage instead of DW_AT_MIPS_linkage - - - - - a2539650 by Ben Gamari at 2020-11-15T03:35:45-05:00 gitlab-ci: Add DWARF release jobs for Debian 10, Fedora27 - - - - - d61adb3d by Ryan Scott at 2020-11-15T03:36:21-05:00 Name (tc)SplitForAll- functions more consistently There is a zoo of `splitForAll-` functions in `GHC.Core.Type` (as well as `tcSplitForAll-` functions in `GHC.Tc.Utils.TcType`) that all do very similar things, but vary in the particular form of type variable that they return. To make things worse, the names of these functions are often quite misleading. Some particularly egregious examples: * `splitForAllTys` returns `TyCoVar`s, but `splitSomeForAllTys` returns `VarBndr`s. * `splitSomeForAllTys` returns `VarBndr`s, but `tcSplitSomeForAllTys` returns `TyVar`s. * `splitForAllTys` returns `TyCoVar`s, but `splitForAllTysInvis` returns `InvisTVBinder`s. (This in particular arose in the context of #18939, and this finally motivated me to bite the bullet and improve the status quo vis-à-vis how we name these functions.) In an attempt to bring some sanity to how these functions are named, I have opted to rename most of these functions en masse to use consistent suffixes that describe the particular form of type variable that each function returns. In concrete terms, this amounts to: * Functions that return a `TyVar` now use the suffix `-TyVar`. This caused the following functions to be renamed: * `splitTyVarForAllTys` -> `splitForAllTyVars` * `splitForAllTy_ty_maybe` -> `splitForAllTyVar_maybe` * `tcSplitForAllTys` -> `tcSplitForAllTyVars` * `tcSplitSomeForAllTys` -> `tcSplitSomeForAllTyVars` * Functions that return a `CoVar` now use the suffix `-CoVar`. This caused the following functions to be renamed: * `splitForAllTy_co_maybe` -> `splitForAllCoVar_maybe` * Functions that return a `TyCoVar` now use the suffix `-TyCoVar`. This caused the following functions to be renamed: * `splitForAllTy` -> `splitForAllTyCoVar` * `splitForAllTys` -> `splitForAllTyCoVars` * `splitForAllTys'` -> `splitForAllTyCoVars'` * `splitForAllTy_maybe` -> `splitForAllTyCoVar_maybe` * Functions that return a `VarBndr` now use the suffix corresponding to the most relevant type synonym. This caused the following functions to be renamed: * `splitForAllVarBndrs` -> `splitForAllTyCoVarBinders` * `splitForAllTysInvis` -> `splitForAllInvisTVBinders` * `splitForAllTysReq` -> `splitForAllReqTVBinders` * `splitSomeForAllTys` -> `splitSomeForAllTyCoVarBndrs` * `tcSplitForAllVarBndrs` -> `tcSplitForAllTyVarBinders` * `tcSplitForAllTysInvis` -> `tcSplitForAllInvisTVBinders` * `tcSplitForAllTysReq` -> `tcSplitForAllReqTVBinders` * `tcSplitForAllTy_maybe` -> `tcSplitForAllTyVarBinder_maybe` Note that I left the following functions alone: * Functions that split apart things besides `ForAllTy`s, such as `splitFunTys` or `splitPiTys`. Thankfully, there are far fewer of these functions than there are functions that split apart `ForAllTy`s, so there isn't much of a pressing need to apply the new naming convention elsewhere. * Functions that split apart `ForAllCo`s in `Coercion`s, such as `GHC.Core.Coercion.splitForAllCo_maybe`. We could theoretically apply the new naming convention here, but then we'd have to figure out how to disambiguate `Type`-splitting functions from `Coercion`-splitting functions. Ultimately, the `Coercion`-splitting functions aren't used nearly as much as the `Type`-splitting functions, so I decided to leave the former alone. This is purely refactoring and should cause no change in behavior. - - - - - 645444af by Ryan Scott at 2020-11-15T03:36:21-05:00 Use tcSplitForAllInvisTyVars (not tcSplitForAllTyVars) in more places The use of `tcSplitForAllTyVars` in `tcDataFamInstHeader` was the immediate cause of #18939, and replacing it with a new `tcSplitForAllInvisTyVars` function (which behaves like `tcSplitForAllTyVars` but only splits invisible type variables) fixes the issue. However, this led me to realize that _most_ uses of `tcSplitForAllTyVars` in GHC really ought to be `tcSplitForAllInvisTyVars` instead. While I was in town, I opted to replace most uses of `tcSplitForAllTys` with `tcSplitForAllTysInvis` to reduce the likelihood of such bugs in the future. I say "most uses" above since there is one notable place where we _do_ want to use `tcSplitForAllTyVars`: in `GHC.Tc.Validity.forAllTyErr`, which produces the "`Illegal polymorphic type`" error message if you try to use a higher-rank `forall` without having `RankNTypes` enabled. Here, we really do want to split all `forall`s, not just invisible ones, or we run the risk of giving an inaccurate error message in the newly added `T18939_Fail` test case. I debated at some length whether I wanted to name the new function `tcSplitForAllInvisTyVars` or `tcSplitForAllTyVarsInvisible`, but in the end, I decided that I liked the former better. For consistency's sake, I opted to rename the existing `splitPiTysInvisible` and `splitPiTysInvisibleN` functions to `splitInvisPiTys` and `splitPiTysInvisN`, respectively, so that they use the same naming convention. As a consequence, this ended up requiring a `haddock` submodule bump. Fixes #18939. - - - - - 8887102f by Moritz Angermann at 2020-11-15T03:36:56-05:00 AArch64/arm64 adjustments This addes the necessary logic to support aarch64 on elf, as well as aarch64 on mach-o, which Apple calls arm64. We change architecture name to AArch64, which is the official arm naming scheme. - - - - - fc644b1a by Ben Gamari at 2020-11-15T03:37:31-05:00 ghc-bin: Build with eventlogging by default We now have all sorts of great facilities using the eventlog which were previously unavailable without building a custom GHC. Fix this by linking with `-eventlog` by default. - - - - - 52114fa0 by Sylvain Henry at 2020-11-16T11:48:47+01:00 Add Addr# atomic primops (#17751) This reuses the codegen used for ByteArray#'s atomic primops. - - - - - 8150f654 by Sebastian Graf at 2020-11-18T23:38:40-05:00 PmCheck: Print types of uncovered patterns (#18932) In order to avoid confusion as in #18932, we display the type of the match variables in the non-exhaustiveness warning, e.g. ``` T18932.hs:14:1: warning: [-Wincomplete-patterns] Pattern match(es) are non-exhaustive In an equation for ‘g’: Patterns of type ‘T a’, ‘T a’, ‘T a’ not matched: (MkT2 _) (MkT1 _) (MkT1 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) (MkT1 _) (MkT2 _) (MkT2 _) (MkT2 _) ... | 14 | g (MkT1 x) (MkT1 _) (MkT1 _) = x | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ ``` It also allows us to omit the type signature on wildcard matches which we previously showed in only some situations, particularly `-XEmptyCase`. Fixes #18932. - - - - - 165352a2 by Krzysztof Gogolewski at 2020-11-20T02:08:36-05:00 Export indexError from GHC.Ix (#18579) - - - - - b57845c3 by Kamil Dworakowski at 2020-11-20T02:09:16-05:00 Clarify interruptible FFI wrt masking state - - - - - 321d1bd8 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Fix strictness signatures of `prefetchValue*#` primops Their strictness signatures said the primops are strict in their first argument, which is wrong: Handing it a thunk will prefetch the pointer to the thunk, but not evaluate it. Hence not strict. The regression test `T8256` actually tests for laziness in the first argument, so GHC apparently never exploited the strictness signature. See also https://gitlab.haskell.org/ghc/ghc/-/issues/8256#note_310867, where this came up. - - - - - 0aec78b6 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Demand: Interleave usage and strictness demands (#18903) As outlined in #18903, interleaving usage and strictness demands not only means a more compact demand representation, but also allows us to express demands that we weren't easily able to express before. Call demands are *relative* in the sense that a call demand `Cn(cd)` on `g` says "`g` is called `n` times. *Whenever `g` is called*, the result is used according to `cd`". Example from #18903: ```hs h :: Int -> Int h m = let g :: Int -> (Int,Int) g 1 = (m, 0) g n = (2 * n, 2 `div` n) {-# NOINLINE g #-} in case m of 1 -> 0 2 -> snd (g m) _ -> uncurry (+) (g m) ``` Without the interleaved representation, we would just get `L` for the strictness demand on `g`. Now we are able to express that whenever `g` is called, its second component is used strictly in denoting `g` by `1C1(P(1P(U),SP(U)))`. This would allow Nested CPR to unbox the division, for example. Fixes #18903. While fixing regressions, I also discovered and fixed #18957. Metric Decrease: T13253-spj - - - - - 3a55b3a2 by Sebastian Graf at 2020-11-20T02:09:51-05:00 Update user's guide entry on demand analysis and worker/wrapper The demand signature notation has been undocumented for a long time. The only source to understand it, apart from reading the `Outputable` instance, has been an outdated wiki page. Since the previous commits have reworked the demand lattice, I took it as an opportunity to also write some documentation about notation. - - - - - fc963932 by Greg Steuck at 2020-11-20T02:10:31-05:00 Find hadrian location more reliably in cabal-install output Fix #18944 - - - - - 9f40cf6c by Ben Gamari at 2020-11-20T02:11:07-05:00 rts/linker: Align bssSize to page size when mapping symbol extras We place symbol_extras right after bss. We also need to ensure that symbol_extras can be mprotect'd independently from the rest of the image. To ensure this we round up the size of bss to a page boundary, thus ensuring that symbol_extras is also page-aligned. - - - - - b739c319 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add usage message to ci.sh - - - - - 802e9180 by Ben Gamari at 2020-11-20T02:11:43-05:00 gitlab-ci: Add VERBOSE environment variable And change the make build system's default behavior to V=0, greatly reducing build log sizes. - - - - - 2a8a979c by Ben Gamari at 2020-11-21T01:13:26-05:00 users-guide: A bit of clean-up in profiling flag documentation - - - - - 56804e33 by Ben Gamari at 2020-11-21T01:13:26-05:00 testsuite: Refactor CountParserDeps - - - - - 53ad67ea by Ben Gamari at 2020-11-21T01:13:26-05:00 Introduce -fprof-callers flag This introducing a new compiler flag to provide a convenient way to introduce profiler cost-centers on all occurrences of the named identifier. Closes #18566. - - - - - ecfd0278 by Sylvain Henry at 2020-11-21T01:14:09-05:00 Move Plugins into HscEnv (#17957) Loaded plugins have nothing to do in DynFlags so this patch moves them into HscEnv (session state). "DynFlags plugins" become "Driver plugins" to still be able to register static plugins. Bump haddock submodule - - - - - 72f2257c by Sylvain Henry at 2020-11-21T01:14:09-05:00 Don't initialize plugins in the Core2Core pipeline Some plugins can be added via TH (cf addCorePlugin). Initialize them in the driver instead of in the Core2Core pipeline. - - - - - ddbeeb3c by Ryan Scott at 2020-11-21T01:14:44-05:00 Add regression test for #10504 This issue was fixed at some point between GHC 8.0 and 8.2. Let's add a regression test to ensure that it stays fixed. Fixes #10504. - - - - - a4a6dc2a by Ben Gamari at 2020-11-21T01:15:21-05:00 dwarf: Apply info table offset consistently Previously we failed to apply the info table offset to the aranges and DIEs, meaning that we often failed to unwind in gdb. For some reason this only seemed to manifest in the RTS's Cmm closures. Nevertheless, now we can unwind completely up to `main` - - - - - 69bfbc21 by Ben Gamari at 2020-11-21T01:15:56-05:00 hadrian: Disable stripping when debug information is enabled - - - - - 7e93ae8b by Ben Gamari at 2020-11-21T13:13:29-05:00 rts: Post ticky entry counts to the eventlog We currently only post the entry counters, not the other global counters as in my experience the former are more useful. We use the heap profiler's census period to decide when to dump. Also spruces up the documentation surrounding ticky-ticky a bit. - - - - - bc9c3916 by Ben Gamari at 2020-11-22T06:28:10-05:00 Implement -ddump-c-backend argument To dump output of the C backend. - - - - - 901bc220 by Ben Gamari at 2020-11-22T12:39:02-05:00 Bump time submodule to 1.11.1 Also bumps directory, Cabal, hpc, time, and unix submodules. Closes #18847. - - - - - 92c0afbf by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Dump STG when ticky is enabled This changes the "ticky" modifier to enable dumping of final STG as this is generally needed to make sense of the ticky profiles. - - - - - d23fef68 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Introduce notion of flavour transformers This extends Hadrian's notion of "flavour", as described in #18942. - - - - - 179d0bec by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add a viaLlvmBackend modifier Note that this also slightly changes the semantics of these flavours as we only use LLVM for >= stage1 builds. - - - - - d4d95e51 by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Add profiled_ghc and no_dynamic_ghc modifiers - - - - - 6815603f by Ben Gamari at 2020-11-22T12:39:38-05:00 hadrian: Drop redundant flavour definitions Drop the profiled, LLVM, and ThreadSanitizer flavour definitions as these can now be realized with flavour transformers. - - - - - f88f4339 by Ben Gamari at 2020-11-24T02:43:20-05:00 rts: Flush eventlog buffers from flushEventLog As noted in #18043, flushTrace failed flush anything beyond the writer. This means that a significant amount of data sitting in capability-local event buffers may never get flushed, despite the users' pleads for us to flush. Fix this by making flushEventLog flush all of the event buffers before flushing the writer. Fixes #18043. - - - - - 7c03cc50 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM job on appropriately-labelled MRs Namely, those marked with the ~"LLVM backend" label - - - - - 9b95d815 by Ben Gamari at 2020-11-24T02:43:55-05:00 gitlab-ci: Run LLVM builds on Debian 10 The current Debian 9 image doesn't provide LLVM 7. - - - - - 2ed3e6c0 by Ben Gamari at 2020-11-24T02:43:55-05:00 CmmToLlvm: Declare signature for memcmp Otherwise `opt` fails with: error: use of undefined value '@memcmp$def' - - - - - be5d74ca by Moritz Angermann at 2020-11-26T16:00:32-05:00 [Sized Cmm] properly retain sizes. This replaces all Word<N> = W<N># Word# and Int<N> = I<N># Int# with Word<N> = W<N># Word<N># and Int<N> = I<N># Int<N>#, thus providing us with properly sized primitives in the codegenerator instead of pretending they are all full machine words. This came up when implementing darwinpcs for arm64. The darwinpcs reqires us to pack function argugments in excess of registers on the stack. While most procedure call standards (pcs) assume arguments are just passed in 8 byte slots; and thus the caller does not know the exact signature to make the call, darwinpcs requires us to adhere to the prototype, and thus have the correct sizes. If we specify CInt in the FFI call, it should correspond to the C int, and not just be Word sized, when it's only half the size. This does change the expected output of T16402 but the new result is no less correct as it eliminates the narrowing (instead of the `and` as was previously done). Bumps the array, bytestring, text, and binary submodules. Co-Authored-By: Ben Gamari <ben at well-typed.com> Metric Increase: T13701 T14697 - - - - - a84e53f9 by Andreas Klebinger at 2020-11-26T16:00:32-05:00 RTS: Fix failed inlining of copy_tag. On windows using gcc-10 gcc failed to inline copy_tag into evacuate. To fix this we now set the always_inline attribute for the various copy* functions in Evac.c. The main motivation here is not the overhead of the function call, but rather that this allows the code to "specialize" for the size of the closure we copy which is often known at compile time. An earlier commit also tried to avoid evacuate_large inlining. But didn't quite succeed. So I also marked evacuate_large as noinline. Fixes #12416 - - - - - cdbd16f5 by Sylvain Henry at 2020-11-26T16:00:33-05:00 Fix toArgRep to support 64-bit reps on all systems [This is @Ericson2314 writing a commit message for @hsyl20's patch.] (Progress towards #11953, #17377, #17375) `Int64Rep` and `Word64Rep` are currently broken on 64-bit systems. This is because they should use "native arg rep" but instead use "large arg rep" as they do on 32-bit systems, which is either a non-concept or a 128-bit rep depending on one's vantage point. Now, these reps currently aren't used during 64-bit compilation, so the brokenness isn't observed, but I don't think that constitutes reasons not to fix it. Firstly, the linked issues there is a clearly expressed desire to use explicit-bitwidth constructs in more places. Secondly, per [1], there are other bugs that *do* manifest from not threading explicit-bitwidth information all the way through the compilation pipeline. One can therefore view this as one piece of the larger effort to do that, improve ergnomics, and squash remaining bugs. Also, this is needed for !3658. I could just merge this as part of that, but I'm keen on merging fixes "as they are ready" so the fixes that aren't ready are isolated and easier to debug. [1]: https://mail.haskell.org/pipermail/ghc-devs/2020-October/019332.html - - - - - a9378e69 by Tim Barnes at 2020-11-26T16:00:34-05:00 Set dynamic users-guide TOC spacing (fixes #18554) - - - - - 86a59d93 by Ben Gamari at 2020-11-26T16:00:34-05:00 rts: Use RTS_LIKELY in CHECK Most compilers probably already infer that `barf` diverges but it nevertheless doesn't hurt to be explicit. - - - - - 5757e82b by Matthew Pickering at 2020-11-26T16:00:35-05:00 Remove special case for GHC.ByteCode.Instr This was added in https://github.com/nomeata/ghc-heap-view/commit/34935206e51b9c86902481d84d2f368a6fd93423 GHC.ByteCode.Instr.BreakInfo no longer exists so the special case is dead code. Any check like this can be easily dealt with in client code. - - - - - d9c8b5b4 by Matthew Pickering at 2020-11-26T16:00:35-05:00 Split Up getClosureDataFromHeapRep Motivation 1. Don't enforce the repeated decoding of an info table, when the client can cache it (ghc-debug) 2. Allow the constructor information decoding to be overridden, this casues segfaults in ghc-debug - - - - - 3e3555cc by Andreas Klebinger at 2020-11-26T16:00:35-05:00 RegAlloc: Add missing raPlatformfield to RegAllocStatsSpill Fixes #18994 Co-Author: Benjamin Maurer <maurer.benjamin at gmail.com> - - - - - a1a75aa9 by Ben Gamari at 2020-11-27T06:20:41-05:00 rts: Allocate MBlocks with MAP_TOP_DOWN on Windows As noted in #18991, we would previously allocate heap in low memory. Due to this the linker, which typically *needs* low memory, would end up competing with the heap. In longer builds we end up running out of low memory entirely, leading to linking failures. - - - - - 75fc1ed5 by Sylvain Henry at 2020-11-28T15:40:23-05:00 Hadrian: fix detection of ghc-pkg for cross-compilers - - - - - 7cb5df96 by Sylvain Henry at 2020-11-28T15:40:23-05:00 hadrian: fix ghc-pkg uses (#17601) Make sure ghc-pkg doesn't read the compiler "settings" file by passing --no-user-package-db. - - - - - e3fd4226 by Ben Gamari at 2020-11-28T15:40:23-05:00 gitlab-ci: Introduce a nightly cross-compilation job This adds a job to test cross-compilation from x86-64 to AArch64 with Hadrian. Fixes #18234 - - - - - 698d3d96 by Ben Gamari at 2020-11-28T15:41:00-05:00 gitlab-ci: Only deploy GitLab Pages in ghc/ghc> The deployments are quite large and yet are currently only served for the ghc/ghc> project. - - - - - 625726f9 by David Eichmann at 2020-11-28T15:41:37-05:00 ghc-heap: partial TSO/STACK decoding Co-authored-by: Sven Tennie <sven.tennie at gmail.com> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 22ea9c29 by Andreas Klebinger at 2020-11-28T15:42:13-05:00 Small optimization to CmmSink. Inside `regsUsedIn` we can avoid some thunks by specializing the recursion. In particular we avoid the thunk for `(f e z)` in the MachOp/Load branches, where we know this will evaluate to z. Reduces allocations for T3294 by ~1%. - - - - - bba42c62 by John Ericson at 2020-11-28T15:42:49-05:00 Make primop handler indentation more consistent - - - - - c82bc8e9 by John Ericson at 2020-11-28T15:42:49-05:00 Cleanup some primop constructor names Harmonize the internal (big sum type) names of the native vs fixed-sized number primops a bit. (Mainly by renaming the former.) No user-facing names are changed. - - - - - ae14f160 by Ben Gamari at 2020-11-28T15:43:25-05:00 testsuite: Mark T14702 as fragile on Windows Due to #18953. - - - - - 1bc104b0 by Ben Gamari at 2020-11-29T15:33:18-05:00 withTimings: Emit allocations counter This will allow us to back out the allocations per compiler pass from the eventlog. Note that we dump the allocation counter rather than the difference since this will allow us to determine how much work is done *between* `withTiming` blocks. - - - - - e992ea84 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 ThreadPaused: Don't zero slop until free vars are pushed When threadPaused blackholes a thunk it calls `OVERWRITING_CLOSURE` to zero the slop for the benefit of the sanity checker. Previously this was done *before* pushing the thunk's free variables to the update remembered set. Consequently we would pull zero'd pointers to the update remembered set. - - - - - e82cd140 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Fix regression from TSAN work The TSAN rework (specifically aad1f803) introduced a subtle regression in GC.c, swapping `g0` in place of `gen`. Whoops! Fixes #18997. - - - - - 35a5207e by GHC GitLab CI at 2020-11-29T15:33:54-05:00 rts/Messages: Add missing write barrier in THROWTO message update After a THROWTO message has been handle the message closure is overwritten by a NULL message. We must ensure that the original closure's pointers continue to be visible to the nonmoving GC. - - - - - 0120829f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Add missing write barrier in shrinkSmallByteArray - - - - - 8a4d8fb6 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 Updates: Don't zero slop until closure has been pushed Ensure that the the free variables have been pushed to the update remembered set before we zero the slop. - - - - - 2793cfdc by GHC GitLab CI at 2020-11-29T15:33:54-05:00 OSThreads: Fix error code checking pthread_join returns its error code and apparently doesn't set errno. - - - - - e391a16f by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Don't join to mark_thread on shutdown The mark thread is not joinable as we detach from it on creation. - - - - - 60d088ab by Ben Gamari at 2020-11-29T15:33:54-05:00 nonmoving: Add reference to Ueno 2016 - - - - - 3aa60362 by GHC GitLab CI at 2020-11-29T15:33:54-05:00 nonmoving: Ensure that evacuated large objects are marked See Note [Non-moving GC: Marking evacuated objects]. - - - - - 8d304a99 by Ben Gamari at 2020-11-30T10:15:22-05:00 rts/m32: Refactor handling of allocator seeding Previously, in an attempt to reduce fragmentation, each new allocator would map a region of M32_MAX_PAGES fresh pages to seed itself. However, this ends up being extremely wasteful since it turns out that we often use fewer than this. Consequently, these pages end up getting freed which, ends up fragmenting our address space more than than we would have if we had naively allocated pages on-demand. Here we refactor m32 to avoid this waste while achieving the fragmentation mitigation previously desired. In particular, we move all page allocation into the global m32_alloc_page, which will pull a page from the free page pool. If the free page pool is empty we then refill it by allocating a region of M32_MAP_PAGES and adding them to the pool. Furthermore, we do away with the initial seeding entirely. That is, the allocator starts with no active pages: pages are rather allocated on an as-needed basis. On the whole this ends up being a pleasingly simple change, simultaneously making m32 more efficient, more robust, and simpler. Fixes #18980. - - - - - b6629289 by Ben Gamari at 2020-11-30T10:15:58-05:00 rts: Use CHECK instead of assert Use the GHC wrappers instead of <assert.h>. - - - - - 9f4efa6a by Ben Gamari at 2020-11-30T10:15:58-05:00 rts/linker: Replace some ASSERTs with CHECK In the past some people have confused ASSERT, which is for checking internal invariants, which CHECK, which should be used when checking things that might fail due to bad input (and therefore should be enabled even in the release compiler). Change some of these cases in the linker to use CHECK. - - - - - 0f8a4655 by Ryan Scott at 2020-11-30T10:16:34-05:00 Allow deploy:pages job to fail See #18973. - - - - - c7c87c05 by Ben Gamari at 2020-11-30T18:58:31-05:00 gitlab-ci: Fix copy-paste error Also be more consistent in quoting. - - - - - cfd02c95 by Ben Gamari at 2020-11-30T18:59:01-05:00 gitlab-ci: Run linters through ci.sh Ensuring that the right toolchain is used. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/ci.sh - aclocal.m4 - + compiler/.hlint.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types.hs-boot - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/Utils.hs - + compiler/GHC/Builtin/bytearray-ops.txt.pp - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/InfoTable.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Dataflow/Collections.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/DebugBlock.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 The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0e2db641c6e938282f135e108eb5eda50e172071...cfd02c95b931dd250ddc75b2038a8a9684cd9f9d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0e2db641c6e938282f135e108eb5eda50e172071...cfd02c95b931dd250ddc75b2038a8a9684cd9f9d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: